Lala
This commit is contained in:
@@ -1,24 +1,20 @@
|
||||
{-# LANGUAGE DataKinds #-}
|
||||
{-# LANGUAGE TypeApplications #-}
|
||||
{-# LANGUAGE OverloadedStrings #-}
|
||||
{-# LANGUAGE TemplateHaskell #-}
|
||||
{-# LANGUAGE QuasiQuotes #-}
|
||||
{-# LANGUAGE DuplicateRecordFields #-}
|
||||
|
||||
|
||||
module AvailableDownloads where
|
||||
module BinaryDownloads where
|
||||
|
||||
import qualified Data.Map as M
|
||||
import GHCup.Prelude
|
||||
import GHCup.Types
|
||||
import GHCup.Utils.Prelude
|
||||
|
||||
import Data.String.QQ
|
||||
import HPath
|
||||
import URI.ByteString.QQ
|
||||
|
||||
import qualified Data.Map as M
|
||||
|
||||
|
||||
-- TODO: version quasiquoter
|
||||
availableDownloads :: AvailableDownloads
|
||||
availableDownloads = M.fromList
|
||||
binaryDownloads :: BinaryDownloads
|
||||
binaryDownloads = M.fromList
|
||||
[ ( GHC
|
||||
, M.fromList
|
||||
[ ( [vver|8.6.5|]
|
||||
@@ -31,6 +27,7 @@ availableDownloads = M.fromList
|
||||
, DownloadInfo
|
||||
[uri|https://downloads.haskell.org/~ghc/8.6.5/ghc-8.6.5-x86_64-fedora27-linux.tar.xz|]
|
||||
(Just ([rel|ghc-8.6.5|] :: Path Rel))
|
||||
[s|5f871a3eaf808acb2420fdeef9318698|]
|
||||
)
|
||||
]
|
||||
)
|
||||
@@ -38,8 +35,9 @@ availableDownloads = M.fromList
|
||||
, M.fromList
|
||||
[ ( Nothing
|
||||
, DownloadInfo
|
||||
[uri|https://downloads.haskell.org/~ghc/8.6.5/ghc-8.6.5-x86_64-deb9-linux.tar.xz|]
|
||||
[uri|https://downloads.haskell.org/~ghc/8.6.5/ghc-8.6.5-x86_64-fedora27-linux.tar.xz|]
|
||||
(Just ([rel|ghc-8.6.5|] :: Path Rel))
|
||||
[s|5f871a3eaf808acb2420fdeef9318698|]
|
||||
)
|
||||
]
|
||||
)
|
||||
@@ -49,11 +47,13 @@ availableDownloads = M.fromList
|
||||
, DownloadInfo
|
||||
[uri|https://downloads.haskell.org/~ghc/8.6.5/ghc-8.6.5-x86_64-debian9-linux.tar.xz|]
|
||||
(Just ([rel|ghc-8.6.5|] :: Path Rel))
|
||||
[s|5f871a3eaf808acb2420fdeef9318698|]
|
||||
)
|
||||
, ( Just $ [vers|8|]
|
||||
, DownloadInfo
|
||||
[uri|https://downloads.haskell.org/~ghc/8.6.5/ghc-8.6.5-x86_64-debian8-linux.tar.xz|]
|
||||
[uri|https://downloads.haskell.org/~ghc/8.6.5/ghc-8.6.5-x86_64-debian9-linux.tar.xz|]
|
||||
(Just ([rel|ghc-8.6.5|] :: Path Rel))
|
||||
[s|5f871a3eaf808acb2420fdeef9318698|]
|
||||
)
|
||||
]
|
||||
)
|
||||
@@ -62,7 +62,7 @@ availableDownloads = M.fromList
|
||||
]
|
||||
),
|
||||
( [vver|8.4.4|]
|
||||
, VersionInfo [Latest] $ M.fromList
|
||||
, VersionInfo [] $ M.fromList
|
||||
[ ( A_64
|
||||
, M.fromList
|
||||
[ ( Linux UnknownLinux
|
||||
@@ -71,6 +71,7 @@ availableDownloads = M.fromList
|
||||
, DownloadInfo
|
||||
[uri|https://downloads.haskell.org/~ghc/8.4.4/ghc-8.4.4-x86_64-fedora27-linux.tar.xz|]
|
||||
(Just ([rel|ghc-8.4.4|] :: Path Rel))
|
||||
[s|86785f41d228168461859e40956973fb|]
|
||||
)
|
||||
]
|
||||
)
|
||||
@@ -78,8 +79,9 @@ availableDownloads = M.fromList
|
||||
, M.fromList
|
||||
[ ( Nothing
|
||||
, DownloadInfo
|
||||
[uri|https://downloads.haskell.org/~ghc/8.4.4/ghc-8.4.4-x86_64-deb9-linux.tar.xz|]
|
||||
[uri|https://downloads.haskell.org/~ghc/8.4.4/ghc-8.4.4-x86_64-fedora27-linux.tar.xz|]
|
||||
(Just ([rel|ghc-8.4.4|] :: Path Rel))
|
||||
[s|f943a245c54c2f2dcb354dceeff886e1|]
|
||||
)
|
||||
]
|
||||
)
|
||||
@@ -89,11 +91,13 @@ availableDownloads = M.fromList
|
||||
, DownloadInfo
|
||||
[uri|https://downloads.haskell.org/~ghc/8.6.5/ghc-8.6.5-x86_64-debian9-linux.tar.xz|]
|
||||
(Just ([rel|ghc-8.6.5|] :: Path Rel))
|
||||
[s|f943a245c54c2f2dcb354dceeff886e1|]
|
||||
)
|
||||
, ( Just $ [vers|8|]
|
||||
, DownloadInfo
|
||||
[uri|https://downloads.haskell.org/~ghc/8.6.5/ghc-8.6.5-x86_64-debian8-linux.tar.xz|]
|
||||
(Just ([rel|ghc-8.6.5|] :: Path Rel))
|
||||
[s|f943a245c54c2f2dcb354dceeff886e1|]
|
||||
)
|
||||
]
|
||||
)
|
||||
@@ -115,6 +119,7 @@ availableDownloads = M.fromList
|
||||
, DownloadInfo
|
||||
[uri|https://downloads.haskell.org/~cabal/cabal-install-3.0.0.0/cabal-install-3.0.0.0-x86_64-unknown-linux.tar.xz|]
|
||||
Nothing
|
||||
[s|32352d2259909970e6ff04faf61bbfac|]
|
||||
)
|
||||
]
|
||||
)
|
||||
11
app/ghcup-gen/GHCupDownloads.hs
Normal file
11
app/ghcup-gen/GHCupDownloads.hs
Normal file
@@ -0,0 +1,11 @@
|
||||
module GHCupDownloads where
|
||||
|
||||
import GHCup.Types
|
||||
import BinaryDownloads
|
||||
import SourceDownloads
|
||||
|
||||
|
||||
ghcupDownloads :: GHCupDownloads
|
||||
ghcupDownloads = GHCupDownloads { _binaryDownloads = binaryDownloads
|
||||
, _sourceDownloads = sourceDownloads
|
||||
}
|
||||
@@ -8,19 +8,21 @@
|
||||
|
||||
module Main where
|
||||
|
||||
import AvailableDownloads
|
||||
import GHCup.Types.JSON ( )
|
||||
import GHCup.Utils.Logger
|
||||
import GHCupDownloads
|
||||
|
||||
import Data.Aeson ( eitherDecode )
|
||||
import Data.Aeson.Encode.Pretty
|
||||
import qualified Data.ByteString.Lazy as L
|
||||
import Data.Semigroup ( (<>) )
|
||||
import GHCup.Types.JSON ( )
|
||||
import Options.Applicative hiding ( style )
|
||||
import GHCup.Logger
|
||||
import System.Console.Pretty
|
||||
import System.Exit
|
||||
import System.IO ( stdout )
|
||||
import Validate
|
||||
|
||||
import qualified Data.ByteString as B
|
||||
import qualified Data.ByteString.Lazy as L
|
||||
|
||||
|
||||
data Options = Options
|
||||
@@ -120,7 +122,7 @@ main = do
|
||||
GenJSON gopts -> do
|
||||
let
|
||||
bs = encodePretty' (defConfig { confIndent = Spaces 2 })
|
||||
availableDownloads
|
||||
ghcupDownloads
|
||||
case gopts of
|
||||
GenJSONOpts { output = Nothing } -> L.hPutStr stdout bs
|
||||
GenJSONOpts { output = Just StdOutput } -> L.hPutStr stdout bs
|
||||
@@ -140,4 +142,4 @@ main = do
|
||||
av <- case eitherDecode contents of
|
||||
Right r -> pure r
|
||||
Left e -> die (color Red $ show e)
|
||||
myLoggerTStdout (validate av) >>= exitWith
|
||||
myLoggerT (LoggerConfig True (B.hPut stdout)) (validate av) >>= exitWith
|
||||
|
||||
26
app/ghcup-gen/SourceDownloads.hs
Normal file
26
app/ghcup-gen/SourceDownloads.hs
Normal file
@@ -0,0 +1,26 @@
|
||||
{-# LANGUAGE QuasiQuotes #-}
|
||||
|
||||
module SourceDownloads where
|
||||
|
||||
|
||||
import GHCup.Types
|
||||
import GHCup.Utils.Prelude
|
||||
|
||||
import Data.String.QQ
|
||||
import HPath
|
||||
import URI.ByteString.QQ
|
||||
|
||||
import qualified Data.Map as M
|
||||
|
||||
|
||||
-- TODO: source tarballs
|
||||
-- TODO: reference tarballs
|
||||
sourceDownloads :: SourceDownloads
|
||||
sourceDownloads = M.fromList
|
||||
[ ( [vver|8.6.5|]
|
||||
, DownloadInfo
|
||||
[uri|https://downloads.haskell.org/~ghc/8.6.5/ghc-8.6.5-src.tar.xz|]
|
||||
(Just ([rel|ghc-8.6.5|] :: Path Rel))
|
||||
[s|b47726aaf302eb87b4970fcee924d45d|]
|
||||
)
|
||||
]
|
||||
@@ -34,20 +34,23 @@ instance Exception ValidationError
|
||||
|
||||
-- TODO: test that GHC is in semver
|
||||
validate :: (Monad m, MonadLogger m, MonadThrow m, MonadIO m)
|
||||
=> AvailableDownloads
|
||||
=> GHCupDownloads
|
||||
-> m ExitCode
|
||||
validate av = do
|
||||
validate GHCupDownloads{..} = do
|
||||
ref <- liftIO $ newIORef 0
|
||||
|
||||
-- * verify binary downloads * --
|
||||
flip runReaderT ref $ do
|
||||
-- unique tags
|
||||
forM_ (M.toList av) $ \(t, _) -> checkUniqueTags t
|
||||
forM_ (M.toList _binaryDownloads) $ \(t, _) -> checkUniqueTags t
|
||||
|
||||
-- required platforms
|
||||
forM_ (M.toList av) $ \(t, versions) ->
|
||||
forM_ (M.toList _binaryDownloads) $ \(t, versions) ->
|
||||
forM_ (M.toList versions) $ \(v, vi) ->
|
||||
forM_ (M.toList $ _viArch vi) $ \(arch, pspecs) -> do
|
||||
checkHasRequiredPlatforms t v arch (M.keys pspecs)
|
||||
|
||||
|
||||
-- exit
|
||||
e <- liftIO $ readIORef ref
|
||||
if e > 0 then pure $ ExitFailure e else pure ExitSuccess
|
||||
@@ -65,7 +68,7 @@ validate av = do
|
||||
[i|FreeBSD missing for #{t} #{v'} #{arch}|]
|
||||
|
||||
checkUniqueTags tool = do
|
||||
let allTags = join $ fmap snd $ availableToolVersions av tool
|
||||
let allTags = join $ fmap snd $ availableToolVersions _binaryDownloads tool
|
||||
let nonUnique =
|
||||
fmap fst
|
||||
. filter (\(_, b) -> not b)
|
||||
|
||||
Reference in New Issue
Block a user