{-# LANGUAGE DataKinds #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE TypeApplications #-}
module HaskellCI.Config.Doctest where
import HaskellCI.Prelude
import Distribution.Version (majorBoundVersion)
import qualified Distribution.FieldGrammar as C
import qualified Distribution.Types.PackageName as C
import HaskellCI.OptionsGrammar
data DoctestConfig = DoctestConfig
{ DoctestConfig -> VersionRange
cfgDoctestEnabled :: !VersionRange
, DoctestConfig -> [String]
cfgDoctestOptions :: [String]
, DoctestConfig -> VersionRange
cfgDoctestVersion :: !VersionRange
, DoctestConfig -> [PackageName]
cfgDoctestFilterEnvPkgs :: ![C.PackageName]
, DoctestConfig -> [PackageName]
cfgDoctestFilterSrcPkgs :: ![C.PackageName]
}
deriving (Int -> DoctestConfig -> ShowS
[DoctestConfig] -> ShowS
DoctestConfig -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [DoctestConfig] -> ShowS
$cshowList :: [DoctestConfig] -> ShowS
show :: DoctestConfig -> String
$cshow :: DoctestConfig -> String
showsPrec :: Int -> DoctestConfig -> ShowS
$cshowsPrec :: Int -> DoctestConfig -> ShowS
Show, forall x. Rep DoctestConfig x -> DoctestConfig
forall x. DoctestConfig -> Rep DoctestConfig x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep DoctestConfig x -> DoctestConfig
$cfrom :: forall x. DoctestConfig -> Rep DoctestConfig x
Generic, Get DoctestConfig
[DoctestConfig] -> Put
DoctestConfig -> Put
forall t. (t -> Put) -> Get t -> ([t] -> Put) -> Binary t
putList :: [DoctestConfig] -> Put
$cputList :: [DoctestConfig] -> Put
get :: Get DoctestConfig
$cget :: Get DoctestConfig
put :: DoctestConfig -> Put
$cput :: DoctestConfig -> Put
Binary)
defaultDoctestVersion :: VersionRange
defaultDoctestVersion :: VersionRange
defaultDoctestVersion = Version -> VersionRange
majorBoundVersion ([Int] -> Version
mkVersion [Int
0,Int
21,Int
0])
doctestConfigGrammar
:: (OptionsGrammar c g, Applicative (g DoctestConfig))
=> g DoctestConfig DoctestConfig
doctestConfigGrammar :: forall (c :: * -> Constraint) (g :: * -> * -> *).
(OptionsGrammar c g, Applicative (g DoctestConfig)) =>
g DoctestConfig DoctestConfig
doctestConfigGrammar = VersionRange
-> [String]
-> VersionRange
-> [PackageName]
-> [PackageName]
-> DoctestConfig
DoctestConfig
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall (c :: * -> Constraint) (p :: * -> * -> *) s.
OptionsGrammar c p =>
FieldName
-> ALens' s VersionRange -> VersionRange -> p s VersionRange
rangeField FieldName
"doctest" (forall (name :: Symbol) r a (f :: * -> *).
(HasField name r a, Functor f) =>
(a -> f a) -> r -> f r
field @"cfgDoctestEnabled") VersionRange
noVersion
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
"Enable Doctest job"
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
"doctest-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 @"cfgDoctestOptions")
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
"Additional Doctest options"
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) =>
FieldName -> ALens' s a -> a -> g s a
C.optionalFieldDef FieldName
"doctest-version" (forall (name :: Symbol) r a (f :: * -> *).
(HasField name r a, Functor f) =>
(a -> f a) -> r -> f r
field @"cfgDoctestVersion") VersionRange
defaultDoctestVersion
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
"Doctest 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) =>
FieldName -> (a -> b) -> ALens' s a -> g s a
C.monoidalFieldAla FieldName
"doctest-filter-packages" (forall sep a. sep -> [a] -> List sep (Identity a) a
C.alaList NoCommaFSep
C.NoCommaFSep) (forall (name :: Symbol) r a (f :: * -> *).
(HasField name r a, Functor f) =>
(a -> f a) -> r -> f r
field @"cfgDoctestFilterEnvPkgs")
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
"PKGS" String
"Filter packages from .ghc.environment 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) =>
FieldName -> (a -> b) -> ALens' s a -> g s a
C.monoidalFieldAla FieldName
"doctest-skip" (forall sep a. sep -> [a] -> List sep (Identity a) a
C.alaList NoCommaFSep
C.NoCommaFSep) (forall (name :: Symbol) r a (f :: * -> *).
(HasField name r a, Functor f) =>
(a -> f a) -> r -> f r
field @"cfgDoctestFilterSrcPkgs")
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
"PKGS" String
"Skip doctests for these packages"