Add tool-requirements subcommand
This commit is contained in:
@@ -94,7 +94,7 @@ getDownloads :: ( FromJSONKey Tool
|
||||
, MonadFail m
|
||||
)
|
||||
=> URLSource
|
||||
-> Excepts '[JSONError , DownloadFailed] m GHCupDownloads
|
||||
-> Excepts '[JSONError , DownloadFailed] m GHCupInfo
|
||||
getDownloads urlSource = do
|
||||
lift $ $(logDebug) [i|Receiving download info from: #{urlSource}|]
|
||||
case urlSource of
|
||||
|
||||
@@ -92,6 +92,9 @@ data TooManyRedirs = TooManyRedirs
|
||||
data PatchFailed = PatchFailed
|
||||
deriving Show
|
||||
|
||||
-- | The tool requirements could not be found.
|
||||
data NoToolRequirements = NoToolRequirements
|
||||
deriving Show
|
||||
|
||||
|
||||
-------------------------
|
||||
|
||||
46
lib/GHCup/Requirements.hs
Normal file
46
lib/GHCup/Requirements.hs
Normal file
@@ -0,0 +1,46 @@
|
||||
{-# LANGUAGE OverloadedStrings #-}
|
||||
|
||||
module GHCup.Requirements where
|
||||
|
||||
import GHCup.Types
|
||||
import GHCup.Types.JSON ( )
|
||||
import GHCup.Types.Optics
|
||||
|
||||
import Control.Applicative
|
||||
import Data.Maybe
|
||||
import Optics
|
||||
import Prelude hiding ( abs
|
||||
, readFile
|
||||
, writeFile
|
||||
)
|
||||
|
||||
import qualified Data.Text as T
|
||||
|
||||
|
||||
-- | Get the requirements. Right now this combines GHC and cabal
|
||||
-- and doesn't do fine-grained distinction. However, the 'ToolRequirements'
|
||||
-- type allows it.
|
||||
getCommonRequirements :: PlatformResult
|
||||
-> ToolRequirements
|
||||
-> Maybe Requirements
|
||||
getCommonRequirements pr tr =
|
||||
preview (ix GHC % ix Nothing % ix (_platform pr) % ix (_distroVersion pr)) tr
|
||||
<|> preview (ix GHC % ix Nothing % ix (_platform pr) % ix Nothing) tr
|
||||
<|> preview
|
||||
( ix GHC
|
||||
% ix Nothing
|
||||
% ix (set _Linux UnknownLinux $ _platform pr)
|
||||
% ix Nothing
|
||||
)
|
||||
tr
|
||||
|
||||
|
||||
prettyRequirements :: Requirements -> T.Text
|
||||
prettyRequirements Requirements {..} =
|
||||
let d = if not . null $ _distroPKGs
|
||||
then
|
||||
"\n Install the following distro packages: "
|
||||
<> T.intercalate " " _distroPKGs
|
||||
else ""
|
||||
n = if not . T.null $ _notes then "\n Note: " <> _notes else ""
|
||||
in "System requirements " <> d <> n
|
||||
@@ -12,6 +12,39 @@ import qualified GHC.Generics as GHC
|
||||
|
||||
|
||||
|
||||
--------------------
|
||||
--[ GHCInfo Tree ]--
|
||||
--------------------
|
||||
|
||||
|
||||
data GHCupInfo = GHCupInfo
|
||||
{ _toolRequirements :: ToolRequirements
|
||||
, _ghcupDownloads :: GHCupDownloads
|
||||
}
|
||||
deriving (Show, GHC.Generic)
|
||||
|
||||
|
||||
|
||||
-------------------------
|
||||
--[ Requirements Tree ]--
|
||||
-------------------------
|
||||
|
||||
|
||||
type ToolRequirements = Map Tool ToolReqVersionSpec
|
||||
type ToolReqVersionSpec = Map (Maybe Version) PlatformReqSpec
|
||||
type PlatformReqSpec = Map Platform PlatformReqVersionSpec
|
||||
type PlatformReqVersionSpec = Map (Maybe Versioning) Requirements
|
||||
|
||||
|
||||
data Requirements = Requirements
|
||||
{ _distroPKGs :: [Text]
|
||||
, _notes :: Text
|
||||
}
|
||||
deriving (Show, GHC.Generic)
|
||||
|
||||
|
||||
|
||||
|
||||
|
||||
---------------------
|
||||
--[ Download Tree ]--
|
||||
@@ -99,7 +132,7 @@ data DownloadInfo = DownloadInfo
|
||||
-- | Where to fetch GHCupDownloads from.
|
||||
data URLSource = GHCupURL
|
||||
| OwnSource URI
|
||||
| OwnSpec GHCupDownloads
|
||||
| OwnSpec GHCupInfo
|
||||
deriving Show
|
||||
|
||||
|
||||
|
||||
@@ -39,6 +39,8 @@ deriveJSON defaultOptions { fieldLabelModifier = removeLensFieldLabel } ''VUnit
|
||||
deriveJSON defaultOptions { fieldLabelModifier = removeLensFieldLabel } ''VersionInfo
|
||||
deriveJSON defaultOptions { fieldLabelModifier = removeLensFieldLabel } ''Tag
|
||||
deriveJSON defaultOptions { fieldLabelModifier = removeLensFieldLabel } ''DownloadInfo
|
||||
deriveJSON defaultOptions { fieldLabelModifier = removeLensFieldLabel } ''GHCupInfo
|
||||
deriveJSON defaultOptions { fieldLabelModifier = removeLensFieldLabel } ''Requirements
|
||||
|
||||
|
||||
instance ToJSON URI where
|
||||
@@ -69,11 +71,11 @@ instance FromJSONKey Versioning where
|
||||
instance ToJSONKey (Maybe Versioning) where
|
||||
toJSONKey = toJSONKeyText $ \case
|
||||
Just x -> prettyV x
|
||||
Nothing -> T.pack "unknown_version"
|
||||
Nothing -> T.pack "unknown_versioning"
|
||||
|
||||
instance FromJSONKey (Maybe Versioning) where
|
||||
fromJSONKey = FromJSONKeyTextParser $ \t ->
|
||||
if t == T.pack "unknown_version" then pure Nothing else pure $ just t
|
||||
if t == T.pack "unknown_versioning" then pure Nothing else pure $ just t
|
||||
where
|
||||
just t = case versioning t of
|
||||
Right x -> pure x
|
||||
@@ -112,6 +114,19 @@ instance ToJSONKey Architecture where
|
||||
instance FromJSONKey Architecture where
|
||||
fromJSONKey = genericFromJSONKey defaultJSONKeyOptions
|
||||
|
||||
instance ToJSONKey (Maybe Version) where
|
||||
toJSONKey = toJSONKeyText $ \case
|
||||
Just x -> prettyVer x
|
||||
Nothing -> T.pack "unknown_version"
|
||||
|
||||
instance FromJSONKey (Maybe Version) where
|
||||
fromJSONKey = FromJSONKeyTextParser $ \t ->
|
||||
if t == T.pack "unknown_version" then pure Nothing else pure $ just t
|
||||
where
|
||||
just t = case version t of
|
||||
Right x -> pure x
|
||||
Left e -> fail $ "Failure in (Maybe Version) (FromJSONKey)" <> show e
|
||||
|
||||
instance ToJSON Version where
|
||||
toJSON = toJSON . prettyVer
|
||||
|
||||
|
||||
@@ -19,6 +19,7 @@ makeLenses ''DownloadInfo
|
||||
makeLenses ''Tag
|
||||
makeLenses ''VersionInfo
|
||||
|
||||
makeLenses ''GHCupInfo
|
||||
|
||||
uriSchemeL' :: Lens' (URIRef Absolute) Scheme
|
||||
uriSchemeL' = lensVL uriSchemeL
|
||||
|
||||
Reference in New Issue
Block a user