{-# LANGUAGE DataKinds #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE TypeApplications #-}
module HaskellCI.Config.ConstraintSet where
import HaskellCI.Prelude
import qualified Distribution.FieldGrammar as C
import HaskellCI.Newtypes
import HaskellCI.OptionsGrammar
data ConstraintSet = ConstraintSet
{ ConstraintSet -> String
csName :: String
, ConstraintSet -> VersionRange
csGhcVersions :: VersionRange
, ConstraintSet -> Bool
csGhcjs :: Bool
, ConstraintSet -> [String]
csConstraints :: [String]
, ConstraintSet -> Bool
csTests :: Bool
, ConstraintSet -> Bool
csRunTests :: Bool
, ConstraintSet -> Bool
csDocspec :: Bool
, ConstraintSet -> Bool
csBenchmarks :: Bool
, ConstraintSet -> Bool
csHaddock :: Bool
}
deriving (Int -> ConstraintSet -> ShowS
[ConstraintSet] -> ShowS
ConstraintSet -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ConstraintSet] -> ShowS
$cshowList :: [ConstraintSet] -> ShowS
show :: ConstraintSet -> String
$cshow :: ConstraintSet -> String
showsPrec :: Int -> ConstraintSet -> ShowS
$cshowsPrec :: Int -> ConstraintSet -> ShowS
Show, forall x. Rep ConstraintSet x -> ConstraintSet
forall x. ConstraintSet -> Rep ConstraintSet x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep ConstraintSet x -> ConstraintSet
$cfrom :: forall x. ConstraintSet -> Rep ConstraintSet x
Generic)
constraintSetGrammar
:: ( OptionsGrammar c g, Applicative (g ConstraintSet)
)
=> String -> g ConstraintSet ConstraintSet
constraintSetGrammar :: forall (c :: * -> Constraint) (g :: * -> * -> *).
(OptionsGrammar c g, Applicative (g ConstraintSet)) =>
String -> g ConstraintSet ConstraintSet
constraintSetGrammar String
name = String
-> VersionRange
-> Bool
-> [String]
-> Bool
-> Bool
-> Bool
-> Bool
-> Bool
-> ConstraintSet
ConstraintSet String
name
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall (c :: * -> Constraint) (g :: * -> * -> *) s a.
(FieldGrammar c g, Functor (g s), c (Identity a), Eq a) =>
FieldName -> ALens' s a -> a -> g s a
C.optionalFieldDef FieldName
"ghc" (forall (name :: Symbol) r a (f :: * -> *).
(HasField name r a, Functor f) =>
(a -> f a) -> r -> f r
field @"csGhcVersions") VersionRange
anyVersion
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> forall (c :: * -> Constraint) (g :: * -> * -> *) s.
FieldGrammar c g =>
FieldName -> ALens' s Bool -> Bool -> g s Bool
C.booleanFieldDef FieldName
"ghcjs" (forall (name :: Symbol) r a (f :: * -> *).
(HasField name r a, Functor f) =>
(a -> f a) -> r -> f r
field @"csGhcjs") Bool
True
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) =>
FieldName -> (a -> b) -> ALens' s a -> g s a
C.monoidalFieldAla FieldName
"constraints" (forall sep a b. sep -> (a -> b) -> [a] -> List sep b a
C.alaList' CommaVCat
C.CommaVCat String -> NoCommas
NoCommas) (forall (name :: Symbol) r a (f :: * -> *).
(HasField name r a, Functor f) =>
(a -> f a) -> r -> f r
field @"csConstraints")
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> forall (c :: * -> Constraint) (g :: * -> * -> *) s.
FieldGrammar c g =>
FieldName -> ALens' s Bool -> Bool -> g s Bool
C.booleanFieldDef FieldName
"tests" (forall (name :: Symbol) r a (f :: * -> *).
(HasField name r a, Functor f) =>
(a -> f a) -> r -> f r
field @"csTests") Bool
False
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> forall (c :: * -> Constraint) (g :: * -> * -> *) s.
FieldGrammar c g =>
FieldName -> ALens' s Bool -> Bool -> g s Bool
C.booleanFieldDef FieldName
"run-tests" (forall (name :: Symbol) r a (f :: * -> *).
(HasField name r a, Functor f) =>
(a -> f a) -> r -> f r
field @"csRunTests") Bool
False
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> forall (c :: * -> Constraint) (g :: * -> * -> *) s.
FieldGrammar c g =>
FieldName -> ALens' s Bool -> Bool -> g s Bool
C.booleanFieldDef FieldName
"docspec" (forall (name :: Symbol) r a (f :: * -> *).
(HasField name r a, Functor f) =>
(a -> f a) -> r -> f r
field @"csDocspec") Bool
False
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> forall (c :: * -> Constraint) (g :: * -> * -> *) s.
FieldGrammar c g =>
FieldName -> ALens' s Bool -> Bool -> g s Bool
C.booleanFieldDef FieldName
"benchmarks" (forall (name :: Symbol) r a (f :: * -> *).
(HasField name r a, Functor f) =>
(a -> f a) -> r -> f r
field @"csBenchmarks") Bool
False
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> forall (c :: * -> Constraint) (g :: * -> * -> *) s.
FieldGrammar c g =>
FieldName -> ALens' s Bool -> Bool -> g s Bool
C.booleanFieldDef FieldName
"haddock" (forall (name :: Symbol) r a (f :: * -> *).
(HasField name r a, Functor f) =>
(a -> f a) -> r -> f r
field @"csHaddock") Bool
False