| Safe Haskell | Safe-Inferred |
|---|---|
| Language | Haskell2010 |
Xrefcheck.Scan
Contents
Description
Generalised repo scanner and analyser.
Synopsis
- type ExclusionConfig = ExclusionConfig' Identity
- data ExclusionConfig' f = ExclusionConfig {}
- type FileSupport = IsSymlink -> Extension -> Maybe ScanAction
- data ReadDirectoryMode
- type ScanAction = FilePath -> RelPosixLink -> IO (FileInfo, [ScanError 'Parse])
- data ScanError (a :: ScanStage) = ScanError {
- seFile :: ScanStageFile a
- sePosition :: Position
- seDescription :: ScanErrorDescription
- data ScanErrorDescription
- data ScanResult = ScanResult {
- srScanErrors :: [ScanError 'Gather]
- srRepoInfo :: RepoInfo
- data ScanStage
- defaultCompOption :: CompOption
- defaultExecOption :: ExecOption
- ecIgnoreL :: forall f. Lens' (ExclusionConfig' f) (Field f [CanonicalRelGlobPattern])
- ecIgnoreLocalRefsToL :: forall f. Lens' (ExclusionConfig' f) (Field f [CanonicalRelGlobPattern])
- ecIgnoreRefsFromL :: forall f. Lens' (ExclusionConfig' f) (Field f [CanonicalRelGlobPattern])
- ecIgnoreExternalRefsToL :: forall f. Lens' (ExclusionConfig' f) (Field f [Regex])
- firstFileSupport :: [FileSupport] -> FileSupport
- mkGatherScanError :: RelPosixLink -> ScanError 'Parse -> ScanError 'Gather
- mkParseScanError :: Position -> ScanErrorDescription -> ScanError 'Parse
- reportScanErrs :: Given ColorMode => NonEmpty (ScanError 'Gather) -> IO ()
- scanRepo :: MonadIO m => ScanPolicy -> Rewrite -> FileSupport -> ExclusionConfig -> FilePath -> m ScanResult
Documentation
type ExclusionConfig = ExclusionConfig' Identity Source #
Type alias for ExclusionConfig' with all required fields.
data ExclusionConfig' f Source #
Config of repositry exclusions.
Constructors
| ExclusionConfig | |
Fields
| |
Instances
type FileSupport = IsSymlink -> Extension -> Maybe ScanAction Source #
All supported ways to parse a file.
data ReadDirectoryMode Source #
Constructors
| RdmTracked | Consider files tracked by Git, obtained from "git ls-files" |
| RdmUntracked | Consider files that are not tracked nor ignored by Git, obtained from "git ls-files --others --exclude-standard" |
| RdmBothTrackedAndUtracked | Combine output from commands listed above, so we consider all files except ones that are explicitly ignored by Git |
type ScanAction = FilePath -> RelPosixLink -> IO (FileInfo, [ScanError 'Parse]) Source #
Way to parse a file.
data ScanError (a :: ScanStage) Source #
A scan error indexed by different process stages.
Within Parse, seFile has no information because the same
file is being parsed.
Within Gather, seFile stores the FilePath corresponding
to the file in where the error was found.
Constructors
| ScanError | |
Fields
| |
data ScanErrorDescription Source #
Constructors
| LinkErr | |
| FileErr | |
| ParagraphErr Text | |
| UnrecognisedErr Text |
Instances
| Show ScanErrorDescription Source # | |
Defined in Xrefcheck.Scan Methods showsPrec :: Int -> ScanErrorDescription -> ShowS # show :: ScanErrorDescription -> String # showList :: [ScanErrorDescription] -> ShowS # | |
| Buildable ScanErrorDescription Source # | |
Defined in Xrefcheck.Scan Methods build :: ScanErrorDescription -> Builder # | |
| Eq ScanErrorDescription Source # | |
Defined in Xrefcheck.Scan Methods (==) :: ScanErrorDescription -> ScanErrorDescription -> Bool # (/=) :: ScanErrorDescription -> ScanErrorDescription -> Bool # | |
data ScanResult Source #
Constructors
| ScanResult | |
Fields
| |
ecIgnoreL :: forall f. Lens' (ExclusionConfig' f) (Field f [CanonicalRelGlobPattern]) Source #
ecIgnoreLocalRefsToL :: forall f. Lens' (ExclusionConfig' f) (Field f [CanonicalRelGlobPattern]) Source #
ecIgnoreRefsFromL :: forall f. Lens' (ExclusionConfig' f) (Field f [CanonicalRelGlobPattern]) Source #
ecIgnoreExternalRefsToL :: forall f. Lens' (ExclusionConfig' f) (Field f [Regex]) Source #
firstFileSupport :: [FileSupport] -> FileSupport Source #
mkGatherScanError :: RelPosixLink -> ScanError 'Parse -> ScanError 'Gather Source #
scanRepo :: MonadIO m => ScanPolicy -> Rewrite -> FileSupport -> ExclusionConfig -> FilePath -> m ScanResult Source #