| Safe Haskell | Safe-Inferred |
|---|---|
| Language | Haskell2010 |
Xrefcheck.Verify
Synopsis
- newtype VerifyResult e = VerifyResult [e]
- verifyErrors :: VerifyResult e -> Maybe (NonEmpty e)
- verifying :: Monad m => ExceptT e m () -> m (VerifyResult e)
- data RetryAfter
- data WithReferenceLoc a = WithReferenceLoc {
- wrlFile :: RelPosixLink
- wrlReference :: Reference
- wrlItem :: a
- data NeedsCaching key
- = NoCaching
- | CacheUnderKey key
- forConcurrentlyCaching :: forall a b cacheKey. Ord cacheKey => [a] -> (a -> NeedsCaching cacheKey) -> (a -> IO b) -> IO (Either (AsyncException, [b]) [b])
- newtype DomainName = DomainName {
- unDomainName :: Text
- data VerifyError
- = LocalFileDoesNotExist RelPosixLink
- | LocalFileOutsideRepo RelPosixLink
- | LinkTargetNotAddedToGit RelPosixLink
- | AnchorDoesNotExist Text [Anchor]
- | AmbiguousAnchorRef RelPosixLink Text (NonEmpty Anchor)
- | ExternalResourceUriParseError UriParseError
- | ExternalResourceInvalidUrl (Maybe Text)
- | ExternalResourceUnknownProtocol
- | ExternalHttpResourceUnavailable Status
- | ExternalHttpTooManyRequests (Maybe RetryAfter) (Maybe DomainName)
- | ExternalHttpTimeout (Maybe DomainName)
- | ExternalFtpResourceUnavailable FTPResponse
- | ExternalFtpException FTPException
- | FtpEntryDoesNotExist FilePath
- | ExternalResourceSomeError Text
- | ExternalResourceConnectionFailure
- | RedirectChainCycle RedirectChain
- | RedirectMissingLocation RedirectChain
- | RedirectChainLimit RedirectChain
- | RedirectRuleError RedirectChain (Maybe RedirectRuleOn)
- verifyRepo :: Given ColorMode => Rewrite -> Config -> VerifyMode -> RepoInfo -> IO (VerifyResult $ WithReferenceLoc VerifyError)
- verifyReference :: Config -> VerifyMode -> IORef (Set DomainName) -> IORef VerifyProgress -> RepoInfo -> RelPosixLink -> Reference -> IO (VerifyResult $ WithReferenceLoc VerifyError)
- checkExternalResource :: RedirectChain -> Config -> Text -> ExceptT VerifyError IO ()
- reportVerifyErrs :: Given ColorMode => NonEmpty (WithReferenceLoc VerifyError) -> IO ()
General verification
newtype VerifyResult e Source #
Constructors
| VerifyResult [e] |
Instances
| Functor VerifyResult Source # | |
Defined in Xrefcheck.Verify Methods fmap :: (a -> b) -> VerifyResult a -> VerifyResult b # (<$) :: a -> VerifyResult b -> VerifyResult a # | |
| Monoid (VerifyResult e) Source # | |
Defined in Xrefcheck.Verify Methods mempty :: VerifyResult e # mappend :: VerifyResult e -> VerifyResult e -> VerifyResult e # mconcat :: [VerifyResult e] -> VerifyResult e # | |
| Semigroup (VerifyResult e) Source # | |
Defined in Xrefcheck.Verify Methods (<>) :: VerifyResult e -> VerifyResult e -> VerifyResult e # sconcat :: NonEmpty (VerifyResult e) -> VerifyResult e # stimes :: Integral b => b -> VerifyResult e -> VerifyResult e # | |
| Show e => Show (VerifyResult e) Source # | |
Defined in Xrefcheck.Verify Methods showsPrec :: Int -> VerifyResult e -> ShowS # show :: VerifyResult e -> String # showList :: [VerifyResult e] -> ShowS # | |
| Eq e => Eq (VerifyResult e) Source # | |
Defined in Xrefcheck.Verify Methods (==) :: VerifyResult e -> VerifyResult e -> Bool # (/=) :: VerifyResult e -> VerifyResult e -> Bool # | |
verifyErrors :: VerifyResult e -> Maybe (NonEmpty e) Source #
data RetryAfter Source #
Instances
| Read RetryAfter Source # | |
Defined in Xrefcheck.Verify Methods readsPrec :: Int -> ReadS RetryAfter # readList :: ReadS [RetryAfter] # readPrec :: ReadPrec RetryAfter # readListPrec :: ReadPrec [RetryAfter] # | |
| Show RetryAfter Source # | |
Defined in Xrefcheck.Verify Methods showsPrec :: Int -> RetryAfter -> ShowS # show :: RetryAfter -> String # showList :: [RetryAfter] -> ShowS # | |
| Buildable RetryAfter Source # | |
Defined in Xrefcheck.Verify Methods build :: RetryAfter -> Builder # | |
| Eq RetryAfter Source # | |
Defined in Xrefcheck.Verify | |
data WithReferenceLoc a Source #
Constructors
| WithReferenceLoc | |
Fields
| |
Concurrent traversal with caching
data NeedsCaching key Source #
Constructors
| NoCaching | |
| CacheUnderKey key |
forConcurrentlyCaching :: forall a b cacheKey. Ord cacheKey => [a] -> (a -> NeedsCaching cacheKey) -> (a -> IO b) -> IO (Either (AsyncException, [b]) [b]) Source #
Perform concurrent traversal of the list with the caching mechanism.
The function is semantically similar to Control.Concurrent.Async.forConcurrently;
each asynchronous result of the action is prepended to the accumulator list [Async b].
Additionally, these action results may also be inserted in a map of the type
Map cacheKey (Async b), depending on the return value of the function
a -> NeedsCaching cacheKey applied to each of the element from the given list.
If an element of the type a needs caching, and the value is already present in the map,
then the action will not be executed, and the value is added to the accumulator list.
After the whole list has been traversed, the accumulator is traversed once again to ensure
every asynchronous action is completed.
If interrupted by AsyncException, returns this exception and list of already calcualted results
(their subset can be arbitrary). Computations that were not ended till this moment are cancelled.
Cross-references validation
newtype DomainName Source #
Contains a name of a domain, examples:
DomainName "github.com",
DomainName "localhost",
DomainName "192.168.0.104"
Constructors
| DomainName | |
Fields
| |
Instances
| Show DomainName Source # | |
Defined in Xrefcheck.Verify Methods showsPrec :: Int -> DomainName -> ShowS # show :: DomainName -> String # showList :: [DomainName] -> ShowS # | |
| Eq DomainName Source # | |
Defined in Xrefcheck.Verify | |
| Ord DomainName Source # | |
Defined in Xrefcheck.Verify Methods compare :: DomainName -> DomainName -> Ordering # (<) :: DomainName -> DomainName -> Bool # (<=) :: DomainName -> DomainName -> Bool # (>) :: DomainName -> DomainName -> Bool # (>=) :: DomainName -> DomainName -> Bool # max :: DomainName -> DomainName -> DomainName # min :: DomainName -> DomainName -> DomainName # | |
data VerifyError Source #
Constructors
Instances
| Show VerifyError Source # | |
Defined in Xrefcheck.Verify Methods showsPrec :: Int -> VerifyError -> ShowS # show :: VerifyError -> String # showList :: [VerifyError] -> ShowS # | |
| Eq VerifyError Source # | |
Defined in Xrefcheck.Verify | |
verifyRepo :: Given ColorMode => Rewrite -> Config -> VerifyMode -> RepoInfo -> IO (VerifyResult $ WithReferenceLoc VerifyError) Source #
verifyReference :: Config -> VerifyMode -> IORef (Set DomainName) -> IORef VerifyProgress -> RepoInfo -> RelPosixLink -> Reference -> IO (VerifyResult $ WithReferenceLoc VerifyError) Source #
checkExternalResource :: RedirectChain -> Config -> Text -> ExceptT VerifyError IO () Source #
reportVerifyErrs :: Given ColorMode => NonEmpty (WithReferenceLoc VerifyError) -> IO () Source #