Safe Haskell | Safe-Inferred |
---|---|
Language | Haskell2010 |
Xrefcheck.Core
Description
Various primitives.
Synopsis
- data Flavor
- allFlavors :: [Flavor]
- caseInsensitiveAnchors :: Flavor -> Bool
- newtype Position = Position Text
- data Reference = Reference {}
- data ReferenceInfo
- data ReferenceInfoFile = ReferenceInfoFile {}
- data ExternalLink
- data FileLink
- _RIFile :: Prism' ReferenceInfo ReferenceInfoFile
- _RIExternal :: Prism' ReferenceInfo ExternalLink
- _ELOther :: Prism' ExternalLink Text
- _ELUrl :: Prism' ExternalLink Text
- pattern PathSep :: Char
- referenceInfo :: Text -> ReferenceInfo
- data AnchorType
- data Anchor = Anchor {}
- data FileInfoDiff = FileInfoDiff {}
- fidReferences :: Lens' FileInfoDiff (DList Reference)
- fidAnchors :: Lens' FileInfoDiff (DList Anchor)
- diffToFileInfo :: FileInfoDiff -> FileInfo
- data FileInfo = FileInfo {
- _fiReferences :: [Reference]
- _fiAnchors :: [Anchor]
- fiReferences :: Lens' FileInfo [Reference]
- fiAnchors :: Lens' FileInfo [Anchor]
- data ScanPolicy
- data FileStatus
- data DirectoryStatus
- data RepoInfo = RepoInfo {}
- lookupFile :: CanonicalRelPosixLink -> RepoInfo -> Maybe FileStatus
- lookupDirectory :: CanonicalRelPosixLink -> RepoInfo -> Maybe DirectoryStatus
- data VerifyMode
- shouldCheckLocal :: VerifyMode -> Bool
- shouldCheckExternal :: VerifyMode -> Bool
- headerToAnchor :: Flavor -> Text -> Text
- stripAnchorDupNo :: Text -> Maybe Text
- data VerifyProgress = VerifyProgress {}
- initVerifyProgress :: [Reference] -> VerifyProgress
- showAnalyseProgress :: Given ColorMode => VerifyMode -> Time Second -> VerifyProgress -> Text
- reprintAnalyseProgress :: Given ColorMode => Rewrite -> VerifyMode -> Time Second -> VerifyProgress -> IO ()
Documentation
Markdown flavor.
Unfortunatelly, CMark renderers used on different sites slightly differ, we have to account for that.
allFlavors :: [Flavor] Source #
caseInsensitiveAnchors :: Flavor -> Bool Source #
Whether anchors are case-sensitive for a given Markdown flavour or not.
Description of element position in source file. We keep this in text because scanners for different formats use different representation of this thing, and it actually appears in reports only.
Full info about a reference.
Constructors
Reference | |
Instances
Generic Reference Source # | |
Show Reference Source # | |
NFData Reference Source # | |
Defined in Xrefcheck.Core | |
Given ColorMode => Buildable Reference Source # | |
Defined in Xrefcheck.Core | |
type Rep Reference Source # | |
Defined in Xrefcheck.Core type Rep Reference = D1 ('MetaData "Reference" "Xrefcheck.Core" "xrefcheck-0.3.0-GeqFdwqv2mJ31qwgW3PUq5" 'False) (C1 ('MetaCons "Reference" 'PrefixI 'True) (S1 ('MetaSel ('Just "rName") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text) :*: (S1 ('MetaSel ('Just "rPos") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Position) :*: S1 ('MetaSel ('Just "rInfo") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 ReferenceInfo)))) |
data ReferenceInfo Source #
Info about the reference.
Constructors
RIExternal ExternalLink | |
RIFile ReferenceInfoFile |
Instances
Generic ReferenceInfo Source # | |
Defined in Xrefcheck.Core Associated Types type Rep ReferenceInfo :: Type -> Type # | |
Show ReferenceInfo Source # | |
Defined in Xrefcheck.Core Methods showsPrec :: Int -> ReferenceInfo -> ShowS # show :: ReferenceInfo -> String # showList :: [ReferenceInfo] -> ShowS # | |
NFData ReferenceInfo Source # | |
Defined in Xrefcheck.Core Methods rnf :: ReferenceInfo -> () # | |
type Rep ReferenceInfo Source # | |
Defined in Xrefcheck.Core type Rep ReferenceInfo = D1 ('MetaData "ReferenceInfo" "Xrefcheck.Core" "xrefcheck-0.3.0-GeqFdwqv2mJ31qwgW3PUq5" 'False) (C1 ('MetaCons "RIExternal" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 ExternalLink)) :+: C1 ('MetaCons "RIFile" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 ReferenceInfoFile))) |
data ReferenceInfoFile Source #
Constructors
ReferenceInfoFile | |
Instances
Generic ReferenceInfoFile Source # | |
Defined in Xrefcheck.Core Associated Types type Rep ReferenceInfoFile :: Type -> Type # Methods from :: ReferenceInfoFile -> Rep ReferenceInfoFile x # to :: Rep ReferenceInfoFile x -> ReferenceInfoFile # | |
Show ReferenceInfoFile Source # | |
Defined in Xrefcheck.Core Methods showsPrec :: Int -> ReferenceInfoFile -> ShowS # show :: ReferenceInfoFile -> String # showList :: [ReferenceInfoFile] -> ShowS # | |
NFData ReferenceInfoFile Source # | |
Defined in Xrefcheck.Core Methods rnf :: ReferenceInfoFile -> () # | |
type Rep ReferenceInfoFile Source # | |
Defined in Xrefcheck.Core type Rep ReferenceInfoFile = D1 ('MetaData "ReferenceInfoFile" "Xrefcheck.Core" "xrefcheck-0.3.0-GeqFdwqv2mJ31qwgW3PUq5" 'False) (C1 ('MetaCons "ReferenceInfoFile" 'PrefixI 'True) (S1 ('MetaSel ('Just "rifAnchor") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Text)) :*: S1 ('MetaSel ('Just "rifLink") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 FileLink))) |
data ExternalLink Source #
Constructors
ELUrl Text | Reference to a file at outer site, e.g |
ELOther Text | Entry not to be processed, e.g. |
Instances
Generic ExternalLink Source # | |
Defined in Xrefcheck.Core Associated Types type Rep ExternalLink :: Type -> Type # | |
Show ExternalLink Source # | |
Defined in Xrefcheck.Core Methods showsPrec :: Int -> ExternalLink -> ShowS # show :: ExternalLink -> String # showList :: [ExternalLink] -> ShowS # | |
NFData ExternalLink Source # | |
Defined in Xrefcheck.Core Methods rnf :: ExternalLink -> () # | |
type Rep ExternalLink Source # | |
Defined in Xrefcheck.Core type Rep ExternalLink = D1 ('MetaData "ExternalLink" "Xrefcheck.Core" "xrefcheck-0.3.0-GeqFdwqv2mJ31qwgW3PUq5" 'False) (C1 ('MetaCons "ELUrl" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text)) :+: C1 ('MetaCons "ELOther" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text))) |
Constructors
FLAbsolute RelPosixLink | Reference to a file or directory relative to the repository root. |
FLRelative RelPosixLink | Reference to a file or directory relative to the given one. |
FLLocal | Reference to this file. |
Instances
Generic FileLink Source # | |
Show FileLink Source # | |
NFData FileLink Source # | |
Defined in Xrefcheck.Core | |
type Rep FileLink Source # | |
Defined in Xrefcheck.Core type Rep FileLink = D1 ('MetaData "FileLink" "Xrefcheck.Core" "xrefcheck-0.3.0-GeqFdwqv2mJ31qwgW3PUq5" 'False) (C1 ('MetaCons "FLAbsolute" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 RelPosixLink)) :+: (C1 ('MetaCons "FLRelative" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 RelPosixLink)) :+: C1 ('MetaCons "FLLocal" 'PrefixI 'False) (U1 :: Type -> Type))) |
referenceInfo :: Text -> ReferenceInfo Source #
Compute the ReferenceInfo
corresponding to a given link.
data AnchorType Source #
Context of anchor.
Constructors
HeaderAnchor Int | Every section header is usually an anchor |
HandAnchor | They can be set up manually |
BiblioAnchor | Id of entry in bibliography |
Instances
Generic AnchorType Source # | |
Defined in Xrefcheck.Core Associated Types type Rep AnchorType :: Type -> Type # | |
Show AnchorType Source # | |
Defined in Xrefcheck.Core Methods showsPrec :: Int -> AnchorType -> ShowS # show :: AnchorType -> String # showList :: [AnchorType] -> ShowS # | |
NFData AnchorType Source # | |
Defined in Xrefcheck.Core Methods rnf :: AnchorType -> () # | |
Given ColorMode => Buildable AnchorType Source # | |
Defined in Xrefcheck.Core Methods build :: AnchorType -> Builder # | |
Eq AnchorType Source # | |
Defined in Xrefcheck.Core | |
type Rep AnchorType Source # | |
Defined in Xrefcheck.Core type Rep AnchorType = D1 ('MetaData "AnchorType" "Xrefcheck.Core" "xrefcheck-0.3.0-GeqFdwqv2mJ31qwgW3PUq5" 'False) (C1 ('MetaCons "HeaderAnchor" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Int)) :+: (C1 ('MetaCons "HandAnchor" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "BiblioAnchor" 'PrefixI 'False) (U1 :: Type -> Type))) |
A referable anchor.
Instances
Generic Anchor Source # | |
Show Anchor Source # | |
NFData Anchor Source # | |
Defined in Xrefcheck.Core | |
Given ColorMode => Buildable Anchor Source # | |
Defined in Xrefcheck.Core | |
Eq Anchor Source # | |
type Rep Anchor Source # | |
Defined in Xrefcheck.Core type Rep Anchor = D1 ('MetaData "Anchor" "Xrefcheck.Core" "xrefcheck-0.3.0-GeqFdwqv2mJ31qwgW3PUq5" 'False) (C1 ('MetaCons "Anchor" 'PrefixI 'True) (S1 ('MetaSel ('Just "aType") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 AnchorType) :*: (S1 ('MetaSel ('Just "aName") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text) :*: S1 ('MetaSel ('Just "aPos") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Position)))) |
data FileInfoDiff Source #
Constructors
FileInfoDiff | |
Fields |
Instances
Monoid FileInfoDiff Source # | |
Defined in Xrefcheck.Core Methods mempty :: FileInfoDiff # mappend :: FileInfoDiff -> FileInfoDiff -> FileInfoDiff # mconcat :: [FileInfoDiff] -> FileInfoDiff # | |
Semigroup FileInfoDiff Source # | |
Defined in Xrefcheck.Core Methods (<>) :: FileInfoDiff -> FileInfoDiff -> FileInfoDiff # sconcat :: NonEmpty FileInfoDiff -> FileInfoDiff # stimes :: Integral b => b -> FileInfoDiff -> FileInfoDiff # |
All information regarding a single file we care about.
Constructors
FileInfo | |
Fields
|
Instances
Generic FileInfo Source # | |
Show FileInfo Source # | |
NFData FileInfo Source # | |
Defined in Xrefcheck.Core | |
Given ColorMode => Buildable FileInfo Source # | |
Defined in Xrefcheck.Core | |
type Rep FileInfo Source # | |
Defined in Xrefcheck.Core type Rep FileInfo = D1 ('MetaData "FileInfo" "Xrefcheck.Core" "xrefcheck-0.3.0-GeqFdwqv2mJ31qwgW3PUq5" 'False) (C1 ('MetaCons "FileInfo" 'PrefixI 'True) (S1 ('MetaSel ('Just "_fiReferences") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [Reference]) :*: S1 ('MetaSel ('Just "_fiAnchors") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [Anchor]))) |
data ScanPolicy Source #
Constructors
OnlyTracked | Scan and treat as existing only files tracked by Git. Warn when there are scannable files not added to Git yet. |
IncludeUntracked | Also scan and treat as existing files that were neither tracked nor ignored by Git. |
Instances
Show ScanPolicy Source # | |
Defined in Xrefcheck.Core Methods showsPrec :: Int -> ScanPolicy -> ShowS # show :: ScanPolicy -> String # showList :: [ScanPolicy] -> ShowS # | |
Eq ScanPolicy Source # | |
Defined in Xrefcheck.Core |
data FileStatus Source #
Constructors
Scanned FileInfo | |
NotScannable | Files that are not supported by our scanners. |
NotAddedToGit | We are not scanning files that are not added to git unless --include-untracked CLI option was enabled, but we're gathering information about them to improve reports. |
Instances
Show FileStatus Source # | |
Defined in Xrefcheck.Core Methods showsPrec :: Int -> FileStatus -> ShowS # show :: FileStatus -> String # showList :: [FileStatus] -> ShowS # |
data DirectoryStatus Source #
Constructors
TrackedDirectory | |
UntrackedDirectory |
Instances
Show DirectoryStatus Source # | |
Defined in Xrefcheck.Core Methods showsPrec :: Int -> DirectoryStatus -> ShowS # show :: DirectoryStatus -> String # showList :: [DirectoryStatus] -> ShowS # |
All tracked files and directories.
Constructors
RepoInfo | |
Fields
|
data VerifyMode Source #
Which parts of verification do we perform.
Constructors
LocalOnlyMode | |
ExternalOnlyMode | |
FullMode |
shouldCheckLocal :: VerifyMode -> Bool Source #
shouldCheckExternal :: VerifyMode -> Bool Source #
headerToAnchor :: Flavor -> Text -> Text Source #
Convert section header name to an anchor refering it. Conversion rules: https://docs.gitlab.com/ee/user/markdown.html#header-ids-and-links
stripAnchorDupNo :: Text -> Maybe Text Source #
When there are several anchors with the same name, github automatically attaches "-number" suffixes to duplications to make them referable unambiguously. For instance, if there are two headers called "description", they would gain "description" and "description-1" anchors correspondingly.
This function strips this suffix and returns the original anchor in case when suffix is present.
data VerifyProgress Source #
Constructors
VerifyProgress | |
Instances
Show VerifyProgress Source # | |
Defined in Xrefcheck.Core Methods showsPrec :: Int -> VerifyProgress -> ShowS # show :: VerifyProgress -> String # showList :: [VerifyProgress] -> ShowS # |
initVerifyProgress :: [Reference] -> VerifyProgress Source #
showAnalyseProgress :: Given ColorMode => VerifyMode -> Time Second -> VerifyProgress -> Text Source #
reprintAnalyseProgress :: Given ColorMode => Rewrite -> VerifyMode -> Time Second -> VerifyProgress -> IO () Source #