{-# LANGUAGE ConstraintKinds #-}
{-# LANGUAGE DataKinds #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE TypeApplications #-}
module HaskellCI.Config.HLint where
import HaskellCI.Prelude
import Distribution.Version (withinVersion)
import qualified Distribution.Compat.CharParsing as C
import qualified Distribution.FieldGrammar as C
import qualified Distribution.Parsec as C
import qualified Distribution.Pretty as C
import qualified Text.PrettyPrint as PP
import HaskellCI.OptionsGrammar
data HLintConfig = HLintConfig
{ HLintConfig -> Bool
cfgHLintEnabled :: !Bool
, HLintConfig -> HLintJob
cfgHLintJob :: !HLintJob
, HLintConfig -> Maybe FilePath
cfgHLintYaml :: !(Maybe FilePath)
, HLintConfig -> [FilePath]
cfgHLintOptions :: [String]
, HLintConfig -> VersionRange
cfgHLintVersion :: !VersionRange
, HLintConfig -> Bool
cfgHLintDownload :: !Bool
}
deriving (Int -> HLintConfig -> ShowS
[HLintConfig] -> ShowS
HLintConfig -> FilePath
forall a.
(Int -> a -> ShowS) -> (a -> FilePath) -> ([a] -> ShowS) -> Show a
showList :: [HLintConfig] -> ShowS
$cshowList :: [HLintConfig] -> ShowS
show :: HLintConfig -> FilePath
$cshow :: HLintConfig -> FilePath
showsPrec :: Int -> HLintConfig -> ShowS
$cshowsPrec :: Int -> HLintConfig -> ShowS
Show, forall x. Rep HLintConfig x -> HLintConfig
forall x. HLintConfig -> Rep HLintConfig x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep HLintConfig x -> HLintConfig
$cfrom :: forall x. HLintConfig -> Rep HLintConfig x
Generic, Get HLintConfig
[HLintConfig] -> Put
HLintConfig -> Put
forall t. (t -> Put) -> Get t -> ([t] -> Put) -> Binary t
putList :: [HLintConfig] -> Put
$cputList :: [HLintConfig] -> Put
get :: Get HLintConfig
$cget :: Get HLintConfig
put :: HLintConfig -> Put
$cput :: HLintConfig -> Put
Binary)
defaultHLintVersion :: VersionRange
defaultHLintVersion :: VersionRange
defaultHLintVersion = Version -> VersionRange
withinVersion ([Int] -> Version
mkVersion [Int
3,Int
5])
data HLintJob
= HLintJobLatest
| HLintJob Version
deriving (HLintJob -> HLintJob -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: HLintJob -> HLintJob -> Bool
$c/= :: HLintJob -> HLintJob -> Bool
== :: HLintJob -> HLintJob -> Bool
$c== :: HLintJob -> HLintJob -> Bool
Eq, Int -> HLintJob -> ShowS
[HLintJob] -> ShowS
HLintJob -> FilePath
forall a.
(Int -> a -> ShowS) -> (a -> FilePath) -> ([a] -> ShowS) -> Show a
showList :: [HLintJob] -> ShowS
$cshowList :: [HLintJob] -> ShowS
show :: HLintJob -> FilePath
$cshow :: HLintJob -> FilePath
showsPrec :: Int -> HLintJob -> ShowS
$cshowsPrec :: Int -> HLintJob -> ShowS
Show, forall x. Rep HLintJob x -> HLintJob
forall x. HLintJob -> Rep HLintJob x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep HLintJob x -> HLintJob
$cfrom :: forall x. HLintJob -> Rep HLintJob x
Generic, Get HLintJob
[HLintJob] -> Put
HLintJob -> Put
forall t. (t -> Put) -> Get t -> ([t] -> Put) -> Binary t
putList :: [HLintJob] -> Put
$cputList :: [HLintJob] -> Put
get :: Get HLintJob
$cget :: Get HLintJob
put :: HLintJob -> Put
$cput :: HLintJob -> Put
Binary)
instance C.Parsec HLintJob where
parsec :: forall (m :: * -> *). CabalParsing m => m HLintJob
parsec = HLintJob
HLintJobLatest forall (f :: * -> *) a b. Functor f => a -> f b -> f a
<$ forall (m :: * -> *). CharParsing m => FilePath -> m FilePath
C.string FilePath
"latest"
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> Version -> HLintJob
HLintJob forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall a (m :: * -> *). (Parsec a, CabalParsing m) => m a
C.parsec
instance C.Pretty HLintJob where
pretty :: HLintJob -> Doc
pretty HLintJob
HLintJobLatest = FilePath -> Doc
PP.text FilePath
"latest"
pretty (HLintJob Version
v) = forall a. Pretty a => a -> Doc
C.pretty Version
v
hlintConfigGrammar
:: (OptionsGrammar c g, Applicative (g HLintConfig), c (Identity HLintJob))
=> g HLintConfig HLintConfig
hlintConfigGrammar :: forall (c :: * -> Constraint) (g :: * -> * -> *).
(OptionsGrammar c g, Applicative (g HLintConfig),
c (Identity HLintJob)) =>
g HLintConfig HLintConfig
hlintConfigGrammar = Bool
-> HLintJob
-> Maybe FilePath
-> [FilePath]
-> VersionRange
-> Bool
-> HLintConfig
HLintConfig
forall (f :: * -> *) a b. Functor 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
"hlint" (forall (name :: Symbol) r a (f :: * -> *).
(HasField name r a, Functor f) =>
(a -> f a) -> r -> f r
field @"cfgHLintEnabled") Bool
False
forall a b. a -> (a -> b) -> b
^^^ forall (c :: * -> Constraint) (p :: * -> * -> *) s a.
OptionsGrammar c p =>
FilePath -> p s a -> p s a
help FilePath
"Enable HLint job"
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
"hlint-job" (forall (name :: Symbol) r a (f :: * -> *).
(HasField name r a, Functor f) =>
(a -> f a) -> r -> f r
field @"cfgHLintJob") HLintJob
HLintJobLatest
forall a b. a -> (a -> b) -> b
^^^ forall (c :: * -> Constraint) (p :: * -> * -> *) s a.
OptionsGrammar c p =>
FilePath -> FilePath -> p s a -> p s a
metahelp FilePath
"JOB" FilePath
"Specify HLint 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, Newtype a b) =>
FieldName -> (a -> b) -> ALens' s (Maybe a) -> g s (Maybe a)
C.optionalFieldAla FieldName
"hlint-yaml" FilePath -> FilePathNT
C.FilePathNT (forall (name :: Symbol) r a (f :: * -> *).
(HasField name r a, Functor f) =>
(a -> f a) -> r -> f r
field @"cfgHLintYaml")
forall a b. a -> (a -> b) -> b
^^^ forall (c :: * -> Constraint) (p :: * -> * -> *) s a.
OptionsGrammar c p =>
FilePath -> FilePath -> FilePath -> p s a -> p s a
metaActionHelp FilePath
"PATH" FilePath
"file" FilePath
"Use specific .hlint.yaml"
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
"hlint-options" (forall sep a b. sep -> (a -> b) -> [a] -> List sep b a
C.alaList' NoCommaFSep
C.NoCommaFSep FilePath -> Token'
C.Token') (forall (name :: Symbol) r a (f :: * -> *).
(HasField name r a, Functor f) =>
(a -> f a) -> r -> f r
field @"cfgHLintOptions")
forall a b. a -> (a -> b) -> b
^^^ forall (c :: * -> Constraint) (p :: * -> * -> *) s a.
OptionsGrammar c p =>
FilePath -> FilePath -> p s a -> p s a
metahelp FilePath
"OPTS" FilePath
"Additional HLint 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
"hlint-version" (forall (name :: Symbol) r a (f :: * -> *).
(HasField name r a, Functor f) =>
(a -> f a) -> r -> f r
field @"cfgHLintVersion") VersionRange
defaultHLintVersion
forall a b. a -> (a -> b) -> b
^^^ forall (c :: * -> Constraint) (p :: * -> * -> *) s a.
OptionsGrammar c p =>
FilePath -> FilePath -> p s a -> p s a
metahelp FilePath
"RANGE" FilePath
"HLint version"
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
"hlint-download-binary" (forall (name :: Symbol) r a (f :: * -> *).
(HasField name r a, Functor f) =>
(a -> f a) -> r -> f r
field @"cfgHLintDownload") Bool
True
forall a b. a -> (a -> b) -> b
^^^ forall (c :: * -> Constraint) (p :: * -> * -> *) s a.
OptionsGrammar c p =>
FilePath -> p s a -> p s a
help FilePath
"Download HLint binary release"