{-# LANGUAGE DataKinds #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE TypeApplications #-}
module HaskellCI.Config.Docspec (
DocspecConfig (..),
docspecConfigGrammar,
) where
import HaskellCI.Prelude
import qualified Distribution.FieldGrammar as C
import HaskellCI.OptionsGrammar
data DocspecConfig = DocspecConfig
{ DocspecConfig -> VersionRange
cfgDocspecEnabled :: !VersionRange
, DocspecConfig -> [String]
cfgDocspecOptions :: [String]
, DocspecConfig -> String
cfgDocspecUrl :: String
, DocspecConfig -> String
cfgDocspecHash :: String
}
deriving (Int -> DocspecConfig -> ShowS
[DocspecConfig] -> ShowS
DocspecConfig -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [DocspecConfig] -> ShowS
$cshowList :: [DocspecConfig] -> ShowS
show :: DocspecConfig -> String
$cshow :: DocspecConfig -> String
showsPrec :: Int -> DocspecConfig -> ShowS
$cshowsPrec :: Int -> DocspecConfig -> ShowS
Show, forall x. Rep DocspecConfig x -> DocspecConfig
forall x. DocspecConfig -> Rep DocspecConfig x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep DocspecConfig x -> DocspecConfig
$cfrom :: forall x. DocspecConfig -> Rep DocspecConfig x
Generic, Get DocspecConfig
[DocspecConfig] -> Put
DocspecConfig -> Put
forall t. (t -> Put) -> Get t -> ([t] -> Put) -> Binary t
putList :: [DocspecConfig] -> Put
$cputList :: [DocspecConfig] -> Put
get :: Get DocspecConfig
$cget :: Get DocspecConfig
put :: DocspecConfig -> Put
$cput :: DocspecConfig -> Put
Binary)
defaultDocspecConfig :: DocspecConfig
defaultDocspecConfig :: DocspecConfig
defaultDocspecConfig = DocspecConfig
{ cfgDocspecEnabled :: VersionRange
cfgDocspecEnabled = VersionRange
noVersion
, cfgDocspecOptions :: [String]
cfgDocspecOptions = []
, cfgDocspecUrl :: String
cfgDocspecUrl = String
"https://github.com/phadej/cabal-extras/releases/download/cabal-docspec-0.0.0.20230406/cabal-docspec-0.0.0.20230406-x86_64-linux.xz"
, cfgDocspecHash :: String
cfgDocspecHash = String
"68fa9addd5dc453d533a74a763950499d4593b1297c9a05c3ea5bd1acc04c9dd"
}
docspecConfigGrammar
:: (OptionsGrammar c g, Applicative (g DocspecConfig))
=> g DocspecConfig DocspecConfig
docspecConfigGrammar :: forall (c :: * -> Constraint) (g :: * -> * -> *).
(OptionsGrammar c g, Applicative (g DocspecConfig)) =>
g DocspecConfig DocspecConfig
docspecConfigGrammar = VersionRange -> [String] -> String -> String -> DocspecConfig
DocspecConfig
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
"docspec" (forall (name :: Symbol) r a (f :: * -> *).
(HasField name r a, Functor f) =>
(a -> f a) -> r -> f r
field @"cfgDocspecEnabled") (DocspecConfig -> VersionRange
cfgDocspecEnabled DocspecConfig
defaultDocspecConfig)
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 Docspec 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
"docspec-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 @"cfgDocspecOptions")
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 Docspec options"
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) =>
FieldName -> (a -> b) -> ALens' s a -> a -> g s a
C.optionalFieldDefAla FieldName
"docspec-url" String -> Token'
C.Token' (forall (name :: Symbol) r a (f :: * -> *).
(HasField name r a, Functor f) =>
(a -> f a) -> r -> f r
field @"cfgDocspecUrl") (DocspecConfig -> String
cfgDocspecUrl DocspecConfig
defaultDocspecConfig)
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
"URL" String
"URL to download cabal-docspec"
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) =>
FieldName -> (a -> b) -> ALens' s a -> a -> g s a
C.optionalFieldDefAla FieldName
"docspec-hash" String -> Token'
C.Token' (forall (name :: Symbol) r a (f :: * -> *).
(HasField name r a, Functor f) =>
(a -> f a) -> r -> f r
field @"cfgDocspecHash") (DocspecConfig -> String
cfgDocspecHash DocspecConfig
defaultDocspecConfig)
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
"HASH" String
"SHA256 of cabal-docspec"