{-# OPTIONS_GHC -fno-warn-orphans #-}
module Xrefcheck.Config
( module Xrefcheck.Config
, module Xrefcheck.Data.Redirect
, defConfigText
) where
import Universum hiding ((.~))
import Control.Lens (makeLensesWith, (.~))
import Data.Aeson (genericParseJSON)
import Data.Yaml (FromJSON (..), decodeEither', prettyPrintParseException, withText)
import Text.Regex.TDFA.Text ()
import Time (KnownRatName, Second, Time (..), unitsP)
import Xrefcheck.Config.Default
import Xrefcheck.Core
import Xrefcheck.Data.Redirect
import Xrefcheck.Scan
import Xrefcheck.Scanners.Markdown
import Xrefcheck.Util (Field, aesonConfigOption, postfixFields)
type Config = Config' Identity
type ConfigOptional = Config' Maybe
data Config' f = Config
{ forall (f :: * -> *). Config' f -> Field f (ExclusionConfig' f)
cExclusions :: Field f (ExclusionConfig' f)
, forall (f :: * -> *). Config' f -> Field f (NetworkingConfig' f)
cNetworking :: Field f (NetworkingConfig' f)
, forall (f :: * -> *). Config' f -> ScannersConfig' f
cScanners :: ScannersConfig' f
} deriving stock ((forall x. Config' f -> Rep (Config' f) x)
-> (forall x. Rep (Config' f) x -> Config' f)
-> Generic (Config' f)
forall x. Rep (Config' f) x -> Config' f
forall x. Config' f -> Rep (Config' f) x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
forall (f :: * -> *) x. Rep (Config' f) x -> Config' f
forall (f :: * -> *) x. Config' f -> Rep (Config' f) x
$cfrom :: forall (f :: * -> *) x. Config' f -> Rep (Config' f) x
from :: forall x. Config' f -> Rep (Config' f) x
$cto :: forall (f :: * -> *) x. Rep (Config' f) x -> Config' f
to :: forall x. Rep (Config' f) x -> Config' f
Generic)
type NetworkingConfig = NetworkingConfig' Identity
data NetworkingConfig' f = NetworkingConfig
{ forall (f :: * -> *). NetworkingConfig' f -> Field f (Time Second)
ncExternalRefCheckTimeout :: Field f (Time Second)
, forall (f :: * -> *). NetworkingConfig' f -> Field f Bool
ncIgnoreAuthFailures :: Field f Bool
, forall (f :: * -> *). NetworkingConfig' f -> Field f (Time Second)
ncDefaultRetryAfter :: Field f (Time Second)
, forall (f :: * -> *). NetworkingConfig' f -> Field f Int
ncMaxRetries :: Field f Int
, forall (f :: * -> *). NetworkingConfig' f -> Field f Int
ncMaxTimeoutRetries :: Field f Int
, forall (f :: * -> *). NetworkingConfig' f -> Field f Int
ncMaxRedirectFollows :: Field f Int
, forall (f :: * -> *). NetworkingConfig' f -> Field f RedirectConfig
ncExternalRefRedirects :: Field f RedirectConfig
} deriving stock ((forall x. NetworkingConfig' f -> Rep (NetworkingConfig' f) x)
-> (forall x. Rep (NetworkingConfig' f) x -> NetworkingConfig' f)
-> Generic (NetworkingConfig' f)
forall x. Rep (NetworkingConfig' f) x -> NetworkingConfig' f
forall x. NetworkingConfig' f -> Rep (NetworkingConfig' f) x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
forall (f :: * -> *) x.
Rep (NetworkingConfig' f) x -> NetworkingConfig' f
forall (f :: * -> *) x.
NetworkingConfig' f -> Rep (NetworkingConfig' f) x
$cfrom :: forall (f :: * -> *) x.
NetworkingConfig' f -> Rep (NetworkingConfig' f) x
from :: forall x. NetworkingConfig' f -> Rep (NetworkingConfig' f) x
$cto :: forall (f :: * -> *) x.
Rep (NetworkingConfig' f) x -> NetworkingConfig' f
to :: forall x. Rep (NetworkingConfig' f) x -> NetworkingConfig' f
Generic)
type RedirectConfig = [RedirectRule]
type ScannersConfig = ScannersConfig' Identity
data ScannersConfig' f = ScannersConfig
{ forall (f :: * -> *). ScannersConfig' f -> MarkdownConfig
scMarkdown :: MarkdownConfig
, forall (f :: * -> *). ScannersConfig' f -> Field f Double
scAnchorSimilarityThreshold :: Field f Double
} deriving stock ((forall x. ScannersConfig' f -> Rep (ScannersConfig' f) x)
-> (forall x. Rep (ScannersConfig' f) x -> ScannersConfig' f)
-> Generic (ScannersConfig' f)
forall x. Rep (ScannersConfig' f) x -> ScannersConfig' f
forall x. ScannersConfig' f -> Rep (ScannersConfig' f) x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
forall (f :: * -> *) x.
Rep (ScannersConfig' f) x -> ScannersConfig' f
forall (f :: * -> *) x.
ScannersConfig' f -> Rep (ScannersConfig' f) x
$cfrom :: forall (f :: * -> *) x.
ScannersConfig' f -> Rep (ScannersConfig' f) x
from :: forall x. ScannersConfig' f -> Rep (ScannersConfig' f) x
$cto :: forall (f :: * -> *) x.
Rep (ScannersConfig' f) x -> ScannersConfig' f
to :: forall x. Rep (ScannersConfig' f) x -> ScannersConfig' f
Generic)
makeLensesWith postfixFields ''Config'
makeLensesWith postfixFields ''NetworkingConfig'
defConfig :: HasCallStack => Flavor -> Config
defConfig :: HasCallStack => Flavor -> Config
defConfig = (ParseException -> Config)
-> (Config -> Config) -> Either ParseException Config -> Config
forall a c b. (a -> c) -> (b -> c) -> Either a b -> c
either (Text -> Config
forall a. HasCallStack => Text -> a
error (Text -> Config)
-> (ParseException -> Text) -> ParseException -> Config
forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> Text
forall a. ToText a => a -> Text
toText (String -> Text)
-> (ParseException -> String) -> ParseException -> Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ParseException -> String
prettyPrintParseException) Config -> Config
forall a. a -> a
id
(Either ParseException Config -> Config)
-> (Flavor -> Either ParseException Config) -> Flavor -> Config
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ByteString -> Either ParseException Config
forall a. FromJSON a => ByteString -> Either ParseException a
decodeEither'
(ByteString -> Either ParseException Config)
-> (Flavor -> ByteString) -> Flavor -> Either ParseException Config
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> ByteString
forall a b. ConvertUtf8 a b => a -> b
encodeUtf8
(Text -> ByteString) -> (Flavor -> Text) -> Flavor -> ByteString
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Flavor -> Text
defConfigText
overrideConfig :: ConfigOptional -> Config
overrideConfig :: ConfigOptional -> Config
overrideConfig ConfigOptional
config
= Config
{ cExclusions :: Field Identity (ExclusionConfig' Identity)
cExclusions = Field Identity (ExclusionConfig' Identity)
-> (ExclusionConfig' Maybe
-> Field Identity (ExclusionConfig' Identity))
-> Maybe (ExclusionConfig' Maybe)
-> Field Identity (ExclusionConfig' Identity)
forall b a. b -> (a -> b) -> Maybe a -> b
maybe Field Identity (ExclusionConfig' Identity)
defExclusions ExclusionConfig' Maybe
-> Field Identity (ExclusionConfig' Identity)
ExclusionConfig' Maybe -> ExclusionConfig' Identity
overrideExclusions (Maybe (ExclusionConfig' Maybe)
-> Field Identity (ExclusionConfig' Identity))
-> Maybe (ExclusionConfig' Maybe)
-> Field Identity (ExclusionConfig' Identity)
forall a b. (a -> b) -> a -> b
$ ConfigOptional -> Field Maybe (ExclusionConfig' Maybe)
forall (f :: * -> *). Config' f -> Field f (ExclusionConfig' f)
cExclusions ConfigOptional
config
, cNetworking :: Field Identity (NetworkingConfig' Identity)
cNetworking = Field Identity (NetworkingConfig' Identity)
-> (NetworkingConfig' Maybe
-> Field Identity (NetworkingConfig' Identity))
-> Maybe (NetworkingConfig' Maybe)
-> Field Identity (NetworkingConfig' Identity)
forall b a. b -> (a -> b) -> Maybe a -> b
maybe Field Identity (NetworkingConfig' Identity)
NetworkingConfig' Identity
defNetworking NetworkingConfig' Maybe
-> Field Identity (NetworkingConfig' Identity)
NetworkingConfig' Maybe -> NetworkingConfig' Identity
overrideNetworking (Maybe (NetworkingConfig' Maybe)
-> Field Identity (NetworkingConfig' Identity))
-> Maybe (NetworkingConfig' Maybe)
-> Field Identity (NetworkingConfig' Identity)
forall a b. (a -> b) -> a -> b
$ ConfigOptional -> Field Maybe (NetworkingConfig' Maybe)
forall (f :: * -> *). Config' f -> Field f (NetworkingConfig' f)
cNetworking ConfigOptional
config
, cScanners :: ScannersConfig' Identity
cScanners = ScannersConfig
{ scMarkdown :: MarkdownConfig
scMarkdown = Flavor -> MarkdownConfig
MarkdownConfig Flavor
flavor
, scAnchorSimilarityThreshold :: Field Identity Double
scAnchorSimilarityThreshold =
Field Identity Double
-> Maybe (Field Identity Double) -> Field Identity Double
forall a. a -> Maybe a -> a
fromMaybe (ScannersConfig' Identity -> Field Identity Double
forall (f :: * -> *). ScannersConfig' f -> Field f Double
scAnchorSimilarityThreshold ScannersConfig' Identity
defScanners)
(Maybe (Field Identity Double) -> Field Identity Double)
-> Maybe (Field Identity Double) -> Field Identity Double
forall a b. (a -> b) -> a -> b
$ ScannersConfig' Maybe -> Field Maybe Double
forall (f :: * -> *). ScannersConfig' f -> Field f Double
scAnchorSimilarityThreshold (ConfigOptional -> ScannersConfig' Maybe
forall (f :: * -> *). Config' f -> ScannersConfig' f
cScanners ConfigOptional
config)
}
}
where
flavor :: Flavor
flavor = MarkdownConfig -> Flavor
mcFlavor (MarkdownConfig -> Flavor)
-> (ScannersConfig' Maybe -> MarkdownConfig)
-> ScannersConfig' Maybe
-> Flavor
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ScannersConfig' Maybe -> MarkdownConfig
forall (f :: * -> *). ScannersConfig' f -> MarkdownConfig
scMarkdown (ScannersConfig' Maybe -> Flavor)
-> ScannersConfig' Maybe -> Flavor
forall a b. (a -> b) -> a -> b
$ ConfigOptional -> ScannersConfig' Maybe
forall (f :: * -> *). Config' f -> ScannersConfig' f
cScanners ConfigOptional
config
defScanners :: ScannersConfig' Identity
defScanners = Config -> ScannersConfig' Identity
forall (f :: * -> *). Config' f -> ScannersConfig' f
cScanners (Config -> ScannersConfig' Identity)
-> Config -> ScannersConfig' Identity
forall a b. (a -> b) -> a -> b
$ HasCallStack => Flavor -> Config
Flavor -> Config
defConfig Flavor
flavor
defExclusions :: Field Identity (ExclusionConfig' Identity)
defExclusions = Config -> Field Identity (ExclusionConfig' Identity)
forall (f :: * -> *). Config' f -> Field f (ExclusionConfig' f)
cExclusions (Config -> Field Identity (ExclusionConfig' Identity))
-> Config -> Field Identity (ExclusionConfig' Identity)
forall a b. (a -> b) -> a -> b
$ HasCallStack => Flavor -> Config
Flavor -> Config
defConfig Flavor
flavor
defNetworking :: NetworkingConfig' Identity
defNetworking = Config -> Field Identity (NetworkingConfig' Identity)
forall (f :: * -> *). Config' f -> Field f (NetworkingConfig' f)
cNetworking (HasCallStack => Flavor -> Config
Flavor -> Config
defConfig Flavor
flavor)
NetworkingConfig' Identity
-> (NetworkingConfig' Identity -> NetworkingConfig' Identity)
-> NetworkingConfig' Identity
forall a b. a -> (a -> b) -> b
& (RedirectConfig -> Identity RedirectConfig)
-> NetworkingConfig' Identity
-> Identity (NetworkingConfig' Identity)
(Field Identity RedirectConfig
-> Identity (Field Identity RedirectConfig))
-> NetworkingConfig' Identity
-> Identity (NetworkingConfig' Identity)
forall (f :: * -> *) (f :: * -> *).
Functor f =>
(Field f RedirectConfig -> f (Field f RedirectConfig))
-> NetworkingConfig' f -> f (NetworkingConfig' f)
ncExternalRefRedirectsL ((RedirectConfig -> Identity RedirectConfig)
-> NetworkingConfig' Identity
-> Identity (NetworkingConfig' Identity))
-> RedirectConfig
-> NetworkingConfig' Identity
-> NetworkingConfig' Identity
forall s t a b. ASetter s t a b -> b -> s -> t
.~ []
overrideExclusions :: ExclusionConfig' Maybe -> ExclusionConfig' Identity
overrideExclusions ExclusionConfig' Maybe
exclusionConfig
= ExclusionConfig
{ ecIgnore :: Field Identity [CanonicalRelGlobPattern]
ecIgnore = (forall (f :: * -> *).
ExclusionConfig' f
-> Field f (Field Identity [CanonicalRelGlobPattern]))
-> Field Identity [CanonicalRelGlobPattern]
forall a.
(forall (f :: * -> *). ExclusionConfig' f -> Field f a) -> a
overrideField ExclusionConfig' f -> Field f [CanonicalRelGlobPattern]
ExclusionConfig' f
-> Field f (Field Identity [CanonicalRelGlobPattern])
forall (f :: * -> *).
ExclusionConfig' f -> Field f [CanonicalRelGlobPattern]
forall (f :: * -> *).
ExclusionConfig' f
-> Field f (Field Identity [CanonicalRelGlobPattern])
ecIgnore
, ecIgnoreLocalRefsTo :: Field Identity [CanonicalRelGlobPattern]
ecIgnoreLocalRefsTo = (forall (f :: * -> *).
ExclusionConfig' f
-> Field f (Field Identity [CanonicalRelGlobPattern]))
-> Field Identity [CanonicalRelGlobPattern]
forall a.
(forall (f :: * -> *). ExclusionConfig' f -> Field f a) -> a
overrideField ExclusionConfig' f -> Field f [CanonicalRelGlobPattern]
ExclusionConfig' f
-> Field f (Field Identity [CanonicalRelGlobPattern])
forall (f :: * -> *).
ExclusionConfig' f -> Field f [CanonicalRelGlobPattern]
forall (f :: * -> *).
ExclusionConfig' f
-> Field f (Field Identity [CanonicalRelGlobPattern])
ecIgnoreLocalRefsTo
, ecIgnoreRefsFrom :: Field Identity [CanonicalRelGlobPattern]
ecIgnoreRefsFrom = (forall (f :: * -> *).
ExclusionConfig' f
-> Field f (Field Identity [CanonicalRelGlobPattern]))
-> Field Identity [CanonicalRelGlobPattern]
forall a.
(forall (f :: * -> *). ExclusionConfig' f -> Field f a) -> a
overrideField ExclusionConfig' f -> Field f [CanonicalRelGlobPattern]
ExclusionConfig' f
-> Field f (Field Identity [CanonicalRelGlobPattern])
forall (f :: * -> *).
ExclusionConfig' f -> Field f [CanonicalRelGlobPattern]
forall (f :: * -> *).
ExclusionConfig' f
-> Field f (Field Identity [CanonicalRelGlobPattern])
ecIgnoreRefsFrom
, ecIgnoreExternalRefsTo :: Field Identity [Regex]
ecIgnoreExternalRefsTo = (forall (f :: * -> *).
ExclusionConfig' f -> Field f (Field Identity [Regex]))
-> Field Identity [Regex]
forall a.
(forall (f :: * -> *). ExclusionConfig' f -> Field f a) -> a
overrideField ExclusionConfig' f -> Field f [Regex]
ExclusionConfig' f -> Field f (Field Identity [Regex])
forall (f :: * -> *). ExclusionConfig' f -> Field f [Regex]
forall (f :: * -> *).
ExclusionConfig' f -> Field f (Field Identity [Regex])
ecIgnoreExternalRefsTo
}
where
overrideField :: (forall f. ExclusionConfig' f -> Field f a) -> a
overrideField :: forall a.
(forall (f :: * -> *). ExclusionConfig' f -> Field f a) -> a
overrideField forall (f :: * -> *). ExclusionConfig' f -> Field f a
field = a -> Maybe a -> a
forall a. a -> Maybe a -> a
fromMaybe (ExclusionConfig' Identity -> Field Identity a
forall (f :: * -> *). ExclusionConfig' f -> Field f a
field Field Identity (ExclusionConfig' Identity)
ExclusionConfig' Identity
defExclusions) (Maybe a -> a) -> Maybe a -> a
forall a b. (a -> b) -> a -> b
$ ExclusionConfig' Maybe -> Field Maybe a
forall (f :: * -> *). ExclusionConfig' f -> Field f a
field ExclusionConfig' Maybe
exclusionConfig
overrideNetworking :: NetworkingConfig' Maybe -> NetworkingConfig' Identity
overrideNetworking NetworkingConfig' Maybe
networkingConfig
= NetworkingConfig
{ ncExternalRefCheckTimeout :: Field Identity (Time Second)
ncExternalRefCheckTimeout = (forall (f :: * -> *).
NetworkingConfig' f -> Field f (Field Identity (Time (1 :% 1))))
-> Field Identity (Time (1 :% 1))
forall a.
(forall (f :: * -> *). NetworkingConfig' f -> Field f a) -> a
overrideField NetworkingConfig' f -> Field f (Time Second)
NetworkingConfig' f -> Field f (Field Identity (Time (1 :% 1)))
forall (f :: * -> *). NetworkingConfig' f -> Field f (Time Second)
forall (f :: * -> *).
NetworkingConfig' f -> Field f (Field Identity (Time (1 :% 1)))
ncExternalRefCheckTimeout
, ncIgnoreAuthFailures :: Field Identity Bool
ncIgnoreAuthFailures = (forall (f :: * -> *).
NetworkingConfig' f -> Field f (Field Identity Bool))
-> Field Identity Bool
forall a.
(forall (f :: * -> *). NetworkingConfig' f -> Field f a) -> a
overrideField NetworkingConfig' f -> Field f Bool
NetworkingConfig' f -> Field f (Field Identity Bool)
forall (f :: * -> *). NetworkingConfig' f -> Field f Bool
forall (f :: * -> *).
NetworkingConfig' f -> Field f (Field Identity Bool)
ncIgnoreAuthFailures
, ncDefaultRetryAfter :: Field Identity (Time Second)
ncDefaultRetryAfter = (forall (f :: * -> *).
NetworkingConfig' f -> Field f (Field Identity (Time (1 :% 1))))
-> Field Identity (Time (1 :% 1))
forall a.
(forall (f :: * -> *). NetworkingConfig' f -> Field f a) -> a
overrideField NetworkingConfig' f -> Field f (Time Second)
NetworkingConfig' f -> Field f (Field Identity (Time (1 :% 1)))
forall (f :: * -> *). NetworkingConfig' f -> Field f (Time Second)
forall (f :: * -> *).
NetworkingConfig' f -> Field f (Field Identity (Time (1 :% 1)))
ncDefaultRetryAfter
, ncMaxRetries :: Field Identity Int
ncMaxRetries = (forall (f :: * -> *).
NetworkingConfig' f -> Field f (Field Identity Int))
-> Field Identity Int
forall a.
(forall (f :: * -> *). NetworkingConfig' f -> Field f a) -> a
overrideField NetworkingConfig' f -> Field f Int
NetworkingConfig' f -> Field f (Field Identity Int)
forall (f :: * -> *). NetworkingConfig' f -> Field f Int
forall (f :: * -> *).
NetworkingConfig' f -> Field f (Field Identity Int)
ncMaxRetries
, ncMaxTimeoutRetries :: Field Identity Int
ncMaxTimeoutRetries = (forall (f :: * -> *).
NetworkingConfig' f -> Field f (Field Identity Int))
-> Field Identity Int
forall a.
(forall (f :: * -> *). NetworkingConfig' f -> Field f a) -> a
overrideField NetworkingConfig' f -> Field f Int
NetworkingConfig' f -> Field f (Field Identity Int)
forall (f :: * -> *). NetworkingConfig' f -> Field f Int
forall (f :: * -> *).
NetworkingConfig' f -> Field f (Field Identity Int)
ncMaxTimeoutRetries
, ncMaxRedirectFollows :: Field Identity Int
ncMaxRedirectFollows = (forall (f :: * -> *).
NetworkingConfig' f -> Field f (Field Identity Int))
-> Field Identity Int
forall a.
(forall (f :: * -> *). NetworkingConfig' f -> Field f a) -> a
overrideField NetworkingConfig' f -> Field f Int
NetworkingConfig' f -> Field f (Field Identity Int)
forall (f :: * -> *). NetworkingConfig' f -> Field f Int
forall (f :: * -> *).
NetworkingConfig' f -> Field f (Field Identity Int)
ncMaxRedirectFollows
, ncExternalRefRedirects :: Field Identity RedirectConfig
ncExternalRefRedirects = (forall (f :: * -> *).
NetworkingConfig' f -> Field f (Field Identity RedirectConfig))
-> Field Identity RedirectConfig
forall a.
(forall (f :: * -> *). NetworkingConfig' f -> Field f a) -> a
overrideField NetworkingConfig' f -> Field f RedirectConfig
NetworkingConfig' f -> Field f (Field Identity RedirectConfig)
forall (f :: * -> *). NetworkingConfig' f -> Field f RedirectConfig
forall (f :: * -> *).
NetworkingConfig' f -> Field f (Field Identity RedirectConfig)
ncExternalRefRedirects
}
where
overrideField :: (forall f. NetworkingConfig' f -> Field f a) -> a
overrideField :: forall a.
(forall (f :: * -> *). NetworkingConfig' f -> Field f a) -> a
overrideField forall (f :: * -> *). NetworkingConfig' f -> Field f a
field = a -> Maybe a -> a
forall a. a -> Maybe a -> a
fromMaybe (NetworkingConfig' Identity -> Field Identity a
forall (f :: * -> *). NetworkingConfig' f -> Field f a
field NetworkingConfig' Identity
defNetworking) (Maybe a -> a) -> Maybe a -> a
forall a b. (a -> b) -> a -> b
$ NetworkingConfig' Maybe -> Field Maybe a
forall (f :: * -> *). NetworkingConfig' f -> Field f a
field NetworkingConfig' Maybe
networkingConfig
instance KnownRatName unit => FromJSON (Time unit) where
parseJSON :: Value -> Parser (Time unit)
parseJSON = String
-> (Text -> Parser (Time unit)) -> Value -> Parser (Time unit)
forall a. String -> (Text -> Parser a) -> Value -> Parser a
withText String
"time" ((Text -> Parser (Time unit)) -> Value -> Parser (Time unit))
-> (Text -> Parser (Time unit)) -> Value -> Parser (Time unit)
forall a b. (a -> b) -> a -> b
$
Parser (Time unit)
-> (Time unit -> Parser (Time unit))
-> Maybe (Time unit)
-> Parser (Time unit)
forall b a. b -> (a -> b) -> Maybe a -> b
maybe (String -> Parser (Time unit)
forall a. String -> Parser a
forall (m :: * -> *) a. MonadFail m => String -> m a
fail String
"Unknown time") Time unit -> Parser (Time unit)
forall a. a -> Parser a
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Maybe (Time unit) -> Parser (Time unit))
-> (Text -> Maybe (Time unit)) -> Text -> Parser (Time unit)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> Maybe (Time unit)
forall (unit :: Rat).
KnownRatName unit =>
String -> Maybe (Time unit)
unitsP (String -> Maybe (Time unit))
-> (Text -> String) -> Text -> Maybe (Time unit)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> String
forall a. ToString a => a -> String
toString
instance FromJSON (ConfigOptional) where
parseJSON :: Value -> Parser ConfigOptional
parseJSON = Options -> Value -> Parser ConfigOptional
forall a.
(Generic a, GFromJSON Zero (Rep a)) =>
Options -> Value -> Parser a
genericParseJSON Options
aesonConfigOption
instance FromJSON (Config) where
parseJSON :: Value -> Parser Config
parseJSON = Options -> Value -> Parser Config
forall a.
(Generic a, GFromJSON Zero (Rep a)) =>
Options -> Value -> Parser a
genericParseJSON Options
aesonConfigOption
instance FromJSON (NetworkingConfig' Maybe) where
parseJSON :: Value -> Parser (NetworkingConfig' Maybe)
parseJSON = Options -> Value -> Parser (NetworkingConfig' Maybe)
forall a.
(Generic a, GFromJSON Zero (Rep a)) =>
Options -> Value -> Parser a
genericParseJSON Options
aesonConfigOption
instance FromJSON (NetworkingConfig) where
parseJSON :: Value -> Parser (NetworkingConfig' Identity)
parseJSON = Options -> Value -> Parser (NetworkingConfig' Identity)
forall a.
(Generic a, GFromJSON Zero (Rep a)) =>
Options -> Value -> Parser a
genericParseJSON Options
aesonConfigOption
instance FromJSON (ScannersConfig) where
parseJSON :: Value -> Parser (ScannersConfig' Identity)
parseJSON = Options -> Value -> Parser (ScannersConfig' Identity)
forall a.
(Generic a, GFromJSON Zero (Rep a)) =>
Options -> Value -> Parser a
genericParseJSON Options
aesonConfigOption
instance FromJSON (ScannersConfig' Maybe) where
parseJSON :: Value -> Parser (ScannersConfig' Maybe)
parseJSON = Options -> Value -> Parser (ScannersConfig' Maybe)
forall a.
(Generic a, GFromJSON Zero (Rep a)) =>
Options -> Value -> Parser a
genericParseJSON Options
aesonConfigOption