{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE RecordWildCards #-}
module HaskellCI.Config.Validity where
import HaskellCI.Prelude
import HaskellCI.Compiler
import HaskellCI.Config
import HaskellCI.Config.Ubuntu
import HaskellCI.Error
import HaskellCI.Jobs
import HaskellCI.MonadErr
checkConfigValidity :: MonadErr HsCiError m => Config -> JobVersions -> m ()
checkConfigValidity :: forall (m :: * -> *).
MonadErr HsCiError m =>
Config -> JobVersions -> m ()
checkConfigValidity Config {Bool
Natural
String
[String]
[PackageName]
[PrettyField ()]
[Installed]
[ConstraintSet]
Maybe String
Maybe Version
Maybe Jobs
VersionRange
Version
Set String
Set Fold
Map Version String
Ubuntu
PackageScope
HLintConfig
DoctestConfig
DocspecConfig
CopyFields
Components
TestedWithJobs
cfgTimeoutMinutes :: Config -> Natural
cfgGitHubActionName :: Config -> Maybe String
cfgRawTravis :: Config -> String
cfgRawProject :: Config -> [PrettyField ()]
cfgConstraintSets :: Config -> [ConstraintSet]
cfgHLint :: Config -> HLintConfig
cfgDocspec :: Config -> DocspecConfig
cfgDoctest :: Config -> DoctestConfig
cfgErrorMissingMethods :: Config -> PackageScope
cfgInsertVersion :: Config -> Bool
cfgGitHubPatches :: Config -> [String]
cfgTravisPatches :: Config -> [String]
cfgApt :: Config -> Set String
cfgGhcupVersion :: Config -> Version
cfgGhcupJobs :: Config -> VersionRange
cfgGhcupCabal :: Config -> Bool
cfgMacosJobs :: Config -> VersionRange
cfgLinuxJobs :: Config -> VersionRange
cfgLastInSeries :: Config -> Bool
cfgAllowFailures :: Config -> VersionRange
cfgEnv :: Config -> Map Version String
cfgGoogleChrome :: Config -> Bool
cfgPostgres :: Config -> Bool
cfgGhcHead :: Config -> Bool
cfgFolds :: Config -> Set Fold
cfgProjectName :: Config -> Maybe String
cfgEmailNotifications :: Config -> Bool
cfgIrcIfInOriginRepo :: Config -> Bool
cfgIrcPassword :: Config -> Maybe String
cfgIrcNickname :: Config -> Maybe String
cfgIrcChannels :: Config -> [String]
cfgOnlyBranches :: Config -> [String]
cfgCheck :: Config -> Bool
cfgTestOutputDirect :: Config -> Bool
cfgGhcjsTools :: Config -> [PackageName]
cfgGhcjsTests :: Config -> Bool
cfgHeadHackageOverride :: Config -> Bool
cfgHeadHackage :: Config -> VersionRange
cfgUnconstrainted :: Config -> VersionRange
cfgNoTestsNoBench :: Config -> VersionRange
cfgHaddockComponents :: Config -> Components
cfgHaddock :: Config -> VersionRange
cfgBenchmarks :: Config -> VersionRange
cfgRunTests :: Config -> VersionRange
cfgTests :: Config -> VersionRange
cfgInstalled :: Config -> [Installed]
cfgInstallDeps :: Config -> Bool
cfgCache :: Config -> Bool
cfgSubmodules :: Config -> Bool
cfgLocalGhcOptions :: Config -> [String]
cfgCopyFields :: Config -> CopyFields
cfgEnabledJobs :: Config -> VersionRange
cfgTestedWith :: Config -> TestedWithJobs
cfgUbuntu :: Config -> Ubuntu
cfgJobs :: Config -> Maybe Jobs
cfgCabalInstallVersion :: Config -> Maybe Version
cfgTimeoutMinutes :: Natural
cfgGitHubActionName :: Maybe String
cfgRawTravis :: String
cfgRawProject :: [PrettyField ()]
cfgConstraintSets :: [ConstraintSet]
cfgHLint :: HLintConfig
cfgDocspec :: DocspecConfig
cfgDoctest :: DoctestConfig
cfgErrorMissingMethods :: PackageScope
cfgInsertVersion :: Bool
cfgGitHubPatches :: [String]
cfgTravisPatches :: [String]
cfgApt :: Set String
cfgGhcupVersion :: Version
cfgGhcupJobs :: VersionRange
cfgGhcupCabal :: Bool
cfgMacosJobs :: VersionRange
cfgLinuxJobs :: VersionRange
cfgLastInSeries :: Bool
cfgAllowFailures :: VersionRange
cfgEnv :: Map Version String
cfgGoogleChrome :: Bool
cfgPostgres :: Bool
cfgGhcHead :: Bool
cfgFolds :: Set Fold
cfgProjectName :: Maybe String
cfgEmailNotifications :: Bool
cfgIrcIfInOriginRepo :: Bool
cfgIrcPassword :: Maybe String
cfgIrcNickname :: Maybe String
cfgIrcChannels :: [String]
cfgOnlyBranches :: [String]
cfgCheck :: Bool
cfgTestOutputDirect :: Bool
cfgGhcjsTools :: [PackageName]
cfgGhcjsTests :: Bool
cfgHeadHackageOverride :: Bool
cfgHeadHackage :: VersionRange
cfgUnconstrainted :: VersionRange
cfgNoTestsNoBench :: VersionRange
cfgHaddockComponents :: Components
cfgHaddock :: VersionRange
cfgBenchmarks :: VersionRange
cfgRunTests :: VersionRange
cfgTests :: VersionRange
cfgInstalled :: [Installed]
cfgInstallDeps :: Bool
cfgCache :: Bool
cfgSubmodules :: Bool
cfgLocalGhcOptions :: [String]
cfgCopyFields :: CopyFields
cfgEnabledJobs :: VersionRange
cfgTestedWith :: TestedWithJobs
cfgUbuntu :: Ubuntu
cfgJobs :: Maybe Jobs
cfgCabalInstallVersion :: Maybe Version
..} JobVersions {Set CompilerVersion
macosVersions :: JobVersions -> Set CompilerVersion
linuxVersions :: JobVersions -> Set CompilerVersion
allVersions :: JobVersions -> Set CompilerVersion
macosVersions :: Set CompilerVersion
linuxVersions :: Set CompilerVersion
allVersions :: Set CompilerVersion
..} = do
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
when (Bool
anyGHCJS Bool -> Bool -> Bool
&& Ubuntu
cfgUbuntu forall a. Ord a => a -> a -> Bool
> Ubuntu
Bionic) forall a b. (a -> b) -> a -> b
$
forall e (m :: * -> *) a. MonadErr e m => e -> m a
throwErr forall a b. (a -> b) -> a -> b
$ String -> HsCiError
ValidationError forall a b. (a -> b) -> a -> b
$ String
"Using GHCJS requires Ubuntu 16.04 (Xenial) or 18.04 (Bionic)."
where
anyGHCJS :: Bool
anyGHCJS = forall (t :: * -> *) a. Foldable t => (a -> Bool) -> t a -> Bool
any CompilerVersion -> Bool
isGHCJS Set CompilerVersion
linuxVersions