Implement 'ghcup test ghc' based on the bindist testsuite

This commit is contained in:
Julian Ospald 2023-01-08 19:29:35 +08:00
parent 54af66d115
commit 1e32639873
Signed by: hasufell
GPG Key ID: 3786C5262ECB4A3F
12 changed files with 1199 additions and 480 deletions

View File

@ -8,6 +8,7 @@
module GHCup.OptParse (
module GHCup.OptParse.Common
, module GHCup.OptParse.Install
, module GHCup.OptParse.Test
, module GHCup.OptParse.Set
, module GHCup.OptParse.UnSet
, module GHCup.OptParse.Rm
@ -31,6 +32,7 @@ module GHCup.OptParse (
import GHCup.OptParse.Common
import GHCup.OptParse.Install
import GHCup.OptParse.Test
import GHCup.OptParse.Set
import GHCup.OptParse.UnSet
import GHCup.OptParse.Rm
@ -87,6 +89,7 @@ data Options = Options
data Command
= Install (Either InstallCommand InstallOptions)
| Test TestCommand
| InstallCabalLegacy InstallOptions
| Set (Either SetCommand SetOptions)
| UnSet UnsetCommand
@ -205,6 +208,14 @@ com =
<> footerDoc (Just $ text installToolFooter)
)
)
<> command
"test"
(info
(Test <$> testParser <**> helper)
( progDesc "Run tests for a tool (if any) [EXPERIMENTAL!]"
<> footerDoc (Just $ text testFooter)
)
)
<> command
"set"
(info

View File

@ -254,7 +254,7 @@ run RunOptions{..} runAppState leanAppstate runLogger = do
liftIO $ putStr tmp
pure ExitSuccess
(cmd:args) -> do
newEnv <- liftIO $ addToPath tmp
newEnv <- liftIO $ addToPath tmp runAppendPATH
#ifndef IS_WINDOWS
void $ liftIO $ SPP.executeFile cmd True args (Just newEnv)
pure ExitSuccess
@ -441,17 +441,6 @@ run RunOptions{..} runAppState leanAppstate runLogger = do
liftE $ setHLS v SetHLS_XYZ (Just tmp)
liftE $ setHLS v SetHLSOnly (Just tmp)
addToPath path = do
cEnv <- Map.fromList <$> getEnvironment
let paths = ["PATH", "Path"]
curPaths = (\x -> maybe [] splitSearchPath (Map.lookup x cEnv)) =<< paths
newPath = intercalate [searchPathSeparator] (if runAppendPATH then (curPaths ++ [path]) else (path : curPaths))
envWithoutPath = foldr (\x y -> Map.delete x y) cEnv paths
pathVar = if isWindows then "Path" else "PATH"
envWithNewPath = Map.toList $ Map.insert pathVar newPath envWithoutPath
liftIO $ setEnv pathVar newPath
return envWithNewPath
createTmpDir :: ( MonadUnliftIO m
, MonadCatch m
, MonadThrow m

View File

@ -0,0 +1,188 @@
{-# LANGUAGE CPP #-}
{-# LANGUAGE DataKinds #-}
{-# LANGUAGE TypeApplications #-}
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE TemplateHaskell #-}
{-# LANGUAGE QuasiQuotes #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE DuplicateRecordFields #-}
{-# LANGUAGE ViewPatterns #-}
{-# LANGUAGE TypeOperators #-}
module GHCup.OptParse.Test where
import GHCup.OptParse.Common
import GHCup
import GHCup.Errors
import GHCup.Types
import GHCup.Utils.Dirs
import GHCup.Prelude.Logger
import GHCup.Prelude.String.QQ
import Codec.Archive
#if !MIN_VERSION_base(4,13,0)
import Control.Monad.Fail ( MonadFail )
#endif
import Control.Monad.Reader
import Control.Monad.Trans.Resource
import Data.Functor
import Data.Maybe
import Haskus.Utils.Variant.Excepts
import Options.Applicative hiding ( style )
import Options.Applicative.Help.Pretty ( text )
import Prelude hiding ( appendFile )
import System.Exit
import URI.ByteString hiding ( uriParser )
import qualified Data.Text as T
----------------
--[ Commands ]--
----------------
data TestCommand = TestGHC TestOptions
---------------
--[ Options ]--
---------------
data TestOptions = TestOptions
{ testVer :: Maybe ToolVersion
, testBindist :: Maybe URI
, addMakeArgs :: [T.Text]
}
---------------
--[ Footers ]--
---------------
testFooter :: String
testFooter = [s|Discussion:
Runs test suites from the test bindist.|]
---------------
--[ Parsers ]--
---------------
testParser :: Parser TestCommand
testParser =
subparser
( command
"ghc"
( TestGHC
<$> info
(testOpts (Just GHC) <**> helper)
( progDesc "Test GHC"
<> footerDoc (Just $ text testGHCFooter)
)
)
)
where
testGHCFooter :: String
testGHCFooter = [s|Discussion:
Runs the GHC test suite from the test bindist.|]
testOpts :: Maybe Tool -> Parser TestOptions
testOpts tool =
(\(u, v) args -> TestOptions v u args)
<$> ( ( (,)
<$> optional
(option
(eitherReader uriParser)
(short 'u' <> long "url" <> metavar "BINDIST_URL" <> help
"Install the specified version from this bindist"
<> completer (toolDlCompleter (fromMaybe GHC tool))
)
)
<*> (Just <$> toolVersionTagArgument Nothing tool)
)
<|> pure (Nothing, Nothing)
)
<*> many (argument str (metavar "MAKE_ARGS" <> help "Additional arguments to 'make', prefix with '-- ' (longopts)"))
---------------------------
--[ Effect interpreters ]--
---------------------------
type TestGHCEffects = [ DigestError
, ContentLengthError
, GPGError
, DownloadFailed
, NoDownload
, ArchiveResult
, TarDirDoesNotExist
, UnknownArchive
, TestFailed
, NextVerNotFound
, TagNotFound
, NoToolVersionSet
]
runTestGHC :: AppState
-> Excepts TestGHCEffects (ResourceT (ReaderT AppState IO)) a
-> IO (VEither TestGHCEffects a)
runTestGHC appstate' =
flip runReaderT appstate'
. runResourceT
. runE
@TestGHCEffects
-------------------
--[ Entrypoints ]--
-------------------
test :: TestCommand -> Settings -> IO AppState -> (ReaderT LeanAppState IO () -> IO ()) -> IO ExitCode
test testCommand settings getAppState' runLogger = case testCommand of
(TestGHC iopts) -> go iopts
where
go :: TestOptions -> IO ExitCode
go TestOptions{..} = do
s'@AppState{ dirs = Dirs{ .. } } <- liftIO getAppState'
(case testBindist of
Nothing -> runTestGHC s' $ do
(v, vi) <- liftE $ fromVersion testVer GHC
liftE $ testGHCVer (_tvVersion v) addMakeArgs
pure vi
Just uri -> do
runTestGHC s'{ settings = settings {noVerify = True}} $ do
(v, vi) <- liftE $ fromVersion testVer GHC
liftE $ testGHCBindist (DownloadInfo uri (Just $ RegexDir ".*/.*") "" Nothing) (_tvVersion v) addMakeArgs
pure vi
)
>>= \case
VRight _ -> do
runLogger $ logInfo "GHC test successful"
pure ExitSuccess
VLeft e -> do
runLogger $ do
logError $ T.pack $ prettyHFError e
logError $ "Also check the logs in " <> T.pack (fromGHCupPath logsDir)
pure $ ExitFailure 3

View File

@ -295,6 +295,7 @@ Report bugs at <https://github.com/haskell/ghcup-hs/issues>|]
#endif
Install installCommand -> install installCommand settings appState runLogger
InstallCabalLegacy iopts -> install (Left (InstallCabal iopts)) settings appState runLogger
Test testCommand -> test testCommand settings appState runLogger
Set setCommand -> set setCommand runAppState runLeanAppState runLogger
UnSet unsetCommand -> unset unsetCommand runLeanAppState runLogger
List lo -> list lo no_color runAppState

View File

@ -14,7 +14,7 @@ source-repository-package
constraints: http-io-streams -brotli,
any.Cabal ==3.6.2.0,
any.aeson >= 2.0.1.0,
any.aeson >= 2.0.1.0
package libarchive
flags: -system-libarchive

View File

@ -1,4 +1,4 @@
cabal-version: 3.0
cabal-version: 2.4
name: ghcup
version: 0.1.18.1
license: LGPL-3.0-only
@ -219,6 +219,7 @@ executable ghcup
GHCup.OptParse.Rm
GHCup.OptParse.Run
GHCup.OptParse.Set
GHCup.OptParse.Test
GHCup.OptParse.ToolRequirements
GHCup.OptParse.UnSet
GHCup.OptParse.Upgrade

View File

@ -83,9 +83,10 @@ allHFError = unlines allErrors
, let proxy = Proxy :: Proxy ToolShadowed in format proxy
, let proxy = Proxy :: Proxy ContentLengthError in format proxy
, ""
, "# high level errors (5000+)"
, "# high level errors (4000+)"
, let proxy = Proxy :: Proxy DownloadFailed in format proxy
, let proxy = Proxy :: Proxy InstallSetError in format proxy
, let proxy = Proxy :: Proxy TestFailed in format proxy
, let proxy = Proxy :: Proxy BuildFailed in format proxy
, let proxy = Proxy :: Proxy GHCupSetError in format proxy
, ""
@ -161,7 +162,6 @@ prettyHFError e =
let errorCode = "GHCup-" <> padIntAndShow (eNum e)
in ("[" <> linkEscapeCode errorCode (hfErrorLink errorCode) <> "] ") <> prettyShow e
where
linkEscapeCode linkText link = "\ESC]8;;" <> link <> "\ESC\\" <> linkText <> "\ESC]8;;\ESC\\"
hfErrorLink errorCode = "https://errors.haskell.org/messages/" <> errorCode
padIntAndShow i
| i < 10 = "0000" <> show i
@ -178,6 +178,9 @@ class HFErrorProject a where
eDesc :: Proxy a -> String
linkEscapeCode :: String -> String -> String
linkEscapeCode linkText link = "\ESC]8;;" <> link <> "\ESC\\" <> linkText <> "\ESC]8;;\ESC\\"
------------------------
--[ Low-level errors ]--
@ -675,6 +678,22 @@ instance HFErrorProject InstallSetError where
eDesc _ = "Installation or setting the tool failed."
-- | A test failed.
data TestFailed = forall es . (ToVariantMaybe TestFailed es, PopVariant TestFailed es, Pretty (V es), Show (V es), HFErrorProject (V es)) => TestFailed FilePath (V es)
instance Pretty TestFailed where
pPrint (TestFailed path reason) =
case reason of
VMaybe (_ :: TestFailed) -> pPrint reason
_ -> text ("The test failed. GHC test suite is fragile and non-portable. Please also check out the " <> linkEscapeCode "issue tracker" " https://gitlab.haskell.org/ghc/ghc/-/issues/?sort=updated_desc&state=opened&label_name%5B%5D=testsuite&label_name%5B%5D=packaging&first_page_size=20" <> ".\nBuild dir was:") <+> text path <+> text "\nReason was:" <+> pPrint reason
deriving instance Show TestFailed
instance HFErrorProject TestFailed where
eBase _ = 4000
eNum (TestFailed _ xs2) = 4000 + eNum xs2
eDesc _ = "The test failed."
-- | A build failed.
data BuildFailed = forall es . (ToVariantMaybe BuildFailed es, PopVariant BuildFailed es, Pretty (V es), Show (V es), HFErrorProject (V es)) => BuildFailed FilePath (V es)

View File

@ -86,6 +86,144 @@ data GHCVer v = SourceDist v
--------------------
--[ Tool testing ]--
--------------------
testGHCVer :: ( MonadFail m
, MonadMask m
, MonadCatch m
, MonadReader env m
, HasDirs env
, HasSettings env
, HasPlatformReq env
, HasGHCupInfo env
, HasLog env
, MonadResource m
, MonadIO m
, MonadUnliftIO m
)
=> Version
-> [T.Text]
-> Excepts
'[ DigestError
, ContentLengthError
, GPGError
, DownloadFailed
, NoDownload
, ArchiveResult
, TarDirDoesNotExist
, UnknownArchive
, TestFailed
]
m
()
testGHCVer ver addMakeArgs = do
GHCupInfo { _ghcupDownloads = dls } <- lift getGHCupInfo
dlInfo <-
preview (ix GHC % ix ver % viTestDL % _Just) dls
?? NoDownload
liftE $ testGHCBindist dlInfo ver addMakeArgs
testGHCBindist :: ( MonadFail m
, MonadMask m
, MonadCatch m
, MonadReader env m
, HasDirs env
, HasSettings env
, HasPlatformReq env
, HasGHCupInfo env
, HasLog env
, MonadResource m
, MonadIO m
, MonadUnliftIO m
)
=> DownloadInfo
-> Version
-> [T.Text]
-> Excepts
'[ DigestError
, ContentLengthError
, GPGError
, DownloadFailed
, NoDownload
, ArchiveResult
, TarDirDoesNotExist
, UnknownArchive
, TestFailed
]
m
()
testGHCBindist dlinfo ver addMakeArgs = do
-- download (or use cached version)
dl <- liftE $ downloadCached dlinfo Nothing
liftE $ testPackedGHC dl (view dlSubdir dlinfo) ver addMakeArgs
testPackedGHC :: ( MonadMask m
, MonadCatch m
, MonadReader env m
, HasDirs env
, HasPlatformReq env
, HasSettings env
, MonadThrow m
, HasLog env
, MonadIO m
, MonadUnliftIO m
, MonadFail m
, MonadResource m
)
=> FilePath -- ^ Path to the packed GHC bindist
-> Maybe TarDir -- ^ Subdir of the archive
-> Version -- ^ The GHC version
-> [T.Text] -- ^ additional make args
-> Excepts
'[ ArchiveResult, UnknownArchive, TarDirDoesNotExist, TestFailed ] m ()
testPackedGHC dl msubdir ver addMakeArgs = do
-- unpack
tmpUnpack <- lift mkGhcupTmpDir
liftE $ cleanUpOnError tmpUnpack (unpackToDir (fromGHCupPath tmpUnpack) dl)
-- the subdir of the archive where we do the work
workdir <- maybe (pure tmpUnpack)
(liftE . intoSubdir tmpUnpack)
msubdir
reThrowAll @_ @'[ArchiveResult, UnknownArchive, TarDirDoesNotExist, ProcessError]
(TestFailed (fromGHCupPath workdir)) $ liftE $ runBuildAction tmpUnpack
(testUnpackedGHC workdir ver addMakeArgs)
testUnpackedGHC :: ( MonadReader env m
, HasDirs env
, HasSettings env
, MonadThrow m
, HasLog env
, MonadIO m
)
=> GHCupPath -- ^ Path to the unpacked GHC bindist (where the make file resides)
-> Version -- ^ The GHC version
-> [T.Text] -- ^ additional configure args for bindist
-> Excepts '[ProcessError] m ()
testUnpackedGHC path ver addMakeArgs = do
lift $ logInfo $ "Testing GHC version " <> prettyVer ver <> "!"
ghcDir <- lift $ ghcupGHCDir (mkTVer ver)
let ghcBinDir = fromGHCupPath ghcDir </> "bin"
env <- liftIO $ addToPath ghcBinDir False
lEM $ make' (fmap T.unpack addMakeArgs)
(Just $ fromGHCupPath path)
"ghc-test"
(Just $ ("STAGE1_GHC", "ghc-" <> T.unpack (prettyVer ver)) : env)
pure ()
---------------------
--[ Tool fetching ]--
---------------------

View File

@ -138,6 +138,7 @@ data VersionInfo = VersionInfo
{ _viTags :: [Tag] -- ^ version specific tag
, _viChangeLog :: Maybe URI
, _viSourceDL :: Maybe DownloadInfo -- ^ source tarball
, _viTestDL :: Maybe DownloadInfo -- ^ test tarball
, _viArch :: ArchitectureSpec -- ^ descend for binary downloads per arch
-- informative messages
, _viPostInstall :: Maybe Text

View File

@ -93,6 +93,7 @@ import qualified Data.List.NonEmpty as NE
import qualified Streamly.Prelude as S
import Control.DeepSeq (force)
import GHC.IO (evaluate)
import System.Environment (getEnvironment, setEnv)
-- $setup
@ -967,11 +968,28 @@ make :: ( MonadThrow m
=> [String]
-> Maybe FilePath
-> m (Either ProcessError ())
make args workdir = do
make args workdir = make' args workdir "ghc-make" Nothing
-- | Calls gmake if it exists in PATH, otherwise make.
make' :: ( MonadThrow m
, MonadIO m
, MonadReader env m
, HasDirs env
, HasLog env
, HasSettings env
)
=> [String]
-> Maybe FilePath
-> FilePath -- ^ log filename (opened in append mode)
-> Maybe [(String, String)] -- ^ optional environment
-> m (Either ProcessError ())
make' args workdir logfile menv = do
spaths <- liftIO getSearchPath
has_gmake <- isJust <$> liftIO (searchPath spaths "gmake")
let mymake = if has_gmake then "gmake" else "make"
execLogged mymake args workdir "ghc-make" Nothing
execLogged mymake args workdir logfile menv
makeOut :: (MonadReader env m, HasDirs env, MonadIO m)
=> [String]
@ -1282,6 +1300,22 @@ warnAboutHlsCompatibility = do
addToPath :: FilePath
-> Bool -- ^ if False will prepend
-> IO [(String, String)]
addToPath path append = do
cEnv <- Map.fromList <$> getEnvironment
let paths = ["PATH", "Path"]
curPaths = (\x -> maybe [] splitSearchPath (Map.lookup x cEnv)) =<< paths
{- HLINT ignore "Redundant bracket" -}
newPath = intercalate [searchPathSeparator] (if append then (curPaths ++ [path]) else (path : curPaths))
envWithoutPath = foldr (\x y -> Map.delete x y) cEnv paths
pathVar = if isWindows then "Path" else "PATH"
envWithNewPath = Map.toList $ Map.insert pathVar newPath envWithoutPath
liftIO $ setEnv pathVar newPath
return envWithNewPath
-----------
--[ Git ]--
-----------

View File

@ -285,7 +285,8 @@
"base-8.7.6",
"Latest",
"Prerelease"
]
],
"viTestDL": null
},
"7.5.5": {
"viArch": {
@ -387,7 +388,8 @@
"base-4.7.6",
"\u0001+n𫛚\r",
"Latest"
]
],
"viTestDL": null
},
"7.7.6": {
"viArch": {
@ -509,7 +511,8 @@
"old",
"base-3.1.4",
"Prerelease"
]
],
"viTestDL": null
},
"8.8.6": {
"viArch": {
@ -824,7 +827,8 @@
"base-5.2.3",
"Prerelease",
"Latest"
]
],
"viTestDL": null
}
},
"HLS": {
@ -1084,7 +1088,8 @@
"Latest",
"Latest",
"Recommended"
]
],
"viTestDL": null
},
"2.1.4": {
"viArch": {
@ -1240,7 +1245,8 @@
"viTags": [
"Prerelease",
"base-4.7.4"
]
],
"viTestDL": null
},
"3.3.7": {
"viArch": {
@ -1670,7 +1676,8 @@
},
"dlUri": "https:mkzzunx"
},
"viTags": []
"viTags": [],
"viTestDL": null
},
"3.5.3": {
"viArch": {
@ -1972,7 +1979,8 @@
"old",
"Recommended",
"old"
]
],
"viTestDL": null
},
"5.2.3": {
"viArch": {
@ -2309,7 +2317,8 @@
"Latest",
"Recommended",
"Recommended"
]
],
"viTestDL": null
},
"8.5.2": {
"viArch": {
@ -2431,7 +2440,8 @@
"Latest",
"Latest",
"base-8.7.3"
]
],
"viTestDL": null
}
}
},
@ -2880,7 +2890,8 @@
},
"dlUri": "https:zxekodom"
},
"viTags": []
"viTags": [],
"viTestDL": null
},
"3.2.1": {
"viArch": {
@ -3100,7 +3111,8 @@
"base-7.7.6",
"𩺈𥲬􅚷\u0015A~",
"old"
]
],
"viTestDL": null
},
"4.5.3": {
"viArch": {
@ -3330,7 +3342,8 @@
"base-1.5.2",
"Latest",
"old"
]
],
"viTestDL": null
},
"7.3.9": {
"viArch": {
@ -3688,7 +3701,8 @@
"base-1.6.1",
"Prerelease",
"old"
]
],
"viTestDL": null
}
},
"GHCup": {
@ -3747,7 +3761,8 @@
"Latest",
"\u0005s톕$󵰇\"g",
"Prerelease"
]
],
"viTestDL": null
},
"3.5.3": {
"viArch": {
@ -3880,7 +3895,8 @@
"Latest",
"xZ\u000b",
"Recommended"
]
],
"viTestDL": null
},
"3.8.5": {
"viArch": {
@ -3993,7 +4009,8 @@
"viSourceDL": null,
"viTags": [
"old"
]
],
"viTestDL": null
},
"4.1.6": {
"viArch": {
@ -4179,7 +4196,8 @@
"viTags": [
"Latest",
"old"
]
],
"viTestDL": null
},
"7.5.4": {
"viArch": {
@ -4456,7 +4474,8 @@
"viSourceDL": null,
"viTags": [
"鲤"
]
],
"viTestDL": null
}
},
"HLS": {
@ -4827,7 +4846,8 @@
"",
"Ctj",
"􃰍|W󶶟d`"
]
],
"viTestDL": null
},
"3.5.1": {
"viArch": {
@ -4937,7 +4957,8 @@
"old",
"Latest",
"Recommended"
]
],
"viTestDL": null
},
"4.2.2": {
"viArch": {
@ -5030,7 +5051,8 @@
"Recommended",
"Recommended",
"Latest"
]
],
"viTestDL": null
},
"4.4.1": {
"viArch": {
@ -5122,7 +5144,8 @@
"Latest",
"Latest",
"Recommended"
]
],
"viTestDL": null
},
"5.7.2": {
"viArch": {
@ -5473,7 +5496,8 @@
"Prerelease",
"Prerelease",
"Recommended"
]
],
"viTestDL": null
},
"7.1.4": {
"viArch": {
@ -5559,7 +5583,8 @@
"Latest",
"\u0013ADq\u001bX<",
"base-8.2.4"
]
],
"viTestDL": null
},
"8.2.3": {
"viArch": {
@ -5667,7 +5692,8 @@
"𠖛",
"恦AD假n#",
"Prerelease"
]
],
"viTestDL": null
},
"8.3.5": {
"viArch": {
@ -6070,7 +6096,8 @@
"Prerelease",
"%󵠣R灡𑈃pS",
"Latest"
]
],
"viTestDL": null
}
}
},
@ -7355,7 +7382,8 @@
"old",
"Latest",
"base-8.5.8"
]
],
"viTestDL": null
},
"2.1.4": {
"viArch": {
@ -8043,7 +8071,8 @@
"",
"\u0018\u0017GF󾐘\u0018",
"base-8.7.8"
]
],
"viTestDL": null
},
"4.6.8": {
"viArch": {
@ -8329,7 +8358,8 @@
"base-8.1.6",
"old",
"Latest"
]
],
"viTestDL": null
},
"5.1.8": {
"viArch": {
@ -8529,7 +8559,8 @@
"Prerelease",
"~X6*𦥹",
"base-2.1.6"
]
],
"viTestDL": null
},
"5.4.7": {
"viArch": {},
@ -8549,7 +8580,8 @@
"󱪀9pR𥎷H",
"base-7.5.6",
"Recommended"
]
],
"viTestDL": null
}
},
"Stack": {
@ -8891,7 +8923,8 @@
},
"dlUri": "http:gji"
},
"viTags": []
"viTags": [],
"viTestDL": null
},
"7.2.3": {
"viArch": {
@ -9036,7 +9069,8 @@
"old",
"Recommended",
"base-2.5.2"
]
],
"viTestDL": null
}
}
},
@ -10413,7 +10447,8 @@
"Recommended",
"S鴖xz󾤞",
"Prerelease"
]
],
"viTestDL": null
},
"4.4.4": {
"viArch": {
@ -10725,7 +10760,8 @@
"Prerelease",
"old",
"Latest"
]
],
"viTestDL": null
},
"5.5.4": {
"viArch": {
@ -11105,7 +11141,8 @@
"Latest",
"base-1.8.1",
"Recommended"
]
],
"viTestDL": null
},
"5.6.4": {
"viArch": {
@ -11348,7 +11385,8 @@
"Prerelease",
">/~l\u0019\u0001F\u0003",
"base-4.4.6"
]
],
"viTestDL": null
},
"6.7.3": {
"viArch": {},
@ -11367,7 +11405,8 @@
"viTags": [
"old",
"old"
]
],
"viTestDL": null
},
"8.5.5": {
"viArch": {},
@ -11388,7 +11427,8 @@
"Latest",
"base-3.6.3",
"Recommended"
]
],
"viTestDL": null
},
"8.6.5": {
"viArch": {
@ -11770,7 +11810,8 @@
"v斾)k",
"Prerelease",
"Latest"
]
],
"viTestDL": null
}
},
"GHC": {},
@ -13541,7 +13582,8 @@
},
"viTags": [
"Prerelease"
]
],
"viTestDL": null
},
"2.6.7": {
"viArch": {
@ -13585,7 +13627,8 @@
"viSourceDL": null,
"viTags": [
"Latest"
]
],
"viTestDL": null
},
"3.3.5": {
"viArch": {
@ -13608,7 +13651,8 @@
"&Z3𭹡X",
"Prerelease",
"Prerelease"
]
],
"viTestDL": null
},
"3.4.4": {
"viArch": {
@ -14065,7 +14109,8 @@
"f8\u0017xNft(",
"Recommended",
"Prerelease"
]
],
"viTestDL": null
},
"6.5.7": {
"viArch": {
@ -14242,7 +14287,8 @@
"dlSubdir": "􂮄qG+0󰊒t",
"dlUri": "http:vvn"
},
"viTags": []
"viTags": [],
"viTestDL": null
},
"6.6.3": {
"viArch": {
@ -14310,7 +14356,8 @@
"",
"\u0014𣉈C\u0018󼀇V",
"Recommended"
]
],
"viTestDL": null
},
"8.5.4": {
"viArch": {
@ -14463,7 +14510,8 @@
"Latest",
"\u0005I{5\u0013",
"base-3.8.8"
]
],
"viTestDL": null
}
},
"GHCup": {
@ -14635,7 +14683,8 @@
"Latest",
"old",
"Latest"
]
],
"viTestDL": null
},
"4.3.4": {
"viArch": {
@ -14831,7 +14880,8 @@
"\u0017M􆼘󴞻",
"old",
"Recommended"
]
],
"viTestDL": null
},
"8.6.2": {
"viArch": {
@ -15167,7 +15217,8 @@
"Prerelease",
"Prerelease",
"base-5.1.6"
]
],
"viTestDL": null
}
},
"Stack": {
@ -15524,7 +15575,8 @@
},
"viTags": [
"Latest"
]
],
"viTestDL": null
}
}
},

File diff suppressed because it is too large Load Diff