{-# LANGUAGE ConstraintKinds #-}
{-# LANGUAGE DataKinds #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE TypeApplications #-}
module HaskellCI.Config where
import HaskellCI.Prelude
import qualified Data.ByteString as BS
import qualified Data.Map as M
import qualified Data.Set as S
import qualified Distribution.CabalSpecVersion as C
import qualified Distribution.Compat.CharParsing as C
import qualified Distribution.Compat.Newtype as C
import qualified Distribution.FieldGrammar as C
import qualified Distribution.Fields as C
import qualified Distribution.Parsec as C
import qualified Distribution.Pretty as C
import qualified Distribution.Types.PackageName as C
import qualified Distribution.Types.VersionRange as C
import qualified Text.PrettyPrint as PP
import HaskellCI.Cabal
import HaskellCI.Config.Components
import HaskellCI.Config.ConstraintSet
import HaskellCI.Config.CopyFields
import HaskellCI.Config.Docspec
import HaskellCI.Config.Doctest
import HaskellCI.Config.Empty
import HaskellCI.Config.Folds
import HaskellCI.Config.HLint
import HaskellCI.Config.Installed
import HaskellCI.Config.Jobs
import HaskellCI.Config.PackageScope
import HaskellCI.Config.Ubuntu
import HaskellCI.Ghcup
import HaskellCI.HeadHackage
import HaskellCI.Newtypes
import HaskellCI.OptionsGrammar
import HaskellCI.ParsecUtils
import HaskellCI.TestedWith
data Config = Config
{ Config -> Maybe Version
cfgCabalInstallVersion :: Maybe Version
, Config -> Maybe Jobs
cfgJobs :: Maybe Jobs
, Config -> Ubuntu
cfgUbuntu :: !Ubuntu
, Config -> TestedWithJobs
cfgTestedWith :: !TestedWithJobs
, Config -> VersionRange
cfgEnabledJobs :: !VersionRange
, Config -> CopyFields
cfgCopyFields :: !CopyFields
, Config -> [String]
cfgLocalGhcOptions :: [String]
, Config -> Bool
cfgSubmodules :: !Bool
, Config -> Bool
cfgCache :: !Bool
, Config -> Bool
cfgInstallDeps :: !Bool
, Config -> [Installed]
cfgInstalled :: [Installed]
, Config -> VersionRange
cfgTests :: !VersionRange
, Config -> VersionRange
cfgRunTests :: !VersionRange
, Config -> VersionRange
cfgBenchmarks :: !VersionRange
, Config -> VersionRange
cfgHaddock :: !VersionRange
, Config -> Components
cfgHaddockComponents :: !Components
, Config -> VersionRange
cfgNoTestsNoBench :: !VersionRange
, Config -> VersionRange
cfgUnconstrainted :: !VersionRange
, Config -> VersionRange
cfgHeadHackage :: !VersionRange
, Config -> Bool
cfgHeadHackageOverride :: !Bool
, Config -> Bool
cfgGhcjsTests :: !Bool
, Config -> [PackageName]
cfgGhcjsTools :: ![C.PackageName]
, Config -> Bool
cfgTestOutputDirect :: !Bool
, Config -> Bool
cfgCheck :: !Bool
, Config -> [String]
cfgOnlyBranches :: [String]
, Config -> [String]
cfgIrcChannels :: [String]
, Config -> Maybe String
cfgIrcNickname :: Maybe String
, Config -> Maybe String
cfgIrcPassword :: Maybe String
, Config -> Bool
cfgIrcIfInOriginRepo :: Bool
, Config -> Bool
cfgEmailNotifications :: Bool
, Config -> Maybe String
cfgProjectName :: Maybe String
, Config -> Set Fold
cfgFolds :: S.Set Fold
, Config -> Bool
cfgGhcHead :: !Bool
, Config -> Bool
cfgPostgres :: !Bool
, Config -> Bool
cfgGoogleChrome :: !Bool
, Config -> Map Version String
cfgEnv :: M.Map Version String
, Config -> VersionRange
cfgAllowFailures :: !VersionRange
, Config -> Bool
cfgLastInSeries :: !Bool
, Config -> VersionRange
cfgLinuxJobs :: !VersionRange
, Config -> VersionRange
cfgMacosJobs :: !VersionRange
, Config -> Bool
cfgGhcupCabal :: !Bool
, Config -> VersionRange
cfgGhcupJobs :: !VersionRange
, Config -> Version
cfgGhcupVersion :: !Version
, Config -> Set String
cfgApt :: S.Set String
, Config -> [String]
cfgTravisPatches :: [FilePath]
, Config -> [String]
cfgGitHubPatches :: [FilePath]
, Config -> Bool
cfgInsertVersion :: !Bool
, Config -> PackageScope
cfgErrorMissingMethods :: !PackageScope
, Config -> DoctestConfig
cfgDoctest :: !DoctestConfig
, Config -> DocspecConfig
cfgDocspec :: !DocspecConfig
, Config -> HLintConfig
cfgHLint :: !HLintConfig
, Config -> [ConstraintSet]
cfgConstraintSets :: [ConstraintSet]
, Config -> [PrettyField ()]
cfgRawProject :: [C.PrettyField ()]
, Config -> String
cfgRawTravis :: !String
, Config -> Maybe String
cfgGitHubActionName :: !(Maybe String)
, Config -> Natural
cfgTimeoutMinutes :: !Natural
}
deriving (forall x. Rep Config x -> Config
forall x. Config -> Rep Config x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep Config x -> Config
$cfrom :: forall x. Config -> Rep Config x
Generic)
emptyConfig :: Config
emptyConfig :: Config
emptyConfig = case forall s a. EmptyGrammar s a -> Either (NonEmpty ByteString) a
runEG forall (c :: * -> Constraint) (g :: * -> * -> *).
(OptionsGrammar c g, Applicative (g Config), c (Identity HLintJob),
c (Identity PackageScope), c (Identity TestedWithJobs),
c (Identity Ubuntu), c (Identity Jobs), c (Identity CopyFields),
c (Identity Version), c (Identity Natural),
c (Identity Components), c Env, c Folds, c CopyFields,
c HeadVersion, c (List FSep (Identity Installed) Installed),
Applicative (g DoctestConfig), Applicative (g DocspecConfig),
Applicative (g HLintConfig)) =>
g Config Config
configGrammar of
Left NonEmpty ByteString
xs -> forall a. HasCallStack => String -> a
error forall a b. (a -> b) -> a -> b
$ String
"Required fields: " forall a. [a] -> [a] -> [a]
++ forall a. Show a => a -> String
show NonEmpty ByteString
xs
Right Config
x -> Config
x
configGrammar
:: ( OptionsGrammar c g, Applicative (g Config)
, c (Identity HLintJob)
, c (Identity PackageScope)
, c (Identity TestedWithJobs)
, c (Identity Ubuntu)
, c (Identity Jobs)
, c (Identity CopyFields)
, c (Identity Version)
, c (Identity Natural)
, c (Identity Components)
, c Env, c Folds, c CopyFields, c HeadVersion
, c (C.List C.FSep (Identity Installed) Installed)
, Applicative (g DoctestConfig)
, Applicative (g DocspecConfig)
, Applicative (g HLintConfig))
=> g Config Config
configGrammar :: forall (c :: * -> Constraint) (g :: * -> * -> *).
(OptionsGrammar c g, Applicative (g Config), c (Identity HLintJob),
c (Identity PackageScope), c (Identity TestedWithJobs),
c (Identity Ubuntu), c (Identity Jobs), c (Identity CopyFields),
c (Identity Version), c (Identity Natural),
c (Identity Components), c Env, c Folds, c CopyFields,
c HeadVersion, c (List FSep (Identity Installed) Installed),
Applicative (g DoctestConfig), Applicative (g DocspecConfig),
Applicative (g HLintConfig)) =>
g Config Config
configGrammar = Maybe Version
-> Maybe Jobs
-> Ubuntu
-> TestedWithJobs
-> VersionRange
-> CopyFields
-> [String]
-> Bool
-> Bool
-> Bool
-> [Installed]
-> VersionRange
-> VersionRange
-> VersionRange
-> VersionRange
-> Components
-> VersionRange
-> VersionRange
-> VersionRange
-> Bool
-> Bool
-> [PackageName]
-> Bool
-> Bool
-> [String]
-> [String]
-> Maybe String
-> Maybe String
-> Bool
-> Bool
-> Maybe String
-> Set Fold
-> Bool
-> Bool
-> Bool
-> Map Version String
-> VersionRange
-> Bool
-> VersionRange
-> VersionRange
-> Bool
-> VersionRange
-> Version
-> Set String
-> [String]
-> [String]
-> Bool
-> PackageScope
-> DoctestConfig
-> DocspecConfig
-> HLintConfig
-> [ConstraintSet]
-> [PrettyField ()]
-> String
-> Maybe String
-> Natural
-> Config
Config
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall (c :: * -> Constraint) (g :: * -> * -> *) b a s.
(FieldGrammar c g, c b, Newtype a b, Eq a) =>
ByteString -> (a -> b) -> ALens' s a -> a -> g s a
C.optionalFieldDefAla ByteString
"cabal-install-version" Maybe Version -> HeadVersion
HeadVersion (forall (name :: Symbol) r a (f :: * -> *).
(HasField name r a, Functor f) =>
(a -> f a) -> r -> f r
field @"cfgCabalInstallVersion") Maybe Version
defaultCabalInstallVersion
forall a b. a -> (a -> b) -> b
^^^ forall (c :: * -> Constraint) (p :: * -> * -> *) s a.
OptionsGrammar c p =>
String -> String -> p s a -> p s a
metahelp String
"VERSION" String
"cabal-install version for all jobs"
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> forall (c :: * -> Constraint) (g :: * -> * -> *) a s.
(FieldGrammar c g, c (Identity a)) =>
ByteString -> ALens' s (Maybe a) -> g s (Maybe a)
C.optionalField ByteString
"jobs" (forall (name :: Symbol) r a (f :: * -> *).
(HasField name r a, Functor f) =>
(a -> f a) -> r -> f r
field @"cfgJobs")
forall a b. a -> (a -> b) -> b
^^^ forall (c :: * -> Constraint) (p :: * -> * -> *) s a.
OptionsGrammar c p =>
String -> String -> p s a -> p s a
metahelp String
"JOBS" String
"jobs (N:M - cabal:ghc)"
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> forall (c :: * -> Constraint) (g :: * -> * -> *) s a.
(FieldGrammar c g, Functor (g s), c (Identity a), Eq a) =>
ByteString -> ALens' s a -> a -> g s a
C.optionalFieldDef ByteString
"distribution" (forall (name :: Symbol) r a (f :: * -> *).
(HasField name r a, Functor f) =>
(a -> f a) -> r -> f r
field @"cfgUbuntu") Ubuntu
Bionic
forall a b. a -> (a -> b) -> b
^^^ forall (c :: * -> Constraint) (p :: * -> * -> *) s a.
OptionsGrammar c p =>
String -> String -> p s a -> p s a
metahelp String
"DIST" (forall (t :: * -> *) a. Foldable t => t [a] -> [a]
concat
[ String
"distribution version ("
, forall a. [a] -> [[a]] -> [a]
intercalate String
", " forall a b. (a -> b) -> a -> b
$ forall a b. (a -> b) -> [a] -> [b]
map Ubuntu -> String
showUbuntu [forall a. Bounded a => a
minBound..forall a. Bounded a => a
maxBound]
, String
")"
])
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> forall (c :: * -> Constraint) (g :: * -> * -> *) s a.
(FieldGrammar c g, Functor (g s), c (Identity a), Eq a) =>
ByteString -> ALens' s a -> a -> g s a
C.optionalFieldDef ByteString
"jobs-selection" (forall (name :: Symbol) r a (f :: * -> *).
(HasField name r a, Functor f) =>
(a -> f a) -> r -> f r
field @"cfgTestedWith") TestedWithJobs
TestedWithUniform
forall a b. a -> (a -> b) -> b
^^^ forall (c :: * -> Constraint) (p :: * -> * -> *) s a.
OptionsGrammar c p =>
String -> String -> p s a -> p s a
metahelp String
"uniform|any" String
"Jobs selection across packages"
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> forall (c :: * -> Constraint) (p :: * -> * -> *) s.
OptionsGrammar c p =>
ByteString
-> ALens' s VersionRange -> VersionRange -> p s VersionRange
rangeField ByteString
"enabled" (forall (name :: Symbol) r a (f :: * -> *).
(HasField name r a, Functor f) =>
(a -> f a) -> r -> f r
field @"cfgEnabledJobs") VersionRange
anyVersion
forall a b. a -> (a -> b) -> b
^^^ forall (c :: * -> Constraint) (p :: * -> * -> *) s a.
OptionsGrammar c p =>
String -> String -> p s a -> p s a
metahelp String
"RANGE" String
"Restrict jobs selection futher from per package tested-with"
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> forall (c :: * -> Constraint) (g :: * -> * -> *) s a.
(FieldGrammar c g, Functor (g s), c (Identity a), Eq a) =>
ByteString -> ALens' s a -> a -> g s a
C.optionalFieldDef ByteString
"copy-fields" (forall (name :: Symbol) r a (f :: * -> *).
(HasField name r a, Functor f) =>
(a -> f a) -> r -> f r
field @"cfgCopyFields") CopyFields
CopyFieldsSome
forall a b. a -> (a -> b) -> b
^^^ forall (c :: * -> Constraint) (p :: * -> * -> *) s a.
OptionsGrammar c p =>
String -> String -> p s a -> p s a
metahelp String
"none|some|all" String
"Copy ? fields from cabal.project fields"
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> forall (c :: * -> Constraint) (g :: * -> * -> *) b a s.
(FieldGrammar c g, c b, Monoid a, Newtype a b) =>
ByteString -> (a -> b) -> ALens' s a -> g s a
C.monoidalFieldAla ByteString
"local-ghc-options" (forall sep a b. sep -> (a -> b) -> [a] -> List sep b a
C.alaList' NoCommaFSep
C.NoCommaFSep String -> Token'
C.Token') (forall (name :: Symbol) r a (f :: * -> *).
(HasField name r a, Functor f) =>
(a -> f a) -> r -> f r
field @"cfgLocalGhcOptions")
forall a b. a -> (a -> b) -> b
^^^ forall (c :: * -> Constraint) (p :: * -> * -> *) s a.
OptionsGrammar c p =>
String -> String -> p s a -> p s a
metahelp String
"OPTS" String
"--ghc-options for local packages"
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> forall (c :: * -> Constraint) (g :: * -> * -> *) s.
FieldGrammar c g =>
ByteString -> ALens' s Bool -> Bool -> g s Bool
C.booleanFieldDef ByteString
"submodules" (forall (name :: Symbol) r a (f :: * -> *).
(HasField name r a, Functor f) =>
(a -> f a) -> r -> f r
field @"cfgSubmodules") Bool
False
forall a b. a -> (a -> b) -> b
^^^ forall (c :: * -> Constraint) (p :: * -> * -> *) s a.
OptionsGrammar c p =>
String -> p s a -> p s a
help String
"Clone submodules, i.e. recursively"
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> forall (c :: * -> Constraint) (g :: * -> * -> *) s.
FieldGrammar c g =>
ByteString -> ALens' s Bool -> Bool -> g s Bool
C.booleanFieldDef ByteString
"cache" (forall (name :: Symbol) r a (f :: * -> *).
(HasField name r a, Functor f) =>
(a -> f a) -> r -> f r
field @"cfgCache") Bool
True
forall a b. a -> (a -> b) -> b
^^^ forall (c :: * -> Constraint) (p :: * -> * -> *) s a.
OptionsGrammar c p =>
String -> p s a -> p s a
help String
"Disable caching"
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> forall (c :: * -> Constraint) (g :: * -> * -> *) s.
FieldGrammar c g =>
ByteString -> ALens' s Bool -> Bool -> g s Bool
C.booleanFieldDef ByteString
"install-dependencies" (forall (name :: Symbol) r a (f :: * -> *).
(HasField name r a, Functor f) =>
(a -> f a) -> r -> f r
field @"cfgInstallDeps") Bool
True
forall a b. a -> (a -> b) -> b
^^^ forall (c :: * -> Constraint) (p :: * -> * -> *) s a.
OptionsGrammar c p =>
String -> p s a -> p s a
help String
"Skip separate dependency installation step"
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> forall (c :: * -> Constraint) (g :: * -> * -> *) b a s.
(FieldGrammar c g, c b, Monoid a, Newtype a b) =>
ByteString -> (a -> b) -> ALens' s a -> g s a
C.monoidalFieldAla ByteString
"installed" (forall sep a. sep -> [a] -> List sep (Identity a) a
C.alaList FSep
C.FSep) (forall (name :: Symbol) r a (f :: * -> *).
(HasField name r a, Functor f) =>
(a -> f a) -> r -> f r
field @"cfgInstalled")
forall a b. a -> (a -> b) -> b
^^^ forall (c :: * -> Constraint) (p :: * -> * -> *) s a.
OptionsGrammar c p =>
String -> String -> p s a -> p s a
metahelp String
"+/-PKG" String
"Specify 'constraint: ... installed' packages"
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> forall (c :: * -> Constraint) (p :: * -> * -> *) s.
OptionsGrammar c p =>
ByteString
-> ALens' s VersionRange -> VersionRange -> p s VersionRange
rangeField ByteString
"tests" (forall (name :: Symbol) r a (f :: * -> *).
(HasField name r a, Functor f) =>
(a -> f a) -> r -> f r
field @"cfgTests") VersionRange
anyVersion
forall a b. a -> (a -> b) -> b
^^^ forall (c :: * -> Constraint) (p :: * -> * -> *) s a.
OptionsGrammar c p =>
String -> String -> p s a -> p s a
metahelp String
"RANGE" String
"Build tests with"
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> forall (c :: * -> Constraint) (p :: * -> * -> *) s.
OptionsGrammar c p =>
ByteString
-> ALens' s VersionRange -> VersionRange -> p s VersionRange
rangeField ByteString
"run-tests" (forall (name :: Symbol) r a (f :: * -> *).
(HasField name r a, Functor f) =>
(a -> f a) -> r -> f r
field @"cfgRunTests") VersionRange
anyVersion
forall a b. a -> (a -> b) -> b
^^^ forall (c :: * -> Constraint) (p :: * -> * -> *) s a.
OptionsGrammar c p =>
String -> String -> p s a -> p s a
metahelp String
"RANGE" String
"Run tests with (note: only built tests are run)"
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> forall (c :: * -> Constraint) (p :: * -> * -> *) s.
OptionsGrammar c p =>
ByteString
-> ALens' s VersionRange -> VersionRange -> p s VersionRange
rangeField ByteString
"benchmarks" (forall (name :: Symbol) r a (f :: * -> *).
(HasField name r a, Functor f) =>
(a -> f a) -> r -> f r
field @"cfgBenchmarks") VersionRange
anyVersion
forall a b. a -> (a -> b) -> b
^^^ forall (c :: * -> Constraint) (p :: * -> * -> *) s a.
OptionsGrammar c p =>
String -> String -> p s a -> p s a
metahelp String
"RANGE" String
"Build benchmarks"
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> forall (c :: * -> Constraint) (p :: * -> * -> *) s.
OptionsGrammar c p =>
ByteString
-> ALens' s VersionRange -> VersionRange -> p s VersionRange
rangeField ByteString
"haddock" (forall (name :: Symbol) r a (f :: * -> *).
(HasField name r a, Functor f) =>
(a -> f a) -> r -> f r
field @"cfgHaddock") VersionRange
anyVersion
forall a b. a -> (a -> b) -> b
^^^ forall (c :: * -> Constraint) (p :: * -> * -> *) s a.
OptionsGrammar c p =>
String -> String -> p s a -> p s a
metahelp String
"RANGE" String
"Haddock step"
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> forall (c :: * -> Constraint) (g :: * -> * -> *) s a.
(FieldGrammar c g, Functor (g s), c (Identity a), Eq a) =>
ByteString -> ALens' s a -> a -> g s a
C.optionalFieldDef ByteString
"haddock-components" (forall (name :: Symbol) r a (f :: * -> *).
(HasField name r a, Functor f) =>
(a -> f a) -> r -> f r
field @"cfgHaddockComponents") Components
ComponentsAll
forall a b. a -> (a -> b) -> b
^^^ forall (c :: * -> Constraint) (p :: * -> * -> *) s a.
OptionsGrammar c p =>
String -> String -> p s a -> p s a
metahelp String
"all|libs" String
"Haddock components"
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> forall (c :: * -> Constraint) (p :: * -> * -> *) s.
OptionsGrammar c p =>
ByteString
-> ALens' s VersionRange -> VersionRange -> p s VersionRange
rangeField ByteString
"no-tests-no-benchmarks" (forall (name :: Symbol) r a (f :: * -> *).
(HasField name r a, Functor f) =>
(a -> f a) -> r -> f r
field @"cfgNoTestsNoBench") VersionRange
anyVersion
forall a b. a -> (a -> b) -> b
^^^ forall (c :: * -> Constraint) (p :: * -> * -> *) s a.
OptionsGrammar c p =>
String -> String -> p s a -> p s a
metahelp String
"RANGE" String
"Build without tests and benchmarks"
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> forall (c :: * -> Constraint) (p :: * -> * -> *) s.
OptionsGrammar c p =>
ByteString
-> ALens' s VersionRange -> VersionRange -> p s VersionRange
rangeField ByteString
"unconstrained" (forall (name :: Symbol) r a (f :: * -> *).
(HasField name r a, Functor f) =>
(a -> f a) -> r -> f r
field @"cfgUnconstrainted") VersionRange
anyVersion
forall a b. a -> (a -> b) -> b
^^^ forall (c :: * -> Constraint) (p :: * -> * -> *) s a.
OptionsGrammar c p =>
String -> String -> p s a -> p s a
metahelp String
"RANGE" String
"Make unconstrained build"
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> forall (c :: * -> Constraint) (p :: * -> * -> *) s.
OptionsGrammar c p =>
ByteString
-> ALens' s VersionRange -> VersionRange -> p s VersionRange
rangeField ByteString
"head-hackage" (forall (name :: Symbol) r a (f :: * -> *).
(HasField name r a, Functor f) =>
(a -> f a) -> r -> f r
field @"cfgHeadHackage") VersionRange
defaultHeadHackage
forall a b. a -> (a -> b) -> b
^^^ forall (c :: * -> Constraint) (p :: * -> * -> *) s a.
OptionsGrammar c p =>
String -> String -> p s a -> p s a
metahelp String
"RANGE" String
"Use head.hackage repository. Also marks as allow-failures"
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> forall (c :: * -> Constraint) (g :: * -> * -> *) s.
FieldGrammar c g =>
ByteString -> ALens' s Bool -> Bool -> g s Bool
C.booleanFieldDef ByteString
"head-hackage-override" (forall (name :: Symbol) r a (f :: * -> *).
(HasField name r a, Functor f) =>
(a -> f a) -> r -> f r
field @"cfgHeadHackageOverride") Bool
True
forall a b. a -> (a -> b) -> b
^^^ forall (c :: * -> Constraint) (p :: * -> * -> *) s a.
OptionsGrammar c p =>
String -> p s a -> p s a
help String
"Use :override for head.hackage repository"
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> forall (c :: * -> Constraint) (g :: * -> * -> *) s.
FieldGrammar c g =>
ByteString -> ALens' s Bool -> Bool -> g s Bool
C.booleanFieldDef ByteString
"ghcjs-tests" (forall (name :: Symbol) r a (f :: * -> *).
(HasField name r a, Functor f) =>
(a -> f a) -> r -> f r
field @"cfgGhcjsTests") Bool
False
forall a b. a -> (a -> b) -> b
^^^ forall (c :: * -> Constraint) (p :: * -> * -> *) s a.
OptionsGrammar c p =>
String -> p s a -> p s a
help String
"Run tests with GHCJS (experimental, relies on cabal-plan finding test-suites)"
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> forall (c :: * -> Constraint) (g :: * -> * -> *) b a s.
(FieldGrammar c g, c b, Monoid a, Newtype a b) =>
ByteString -> (a -> b) -> ALens' s a -> g s a
C.monoidalFieldAla ByteString
"ghcjs-tools" (forall sep a. sep -> [a] -> List sep (Identity a) a
C.alaList FSep
C.FSep) (forall (name :: Symbol) r a (f :: * -> *).
(HasField name r a, Functor f) =>
(a -> f a) -> r -> f r
field @"cfgGhcjsTools")
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> forall (c :: * -> Constraint) (g :: * -> * -> *) s.
FieldGrammar c g =>
ByteString -> ALens' s Bool -> Bool -> g s Bool
C.booleanFieldDef ByteString
"test-output-direct" (forall (name :: Symbol) r a (f :: * -> *).
(HasField name r a, Functor f) =>
(a -> f a) -> r -> f r
field @"cfgTestOutputDirect") Bool
True
forall a b. a -> (a -> b) -> b
^^^ forall (c :: * -> Constraint) (p :: * -> * -> *) s a.
OptionsGrammar c p =>
String -> p s a -> p s a
help String
"Use --test-show-details=direct, may cause problems with build-type: Custom"
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> forall (c :: * -> Constraint) (g :: * -> * -> *) s.
FieldGrammar c g =>
ByteString -> ALens' s Bool -> Bool -> g s Bool
C.booleanFieldDef ByteString
"cabal-check" (forall (name :: Symbol) r a (f :: * -> *).
(HasField name r a, Functor f) =>
(a -> f a) -> r -> f r
field @"cfgCheck") Bool
True
forall a b. a -> (a -> b) -> b
^^^ forall (c :: * -> Constraint) (p :: * -> * -> *) s a.
OptionsGrammar c p =>
String -> p s a -> p s a
help String
"Disable cabal check run"
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> forall (c :: * -> Constraint) (g :: * -> * -> *) b a s.
(FieldGrammar c g, c b, Monoid a, Newtype a b) =>
ByteString -> (a -> b) -> ALens' s a -> g s a
C.monoidalFieldAla ByteString
"branches" (forall sep a b. sep -> (a -> b) -> [a] -> List sep b a
C.alaList' FSep
C.FSep String -> Token'
C.Token') (forall (name :: Symbol) r a (f :: * -> *).
(HasField name r a, Functor f) =>
(a -> f a) -> r -> f r
field @"cfgOnlyBranches")
forall a b. a -> (a -> b) -> b
^^^ forall (c :: * -> Constraint) (p :: * -> * -> *) s a.
OptionsGrammar c p =>
String -> String -> p s a -> p s a
metahelp String
"BRANCH" String
"Enable builds only for specific branches"
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> forall (c :: * -> Constraint) (g :: * -> * -> *) b a s.
(FieldGrammar c g, c b, Monoid a, Newtype a b) =>
ByteString -> (a -> b) -> ALens' s a -> g s a
C.monoidalFieldAla ByteString
"irc-channels" (forall sep a b. sep -> (a -> b) -> [a] -> List sep b a
C.alaList' FSep
C.FSep String -> Token'
C.Token') (forall (name :: Symbol) r a (f :: * -> *).
(HasField name r a, Functor f) =>
(a -> f a) -> r -> f r
field @"cfgIrcChannels")
forall a b. a -> (a -> b) -> b
^^^ forall (c :: * -> Constraint) (p :: * -> * -> *) s a.
OptionsGrammar c p =>
String -> String -> p s a -> p s a
metahelp String
"IRC" String
"Enable IRC notifications to given channel (e.g. 'irc.libera.chat#haskell-lens')"
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> forall (c :: * -> Constraint) (g :: * -> * -> *) s.
FieldGrammar c g =>
ByteString -> ALens' s (Maybe String) -> g s (Maybe String)
C.freeTextField ByteString
"irc-nickname" (forall (name :: Symbol) r a (f :: * -> *).
(HasField name r a, Functor f) =>
(a -> f a) -> r -> f r
field @"cfgIrcNickname")
forall a b. a -> (a -> b) -> b
^^^ forall (c :: * -> Constraint) (p :: * -> * -> *) s a.
OptionsGrammar c p =>
String -> String -> p s a -> p s a
metahelp String
"NICKNAME" String
"Nickname with which to authenticate to an IRC server. Only used if `irc-channels` are set."
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> forall (c :: * -> Constraint) (g :: * -> * -> *) s.
FieldGrammar c g =>
ByteString -> ALens' s (Maybe String) -> g s (Maybe String)
C.freeTextField ByteString
"irc-password" (forall (name :: Symbol) r a (f :: * -> *).
(HasField name r a, Functor f) =>
(a -> f a) -> r -> f r
field @"cfgIrcPassword")
forall a b. a -> (a -> b) -> b
^^^ forall (c :: * -> Constraint) (p :: * -> * -> *) s a.
OptionsGrammar c p =>
String -> String -> p s a -> p s a
metahelp String
"PASSWORD" String
"Password with which to authenticate to an IRC server. Only used if `irc-channels` are set."
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> forall (c :: * -> Constraint) (g :: * -> * -> *) s.
FieldGrammar c g =>
ByteString -> ALens' s Bool -> Bool -> g s Bool
C.booleanFieldDef ByteString
"irc-if-in-origin-repo" (forall (name :: Symbol) r a (f :: * -> *).
(HasField name r a, Functor f) =>
(a -> f a) -> r -> f r
field @"cfgIrcIfInOriginRepo") Bool
False
forall a b. a -> (a -> b) -> b
^^^ forall (c :: * -> Constraint) (p :: * -> * -> *) s a.
OptionsGrammar c p =>
String -> p s a -> p s a
help String
"Only send IRC notifications if run from the original remote (GitHub Actions only)"
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> forall (c :: * -> Constraint) (g :: * -> * -> *) s.
FieldGrammar c g =>
ByteString -> ALens' s Bool -> Bool -> g s Bool
C.booleanFieldDef ByteString
"email-notifications" (forall (name :: Symbol) r a (f :: * -> *).
(HasField name r a, Functor f) =>
(a -> f a) -> r -> f r
field @"cfgEmailNotifications") Bool
True
forall a b. a -> (a -> b) -> b
^^^ forall (c :: * -> Constraint) (p :: * -> * -> *) s a.
OptionsGrammar c p =>
String -> p s a -> p s a
help String
"Disable email notifications"
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> forall (c :: * -> Constraint) (g :: * -> * -> *) b a s.
(FieldGrammar c g, c b, Newtype a b) =>
ByteString -> (a -> b) -> ALens' s (Maybe a) -> g s (Maybe a)
C.optionalFieldAla ByteString
"project-name" String -> Token'
C.Token' (forall (name :: Symbol) r a (f :: * -> *).
(HasField name r a, Functor f) =>
(a -> f a) -> r -> f r
field @"cfgProjectName")
forall a b. a -> (a -> b) -> b
^^^ forall (c :: * -> Constraint) (p :: * -> * -> *) s a.
OptionsGrammar c p =>
String -> String -> p s a -> p s a
metahelp String
"NAME" String
"Project name (used for IRC notifications), defaults to package name or name of first package listed in cabal.project file"
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> forall (c :: * -> Constraint) (g :: * -> * -> *) b a s.
(FieldGrammar c g, c b, Monoid a, Newtype a b) =>
ByteString -> (a -> b) -> ALens' s a -> g s a
C.monoidalFieldAla ByteString
"folds" Set Fold -> Folds
Folds (forall (name :: Symbol) r a (f :: * -> *).
(HasField name r a, Functor f) =>
(a -> f a) -> r -> f r
field @"cfgFolds")
forall a b. a -> (a -> b) -> b
^^^ forall (c :: * -> Constraint) (p :: * -> * -> *) s a.
OptionsGrammar c p =>
String -> String -> p s a -> p s a
metahelp String
"FOLD" String
"Build steps to fold"
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> forall (c :: * -> Constraint) (g :: * -> * -> *) s.
FieldGrammar c g =>
ByteString -> ALens' s Bool -> Bool -> g s Bool
C.booleanFieldDef ByteString
"ghc-head" (forall (name :: Symbol) r a (f :: * -> *).
(HasField name r a, Functor f) =>
(a -> f a) -> r -> f r
field @"cfgGhcHead") Bool
False
forall a b. a -> (a -> b) -> b
^^^ forall (c :: * -> Constraint) (p :: * -> * -> *) s a.
OptionsGrammar c p =>
String -> p s a -> p s a
help String
"Add ghc-head job"
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> forall (c :: * -> Constraint) (g :: * -> * -> *) s.
FieldGrammar c g =>
ByteString -> ALens' s Bool -> Bool -> g s Bool
C.booleanFieldDef ByteString
"postgresql" (forall (name :: Symbol) r a (f :: * -> *).
(HasField name r a, Functor f) =>
(a -> f a) -> r -> f r
field @"cfgPostgres") Bool
False
forall a b. a -> (a -> b) -> b
^^^ forall (c :: * -> Constraint) (p :: * -> * -> *) s a.
OptionsGrammar c p =>
String -> p s a -> p s a
help String
"Add postgresql service"
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> forall (c :: * -> Constraint) (g :: * -> * -> *) s.
FieldGrammar c g =>
ByteString -> ALens' s Bool -> Bool -> g s Bool
C.booleanFieldDef ByteString
"google-chrome" (forall (name :: Symbol) r a (f :: * -> *).
(HasField name r a, Functor f) =>
(a -> f a) -> r -> f r
field @"cfgGoogleChrome") Bool
False
forall a b. a -> (a -> b) -> b
^^^ forall (c :: * -> Constraint) (p :: * -> * -> *) s a.
OptionsGrammar c p =>
String -> p s a -> p s a
help String
"Add google-chrome service"
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> forall (c :: * -> Constraint) (g :: * -> * -> *) b a s.
(FieldGrammar c g, c b, Monoid a, Newtype a b) =>
ByteString -> (a -> b) -> ALens' s a -> g s a
C.monoidalFieldAla ByteString
"env" Map Version String -> Env
Env (forall (name :: Symbol) r a (f :: * -> *).
(HasField name r a, Functor f) =>
(a -> f a) -> r -> f r
field @"cfgEnv")
forall a b. a -> (a -> b) -> b
^^^ forall (c :: * -> Constraint) (p :: * -> * -> *) s a.
OptionsGrammar c p =>
String -> String -> p s a -> p s a
metahelp String
"ENV" String
"Environment variables per job (e.g. `8.0.2:HADDOCK=false`)"
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> forall (c :: * -> Constraint) (g :: * -> * -> *) b a s.
(FieldGrammar c g, c b, Newtype a b, Eq a) =>
ByteString -> (a -> b) -> ALens' s a -> a -> g s a
C.optionalFieldDefAla ByteString
"allow-failures" VersionRange -> Range
Range (forall (name :: Symbol) r a (f :: * -> *).
(HasField name r a, Functor f) =>
(a -> f a) -> r -> f r
field @"cfgAllowFailures") VersionRange
noVersion
forall a b. a -> (a -> b) -> b
^^^ forall (c :: * -> Constraint) (p :: * -> * -> *) s a.
OptionsGrammar c p =>
String -> String -> p s a -> p s a
metahelp String
"JOB" String
"Allow failures of particular GHC version"
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> forall (c :: * -> Constraint) (g :: * -> * -> *) s.
FieldGrammar c g =>
ByteString -> ALens' s Bool -> Bool -> g s Bool
C.booleanFieldDef ByteString
"last-in-series" (forall (name :: Symbol) r a (f :: * -> *).
(HasField name r a, Functor f) =>
(a -> f a) -> r -> f r
field @"cfgLastInSeries") Bool
False
forall a b. a -> (a -> b) -> b
^^^ forall (c :: * -> Constraint) (p :: * -> * -> *) s a.
OptionsGrammar c p =>
String -> p s a -> p s a
help String
"[Discouraged] Assume there are only GHCs last in major series: 8.2.* will match only 8.2.2"
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> forall (c :: * -> Constraint) (p :: * -> * -> *) s.
OptionsGrammar c p =>
ByteString
-> ALens' s VersionRange -> VersionRange -> p s VersionRange
rangeField ByteString
"linux-jobs" (forall (name :: Symbol) r a (f :: * -> *).
(HasField name r a, Functor f) =>
(a -> f a) -> r -> f r
field @"cfgLinuxJobs") VersionRange
anyVersion
forall a b. a -> (a -> b) -> b
^^^ forall (c :: * -> Constraint) (p :: * -> * -> *) s a.
OptionsGrammar c p =>
String -> String -> p s a -> p s a
metahelp String
"RANGE" String
"Jobs to build on Linux"
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> forall (c :: * -> Constraint) (p :: * -> * -> *) s.
OptionsGrammar c p =>
ByteString
-> ALens' s VersionRange -> VersionRange -> p s VersionRange
rangeField ByteString
"macos-jobs" (forall (name :: Symbol) r a (f :: * -> *).
(HasField name r a, Functor f) =>
(a -> f a) -> r -> f r
field @"cfgMacosJobs") VersionRange
noVersion
forall a b. a -> (a -> b) -> b
^^^ forall (c :: * -> Constraint) (p :: * -> * -> *) s a.
OptionsGrammar c p =>
String -> String -> p s a -> p s a
metahelp String
"RANGE" String
"Jobs to additionally build with OSX"
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> forall (c :: * -> Constraint) (g :: * -> * -> *) s.
FieldGrammar c g =>
ByteString -> ALens' s Bool -> Bool -> g s Bool
C.booleanFieldDef ByteString
"ghcup-cabal" (forall (name :: Symbol) r a (f :: * -> *).
(HasField name r a, Functor f) =>
(a -> f a) -> r -> f r
field @"cfgGhcupCabal") Bool
True
forall a b. a -> (a -> b) -> b
^^^ forall (c :: * -> Constraint) (p :: * -> * -> *) s a.
OptionsGrammar c p =>
String -> p s a -> p s a
help String
"Use (or don't) ghcup to install cabal"
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> forall (c :: * -> Constraint) (p :: * -> * -> *) s.
OptionsGrammar c p =>
ByteString
-> ALens' s VersionRange -> VersionRange -> p s VersionRange
rangeField ByteString
"ghcup-jobs" (forall (name :: Symbol) r a (f :: * -> *).
(HasField name r a, Functor f) =>
(a -> f a) -> r -> f r
field @"cfgGhcupJobs") (VersionRange -> VersionRange -> VersionRange
C.unionVersionRanges (VersionRange -> VersionRange -> VersionRange
C.intersectVersionRanges (Version -> VersionRange
C.laterVersion ([Int] -> Version
mkVersion [Int
8,Int
10,Int
4])) (Version -> VersionRange
C.earlierVersion ([Int] -> Version
mkVersion [Int
9]))) (Version -> VersionRange
C.laterVersion ([Int] -> Version
mkVersion [Int
9,Int
0,Int
1])))
forall a b. a -> (a -> b) -> b
^^^ forall (c :: * -> Constraint) (p :: * -> * -> *) s a.
OptionsGrammar c p =>
String -> String -> p s a -> p s a
metahelp String
"RANGE" String
"(Linux) jobs to use ghcup to install tools"
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> forall (c :: * -> Constraint) (g :: * -> * -> *) s a.
(FieldGrammar c g, Functor (g s), c (Identity a), Eq a) =>
ByteString -> ALens' s a -> a -> g s a
C.optionalFieldDef ByteString
"ghcup-version" (forall (name :: Symbol) r a (f :: * -> *).
(HasField name r a, Functor f) =>
(a -> f a) -> r -> f r
field @"cfgGhcupVersion") Version
defaultGhcupVersion
forall a b. a -> (a -> b) -> b
^^^ forall (c :: * -> Constraint) (p :: * -> * -> *) s a.
OptionsGrammar c p =>
String -> String -> p s a -> p s a
metahelp String
"VERSION" String
"ghcup version"
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> forall (c :: * -> Constraint) (g :: * -> * -> *) b a s.
(FieldGrammar c g, c b, Monoid a, Newtype a b) =>
ByteString -> (a -> b) -> ALens' s a -> g s a
C.monoidalFieldAla ByteString
"apt" (forall sep a b. sep -> (a -> b) -> Set a -> AlaSet sep b a
alaSet' NoCommaFSep
C.NoCommaFSep String -> Token'
C.Token') (forall (name :: Symbol) r a (f :: * -> *).
(HasField name r a, Functor f) =>
(a -> f a) -> r -> f r
field @"cfgApt")
forall a b. a -> (a -> b) -> b
^^^ forall (c :: * -> Constraint) (p :: * -> * -> *) s a.
OptionsGrammar c p =>
String -> String -> p s a -> p s a
metahelp String
"PKG" String
"Additional apt packages to install"
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> forall (c :: * -> Constraint) (g :: * -> * -> *) b a s.
(FieldGrammar c g, c b, Monoid a, Newtype a b) =>
ByteString -> (a -> b) -> ALens' s a -> g s a
C.monoidalFieldAla ByteString
"travis-patches" (forall sep a b. sep -> (a -> b) -> [a] -> List sep b a
C.alaList' NoCommaFSep
C.NoCommaFSep String -> Token'
C.Token') (forall (name :: Symbol) r a (f :: * -> *).
(HasField name r a, Functor f) =>
(a -> f a) -> r -> f r
field @"cfgTravisPatches")
forall a b. a -> (a -> b) -> b
^^^ forall (c :: * -> Constraint) (p :: * -> * -> *) s a.
OptionsGrammar c p =>
String -> String -> String -> p s a -> p s a
metaActionHelp String
"PATCH" String
"file" String
".patch files to apply to the generated Travis YAML file"
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> forall (c :: * -> Constraint) (g :: * -> * -> *) b a s.
(FieldGrammar c g, c b, Monoid a, Newtype a b) =>
ByteString -> (a -> b) -> ALens' s a -> g s a
C.monoidalFieldAla ByteString
"github-patches" (forall sep a b. sep -> (a -> b) -> [a] -> List sep b a
C.alaList' NoCommaFSep
C.NoCommaFSep String -> Token'
C.Token') (forall (name :: Symbol) r a (f :: * -> *).
(HasField name r a, Functor f) =>
(a -> f a) -> r -> f r
field @"cfgGitHubPatches")
forall a b. a -> (a -> b) -> b
^^^ forall (c :: * -> Constraint) (p :: * -> * -> *) s a.
OptionsGrammar c p =>
String -> String -> String -> p s a -> p s a
metaActionHelp String
"PATCH" String
"file" String
".patch files to apply to the generated GitHub Actions YAML file"
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> forall (c :: * -> Constraint) (g :: * -> * -> *) s.
FieldGrammar c g =>
ByteString -> ALens' s Bool -> Bool -> g s Bool
C.booleanFieldDef ByteString
"insert-version" (forall (name :: Symbol) r a (f :: * -> *).
(HasField name r a, Functor f) =>
(a -> f a) -> r -> f r
field @"cfgInsertVersion") Bool
True
forall a b. a -> (a -> b) -> b
^^^ forall (c :: * -> Constraint) (p :: * -> * -> *) s a.
OptionsGrammar c p =>
String -> p s a -> p s a
help String
"Don't insert the haskell-ci version into the generated Travis YAML file"
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> forall (c :: * -> Constraint) (g :: * -> * -> *) s a.
(FieldGrammar c g, Functor (g s), c (Identity a), Eq a) =>
ByteString -> ALens' s a -> a -> g s a
C.optionalFieldDef ByteString
"error-missing-methods" (forall (name :: Symbol) r a (f :: * -> *).
(HasField name r a, Functor f) =>
(a -> f a) -> r -> f r
field @"cfgErrorMissingMethods") PackageScope
PackageScopeLocal
forall a b. a -> (a -> b) -> b
^^^ forall (c :: * -> Constraint) (p :: * -> * -> *) s a.
OptionsGrammar c p =>
String -> String -> p s a -> p s a
metahelp String
"PKGSCOPE" String
"Insert -Werror=missing-methods for package scope (none, local, all)"
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> forall (c :: * -> Constraint) (g :: * -> * -> *) a b d.
FieldGrammar c g =>
ALens' a b -> g b d -> g a d
C.blurFieldGrammar (forall (name :: Symbol) r a (f :: * -> *).
(HasField name r a, Functor f) =>
(a -> f a) -> r -> f r
field @"cfgDoctest") forall (c :: * -> Constraint) (g :: * -> * -> *).
(OptionsGrammar c g, Applicative (g DoctestConfig)) =>
g DoctestConfig DoctestConfig
doctestConfigGrammar
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> forall (c :: * -> Constraint) (g :: * -> * -> *) a b d.
FieldGrammar c g =>
ALens' a b -> g b d -> g a d
C.blurFieldGrammar (forall (name :: Symbol) r a (f :: * -> *).
(HasField name r a, Functor f) =>
(a -> f a) -> r -> f r
field @"cfgDocspec") forall (c :: * -> Constraint) (g :: * -> * -> *).
(OptionsGrammar c g, Applicative (g DocspecConfig)) =>
g DocspecConfig DocspecConfig
docspecConfigGrammar
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> forall (c :: * -> Constraint) (g :: * -> * -> *) a b d.
FieldGrammar c g =>
ALens' a b -> g b d -> g a d
C.blurFieldGrammar (forall (name :: Symbol) r a (f :: * -> *).
(HasField name r a, Functor f) =>
(a -> f a) -> r -> f r
field @"cfgHLint") forall (c :: * -> Constraint) (g :: * -> * -> *).
(OptionsGrammar c g, Applicative (g HLintConfig),
c (Identity HLintJob)) =>
g HLintConfig HLintConfig
hlintConfigGrammar
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> forall (f :: * -> *) a. Applicative f => a -> f a
pure []
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> forall (f :: * -> *) a. Applicative f => a -> f a
pure []
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> forall (c :: * -> Constraint) (g :: * -> * -> *) s.
FieldGrammar c g =>
ByteString -> ALens' s String -> g s String
C.freeTextFieldDef ByteString
"raw-travis" (forall (name :: Symbol) r a (f :: * -> *).
(HasField name r a, Functor f) =>
(a -> f a) -> r -> f r
field @"cfgRawTravis")
forall a b. a -> (a -> b) -> b
^^^ forall (c :: * -> Constraint) (p :: * -> * -> *) s a.
OptionsGrammar c p =>
String -> p s a -> p s a
help String
"Raw travis commands which will be run at the very end of the script"
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> forall (c :: * -> Constraint) (g :: * -> * -> *) s.
FieldGrammar c g =>
ByteString -> ALens' s (Maybe String) -> g s (Maybe String)
C.freeTextField ByteString
"github-action-name" (forall (name :: Symbol) r a (f :: * -> *).
(HasField name r a, Functor f) =>
(a -> f a) -> r -> f r
field @"cfgGitHubActionName")
forall a b. a -> (a -> b) -> b
^^^ forall (c :: * -> Constraint) (p :: * -> * -> *) s a.
OptionsGrammar c p =>
String -> p s a -> p s a
help String
"The name of GitHub Action"
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> forall (c :: * -> Constraint) (g :: * -> * -> *) s a.
(FieldGrammar c g, Functor (g s), c (Identity a), Eq a) =>
ByteString -> ALens' s a -> a -> g s a
C.optionalFieldDef ByteString
"timeout-minutes" (forall (name :: Symbol) r a (f :: * -> *).
(HasField name r a, Functor f) =>
(a -> f a) -> r -> f r
field @"cfgTimeoutMinutes") Natural
60
forall a b. a -> (a -> b) -> b
^^^ forall (c :: * -> Constraint) (p :: * -> * -> *) s a.
OptionsGrammar c p =>
String -> String -> p s a -> p s a
metahelp String
"MINUTES" String
"The maximum number of minutes to let a job run"
readConfigFile :: MonadIO m => FilePath -> m Config
readConfigFile :: forall (m :: * -> *). MonadIO m => String -> m Config
readConfigFile = forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. ([Field Position] -> ParseResult a) -> String -> IO a
readAndParseFile [Field Position] -> ParseResult Config
parseConfigFile
parseConfigFile :: [C.Field C.Position] -> C.ParseResult Config
parseConfigFile :: [Field Position] -> ParseResult Config
parseConfigFile [Field Position]
fields0 = do
Config
config <- forall s a.
CabalSpecVersion
-> Fields Position -> ParsecFieldGrammar s a -> ParseResult a
C.parseFieldGrammar CabalSpecVersion
C.cabalSpecLatest Fields Position
fields forall (c :: * -> Constraint) (g :: * -> * -> *).
(OptionsGrammar c g, Applicative (g Config), c (Identity HLintJob),
c (Identity PackageScope), c (Identity TestedWithJobs),
c (Identity Ubuntu), c (Identity Jobs), c (Identity CopyFields),
c (Identity Version), c (Identity Natural),
c (Identity Components), c Env, c Folds, c CopyFields,
c HeadVersion, c (List FSep (Identity Installed) Installed),
Applicative (g DoctestConfig), Applicative (g DocspecConfig),
Applicative (g HLintConfig)) =>
g Config Config
configGrammar
[Config -> Config]
config' <- forall (t :: * -> *) (f :: * -> *) a b.
(Traversable t, Applicative f) =>
(a -> f b) -> t a -> f (t b)
traverse Section Position -> ParseResult (Config -> Config)
parseSection forall a b. (a -> b) -> a -> b
$ forall (t :: * -> *) a. Foldable t => t [a] -> [a]
concat [[Section Position]]
sections
forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ Config -> Config
postprocess forall a b. (a -> b) -> a -> b
$ forall (t :: * -> *) b a.
Foldable t =>
(b -> a -> b) -> b -> t a -> b
foldl' forall a b. a -> (a -> b) -> b
(&) Config
config [Config -> Config]
config'
where
(Fields Position
fields, [[Section Position]]
sections) = forall ann. [Field ann] -> (Fields ann, [[Section ann]])
C.partitionFields [Field Position]
fields0
parseSection :: C.Section C.Position -> C.ParseResult (Config -> Config)
parseSection :: Section Position -> ParseResult (Config -> Config)
parseSection (C.MkSection (C.Name Position
pos ByteString
name) [SectionArg Position]
args [Field Position]
cfields)
| ByteString
name forall a. Eq a => a -> a -> Bool
== ByteString
"constraint-set" = do
String
name' <- Position -> [SectionArg Position] -> ParseResult String
parseName Position
pos [SectionArg Position]
args
let (Fields Position
fs, [[Section Position]]
_sections) = forall ann. [Field ann] -> (Fields ann, [[Section ann]])
C.partitionFields [Field Position]
cfields
ConstraintSet
cs <- forall s a.
CabalSpecVersion
-> Fields Position -> ParsecFieldGrammar s a -> ParseResult a
C.parseFieldGrammar CabalSpecVersion
C.cabalSpecLatest Fields Position
fs (forall (c :: * -> Constraint) (g :: * -> * -> *).
(OptionsGrammar c g, Applicative (g ConstraintSet)) =>
String -> g ConstraintSet ConstraintSet
constraintSetGrammar String
name')
forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ forall s t a b. ASetter s t a b -> (a -> b) -> s -> t
over (forall (name :: Symbol) r a (f :: * -> *).
(HasField name r a, Functor f) =>
(a -> f a) -> r -> f r
field @"cfgConstraintSets") (ConstraintSet
cs forall a. a -> [a] -> [a]
:)
| ByteString
name forall a. Eq a => a -> a -> Bool
== ByteString
"raw-project" = do
let fs :: [PrettyField Position]
fs = forall ann. [Field ann] -> [PrettyField ann]
C.fromParsecFields [Field Position]
cfields
forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ forall s t a b. ASetter s t a b -> (a -> b) -> s -> t
over (forall (name :: Symbol) r a (f :: * -> *).
(HasField name r a, Functor f) =>
(a -> f a) -> r -> f r
field @"cfgRawProject") (forall a. [a] -> [a] -> [a]
++ forall a b. (a -> b) -> [a] -> [b]
map forall (f :: * -> *) a. Functor f => f a -> f ()
void [PrettyField Position]
fs)
| Bool
otherwise = do
Position -> PWarnType -> String -> ParseResult ()
C.parseWarning Position
pos PWarnType
C.PWTUnknownSection forall a b. (a -> b) -> a -> b
$ String
"Unknown section " forall a. [a] -> [a] -> [a]
++ ByteString -> String
fromUTF8BS ByteString
name
forall (m :: * -> *) a. Monad m => a -> m a
return forall a. a -> a
id
postprocess :: Config -> Config
postprocess :: Config -> Config
postprocess Config
cfg
| Config -> Ubuntu
cfgUbuntu Config
cfg forall a. Ord a => a -> a -> Bool
>= Ubuntu
Jammy = Config
cfg { cfgGhcupJobs :: VersionRange
cfgGhcupJobs = VersionRange
anyVersion }
| Bool
otherwise = Config
cfg
newtype Env = Env (M.Map Version String)
deriving anyclass (C.Newtype (M.Map Version String))
instance C.Parsec Env where
parsec :: forall (m :: * -> *). CabalParsing m => m Env
parsec = Map Version String -> Env
Env forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall k a. Ord k => [(k, a)] -> Map k a
M.fromList forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall (m :: * -> *) a. CabalParsing m => m a -> m [a]
C.parsecLeadingCommaList m (Version, String)
p where
p :: m (Version, String)
p = do
Version
v <- forall a (m :: * -> *). (Parsec a, CabalParsing m) => m a
C.parsec
Char
_ <- forall (m :: * -> *). CharParsing m => Char -> m Char
C.char Char
':'
String
s <- forall (m :: * -> *). CharParsing m => (Char -> Bool) -> m String
C.munch1 forall a b. (a -> b) -> a -> b
$ \Char
c -> Char
c forall a. Eq a => a -> a -> Bool
/= Char
','
forall (m :: * -> *) a. Monad m => a -> m a
return (Version
v, String
s)
instance C.Pretty Env where
pretty :: Env -> Doc
pretty (Env Map Version String
m) = [Doc] -> Doc
PP.fsep forall b c a. (b -> c) -> (a -> b) -> a -> c
. Doc -> [Doc] -> [Doc]
PP.punctuate Doc
PP.comma forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a b. (a -> b) -> [a] -> [b]
map forall {a}. Pretty a => (a, String) -> Doc
p forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall k a. Map k a -> [(k, a)]
M.toList forall a b. (a -> b) -> a -> b
$ Map Version String
m where
p :: (a, String) -> Doc
p (a
v, String
s) = forall a. Pretty a => a -> Doc
C.pretty a
v Doc -> Doc -> Doc
PP.<> Doc
PP.colon Doc -> Doc -> Doc
PP.<> String -> Doc
PP.text String
s
parseName :: C.Position -> [C.SectionArg C.Position] -> C.ParseResult String
parseName :: Position -> [SectionArg Position] -> ParseResult String
parseName Position
pos [SectionArg Position]
args = ByteString -> String
fromUTF8BS forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Position -> [SectionArg Position] -> ParseResult ByteString
parseNameBS Position
pos [SectionArg Position]
args
parseNameBS :: C.Position -> [C.SectionArg C.Position] -> C.ParseResult BS.ByteString
parseNameBS :: Position -> [SectionArg Position] -> ParseResult ByteString
parseNameBS Position
pos [SectionArg Position]
args = case [SectionArg Position]
args of
[C.SecArgName Position
_pos ByteString
secName] ->
forall (f :: * -> *) a. Applicative f => a -> f a
pure ByteString
secName
[C.SecArgStr Position
_pos ByteString
secName] ->
forall (f :: * -> *) a. Applicative f => a -> f a
pure ByteString
secName
[] -> do
Position -> String -> ParseResult ()
C.parseFailure Position
pos String
"name required"
forall (f :: * -> *) a. Applicative f => a -> f a
pure ByteString
""
[SectionArg Position]
_ -> do
Position -> String -> ParseResult ()
C.parseFailure Position
pos forall a b. (a -> b) -> a -> b
$ String
"Invalid name " forall a. [a] -> [a] -> [a]
++ forall a. Show a => a -> String
show [SectionArg Position]
args
forall (f :: * -> *) a. Applicative f => a -> f a
pure ByteString
""