xrefcheck-0.3.0
Safe HaskellSafe-Inferred
LanguageHaskell2010

Xrefcheck.Config

Synopsis

Documentation

type Config = Config' Identity Source #

Type alias for Config' with all required fields.

type NetworkingConfig = NetworkingConfig' Identity Source #

Type alias for NetworkingConfig' with all required fields.

data NetworkingConfig' f Source #

Config of networking.

Constructors

NetworkingConfig 

Fields

  • ncExternalRefCheckTimeout :: Field f (Time Second)

    When checking external references, how long to wait on request before declaring "Response timeout".

  • ncIgnoreAuthFailures :: Field f Bool

    If True - links which return 403 or 401 code will be skipped, otherwise – will be marked as broken, because we can't check it.

  • ncDefaultRetryAfter :: Field f (Time Second)

    Default Retry-After delay, applicable when we receive a 429 response and it does not contain a Retry-After header.

  • ncMaxRetries :: Field f Int

    How many attempts to retry an external link after getting a "429 Too Many Requests" response. Timeouts may also be accounted here, see the description of maxTimeoutRetries field.

    If a site once responded with 429 error code, subsequent request timeouts will also be treated as hitting the site's rate limiter and result in retry attempts, unless the maximum retries number has been reached.

    On other errors xrefcheck fails immediately, without retrying.

  • ncMaxTimeoutRetries :: Field f Int

    Querying a given domain that ever returned 429 before, this defines how many timeouts are allowed during retries.

    For such domains, timeouts likely mean hitting the rate limiter, and so xrefcheck considers timeouts in the same way as 429 errors.

    For other domains, a timeout results in a respective error, no retry attempts will be performed. Use externalRefCheckTimeout option to increase the time after which timeout is declared.

    This option is similar to maxRetries, the difference is that this maxTimeoutRetries option limits only the number of retries caused by timeouts, and maxRetries limits the number of retries caused both by 429s and timeouts.

  • ncMaxRedirectFollows :: Field f Int

    Maximum number of links that can be followed in a single redirect chain.

  • ncExternalRefRedirects :: Field f RedirectConfig

    Rules to override the redirect behavior for external references.

Instances

Instances details
FromJSON NetworkingConfig Source # 
Instance details

Defined in Xrefcheck.Config

FromJSON (NetworkingConfig' Maybe) Source # 
Instance details

Defined in Xrefcheck.Config

Generic (NetworkingConfig' f) Source # 
Instance details

Defined in Xrefcheck.Config

Associated Types

type Rep (NetworkingConfig' f) :: Type -> Type #

type Rep (NetworkingConfig' f) Source # 
Instance details

Defined in Xrefcheck.Config

type Rep (NetworkingConfig' f) = D1 ('MetaData "NetworkingConfig'" "Xrefcheck.Config" "xrefcheck-0.3.0-GeqFdwqv2mJ31qwgW3PUq5" 'False) (C1 ('MetaCons "NetworkingConfig" 'PrefixI 'True) ((S1 ('MetaSel ('Just "ncExternalRefCheckTimeout") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Field f (Time Second))) :*: (S1 ('MetaSel ('Just "ncIgnoreAuthFailures") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Field f Bool)) :*: S1 ('MetaSel ('Just "ncDefaultRetryAfter") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Field f (Time Second))))) :*: ((S1 ('MetaSel ('Just "ncMaxRetries") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Field f Int)) :*: S1 ('MetaSel ('Just "ncMaxTimeoutRetries") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Field f Int))) :*: (S1 ('MetaSel ('Just "ncMaxRedirectFollows") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Field f Int)) :*: S1 ('MetaSel ('Just "ncExternalRefRedirects") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Field f RedirectConfig))))))

data Config' f Source #

Overall config.

Instances

Instances details
FromJSON Config Source # 
Instance details

Defined in Xrefcheck.Config

FromJSON ConfigOptional Source # 
Instance details

Defined in Xrefcheck.Config

Generic (Config' f) Source # 
Instance details

Defined in Xrefcheck.Config

Associated Types

type Rep (Config' f) :: Type -> Type #

Methods

from :: Config' f -> Rep (Config' f) x #

to :: Rep (Config' f) x -> Config' f #

type Rep (Config' f) Source # 
Instance details

Defined in Xrefcheck.Config

type Rep (Config' f) = D1 ('MetaData "Config'" "Xrefcheck.Config" "xrefcheck-0.3.0-GeqFdwqv2mJ31qwgW3PUq5" 'False) (C1 ('MetaCons "Config" 'PrefixI 'True) (S1 ('MetaSel ('Just "cExclusions") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Field f (ExclusionConfig' f))) :*: (S1 ('MetaSel ('Just "cNetworking") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Field f (NetworkingConfig' f))) :*: S1 ('MetaSel ('Just "cScanners") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (ScannersConfig' f)))))

type ScannersConfig = ScannersConfig' Identity Source #

Type alias for ScannersConfig' with all required fields.

data ScannersConfig' f Source #

Configs for all the supported scanners.

Constructors

ScannersConfig 

Fields

Instances

Instances details
FromJSON ScannersConfig Source # 
Instance details

Defined in Xrefcheck.Config

FromJSON (ScannersConfig' Maybe) Source # 
Instance details

Defined in Xrefcheck.Config

Generic (ScannersConfig' f) Source # 
Instance details

Defined in Xrefcheck.Config

Associated Types

type Rep (ScannersConfig' f) :: Type -> Type #

type Rep (ScannersConfig' f) Source # 
Instance details

Defined in Xrefcheck.Config

type Rep (ScannersConfig' f) = D1 ('MetaData "ScannersConfig'" "Xrefcheck.Config" "xrefcheck-0.3.0-GeqFdwqv2mJ31qwgW3PUq5" 'False) (C1 ('MetaCons "ScannersConfig" 'PrefixI 'True) (S1 ('MetaSel ('Just "scMarkdown") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 MarkdownConfig) :*: S1 ('MetaSel ('Just "scAnchorSimilarityThreshold") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Field f Double))))

type ConfigOptional = Config' Maybe Source #

Type alias for Config' with optional fields.

type RedirectConfig = [RedirectRule] Source #

A list of custom redirect rules.

overrideConfig :: ConfigOptional -> Config Source #

Override missed fields with default values.

Orphan instances

KnownRatName unit => FromJSON (Time unit) Source # 
Instance details

Methods

parseJSON :: Value -> Parser (Time unit) #

parseJSONList :: Value -> Parser [Time unit] #

omittedField :: Maybe (Time unit) #