{-# 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
(Int -> ConstraintSet -> ShowS)
-> (ConstraintSet -> String)
-> ([ConstraintSet] -> ShowS)
-> Show ConstraintSet
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> ConstraintSet -> ShowS
showsPrec :: Int -> ConstraintSet -> ShowS
$cshow :: ConstraintSet -> String
show :: ConstraintSet -> String
$cshowList :: [ConstraintSet] -> ShowS
showList :: [ConstraintSet] -> ShowS
Show, (forall x. ConstraintSet -> Rep ConstraintSet x)
-> (forall x. Rep ConstraintSet x -> ConstraintSet)
-> Generic ConstraintSet
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
$cfrom :: forall x. ConstraintSet -> Rep ConstraintSet x
from :: forall x. ConstraintSet -> Rep ConstraintSet x
$cto :: forall x. Rep ConstraintSet x -> ConstraintSet
to :: forall x. Rep ConstraintSet x -> ConstraintSet
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
    (VersionRange
 -> Bool
 -> [String]
 -> Bool
 -> Bool
 -> Bool
 -> Bool
 -> Bool
 -> ConstraintSet)
-> g ConstraintSet VersionRange
-> g ConstraintSet
     (Bool
      -> [String]
      -> Bool
      -> Bool
      -> Bool
      -> Bool
      -> Bool
      -> ConstraintSet)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> FieldName
-> ALens' ConstraintSet VersionRange
-> VersionRange
-> g ConstraintSet VersionRange
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
    g ConstraintSet
  (Bool
   -> [String]
   -> Bool
   -> Bool
   -> Bool
   -> Bool
   -> Bool
   -> ConstraintSet)
-> g ConstraintSet Bool
-> g ConstraintSet
     ([String] -> Bool -> Bool -> Bool -> Bool -> Bool -> ConstraintSet)
forall a b.
g ConstraintSet (a -> b) -> g ConstraintSet a -> g ConstraintSet b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> FieldName
-> ALens' ConstraintSet Bool -> Bool -> g ConstraintSet Bool
forall s. FieldName -> ALens' s Bool -> Bool -> g s Bool
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
    g ConstraintSet
  ([String] -> Bool -> Bool -> Bool -> Bool -> Bool -> ConstraintSet)
-> g ConstraintSet [String]
-> g ConstraintSet
     (Bool -> Bool -> Bool -> Bool -> Bool -> ConstraintSet)
forall a b.
g ConstraintSet (a -> b) -> g ConstraintSet a -> g ConstraintSet b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> FieldName
-> ([String] -> List CommaVCat NoCommas String)
-> ALens' ConstraintSet [String]
-> g ConstraintSet [String]
forall b a s.
(c b, Monoid a, Newtype a b) =>
FieldName -> (a -> b) -> ALens' s a -> g s a
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" (CommaVCat
-> (String -> NoCommas)
-> [String]
-> List CommaVCat NoCommas String
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")
    g ConstraintSet
  (Bool -> Bool -> Bool -> Bool -> Bool -> ConstraintSet)
-> g ConstraintSet Bool
-> g ConstraintSet (Bool -> Bool -> Bool -> Bool -> ConstraintSet)
forall a b.
g ConstraintSet (a -> b) -> g ConstraintSet a -> g ConstraintSet b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> FieldName
-> ALens' ConstraintSet Bool -> Bool -> g ConstraintSet Bool
forall s. FieldName -> ALens' s Bool -> Bool -> g s Bool
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
    g ConstraintSet (Bool -> Bool -> Bool -> Bool -> ConstraintSet)
-> g ConstraintSet Bool
-> g ConstraintSet (Bool -> Bool -> Bool -> ConstraintSet)
forall a b.
g ConstraintSet (a -> b) -> g ConstraintSet a -> g ConstraintSet b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> FieldName
-> ALens' ConstraintSet Bool -> Bool -> g ConstraintSet Bool
forall s. FieldName -> ALens' s Bool -> Bool -> g s Bool
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
    g ConstraintSet (Bool -> Bool -> Bool -> ConstraintSet)
-> g ConstraintSet Bool
-> g ConstraintSet (Bool -> Bool -> ConstraintSet)
forall a b.
g ConstraintSet (a -> b) -> g ConstraintSet a -> g ConstraintSet b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> FieldName
-> ALens' ConstraintSet Bool -> Bool -> g ConstraintSet Bool
forall s. FieldName -> ALens' s Bool -> Bool -> g s Bool
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
    g ConstraintSet (Bool -> Bool -> ConstraintSet)
-> g ConstraintSet Bool -> g ConstraintSet (Bool -> ConstraintSet)
forall a b.
g ConstraintSet (a -> b) -> g ConstraintSet a -> g ConstraintSet b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> FieldName
-> ALens' ConstraintSet Bool -> Bool -> g ConstraintSet Bool
forall s. FieldName -> ALens' s Bool -> Bool -> g s Bool
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
    g ConstraintSet (Bool -> ConstraintSet)
-> g ConstraintSet Bool -> g ConstraintSet ConstraintSet
forall a b.
g ConstraintSet (a -> b) -> g ConstraintSet a -> g ConstraintSet b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> FieldName
-> ALens' ConstraintSet Bool -> Bool -> g ConstraintSet Bool
forall s. FieldName -> ALens' s Bool -> Bool -> g s Bool
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