[#139] Ignore build-related files

Problem: At the moment, we're using the ignored option for mainly 2
purposes: 1) to ignore all files in the `.git` folder (`.git/**/*`) to
ignore all build-related temporary files (the default config ignores
`.stack-work/**/*`). A more robust alternative might be to ignore all
files implicitly ignored by git.

Solution: Use `git ls-files` to ignore all files implicitly ignored by git.
This commit is contained in:
Sergey Gulin 2022-09-26 15:34:13 +10:00
parent c2aad89227
commit bfbe20a5b0
No known key found for this signature in database
GPG Key ID: 67CBDE9BE7E6399B
22 changed files with 283 additions and 175 deletions

View File

@ -28,7 +28,7 @@ steps:
artifact_paths: artifact_paths:
- "result/bin/*" - "result/bin/*"
- command: nix run -f ci.nix xrefcheck-static -c xrefcheck --ignored 'tests/**/*' - command: nix run -f ci.nix xrefcheck-static -c xrefcheck --ignored 'tests/markdowns/**/*' --ignored 'tests/golden/**/*'
label: Xrefcheck itself label: Xrefcheck itself
- label: lint - label: lint

View File

@ -25,6 +25,10 @@ Unreleased
as broken (with message `Link targets a local file outside repository`). as broken (with message `Link targets a local file outside repository`).
Same for links that are using directories outside repository (e.g. `/../repo/a.md`), Same for links that are using directories outside repository (e.g. `/../repo/a.md`),
since such things are not supported by GitHub markdown renderer. since such things are not supported by GitHub markdown renderer.
* [#174](https://github.com/serokell/xrefcheck/pull/174)
+ Make xrefcheck only scan files that are tracked by git.
+ Fixed bug where links to ignored files were valid.
+ Fixed bug where links with trailing slashes were invalid.
0.2.1 0.2.1
========== ==========

View File

@ -47,6 +47,10 @@ Both relative and absolute local links are supported out of the box.
At the moment of writing, the listed solutions don't support ftp/ftps links. At the moment of writing, the listed solutions don't support ftp/ftps links.
## Dependencies [](#xrefcheck)
Xrefcheck requires you to have `git` version 2.18.0 or later in your PATH.
## Usage [](#xrefcheck) ## Usage [](#xrefcheck)
We provide the following ways for you to use xrefcheck: We provide the following ways for you to use xrefcheck:

View File

@ -82,7 +82,6 @@ library:
- containers - containers
- cmark-gfm >= 0.2.5 - cmark-gfm >= 0.2.5
- data-default - data-default
- directory-tree
- directory - directory
- dlist - dlist
- exceptions - exceptions
@ -99,6 +98,7 @@ library:
- mtl - mtl
- o-clock - o-clock
- optparse-applicative - optparse-applicative
- process
- regex-tdfa - regex-tdfa
- req - req
- tagsoup - tagsoup

View File

@ -17,12 +17,7 @@ defConfigUnfilled =
traversal: traversal:
# Glob patterns describing files which we pretend do not exist # Glob patterns describing files which we pretend do not exist
# (so they are neither analyzed nor can be referenced). # (so they are neither analyzed nor can be referenced).
ignored: ignored: []
# Git files
- .git/**/*
# Stack files
- .stack-work/**/*
# Verification parameters. # Verification parameters.
verification: verification:

View File

@ -122,8 +122,13 @@ makeLenses ''FileInfo
instance Default FileInfo where instance Default FileInfo where
def = diffToFileInfo mempty def = diffToFileInfo mempty
newtype RepoInfo = RepoInfo (Map FilePath FileInfo) -- | All tracked files and directories.
deriving stock (Show) data RepoInfo = RepoInfo
{ riFiles :: Map FilePath (Maybe FileInfo)
-- ^ Files from the repo with `FileInfo` attached to files that we can scan.
, riDirectories :: Set FilePath
-- ^ Tracked directories.
} deriving stock (Show)
----------------------------------------------------------- -----------------------------------------------------------
-- Instances -- Instances
@ -171,7 +176,8 @@ instance Given ColorMode => Buildable FileInfo where
] ]
instance Given ColorMode => Buildable RepoInfo where instance Given ColorMode => Buildable RepoInfo where
build (RepoInfo m) = blockListF' "" buildFileReport (M.toList m) build (RepoInfo m _) =
blockListF' "" buildFileReport (mapMaybe sequence $ M.toList m)
where where
buildFileReport (name, info) = mconcat buildFileReport (name, info) = mconcat
[ colorIfNeeded Cyan $ fromString name <> ":\n" [ colorIfNeeded Cyan $ fromString name <> ":\n"

View File

@ -24,13 +24,14 @@ module Xrefcheck.Scan
import Universum import Universum
import Data.Aeson (FromJSON (..), genericParseJSON) import Data.Aeson (FromJSON (..), genericParseJSON)
import Data.Foldable qualified as F import Data.List qualified as L
import Data.Map qualified as M import Data.Map qualified as M
import Data.Reflection (Given) import Data.Reflection (Given)
import Fmt (Buildable (..), nameF, (+|), (|+)) import Fmt (Buildable (..), nameF, (+|), (|+))
import System.Directory (doesDirectoryExist) import System.Directory (doesDirectoryExist)
import System.Directory.Tree qualified as Tree import System.FilePath
import System.FilePath (dropTrailingPathSeparator, equalFilePath, takeDirectory, takeExtension) (dropTrailingPathSeparator, equalFilePath, splitDirectories, takeDirectory, takeExtension, (</>))
import System.Process (cwd, readCreateProcess, shell)
import Xrefcheck.Core import Xrefcheck.Core
import Xrefcheck.Progress import Xrefcheck.Progress
@ -107,6 +108,31 @@ specificFormatsSupport formats = \ext -> M.lookup ext formatsMap
, extension <- extensions , extension <- extensions
] ]
-- | Process files that are tracked by git and not ignored by the config.
readDirectoryWith
:: forall a. TraversalConfig
-> (FilePath -> IO a)
-> FilePath
-> IO [(FilePath, a)]
readDirectoryWith config scanner root =
traverse scanFile
. filter (not . isIgnored)
. fmap (location </>)
. L.lines =<< readCreateProcess (shell "git ls-files"){cwd = Just root} ""
where
scanFile :: FilePath -> IO (FilePath, a)
scanFile = sequence . (normaliseWithNoTrailing &&& scanner)
isIgnored :: FilePath -> Bool
isIgnored = matchesGlobPatterns root $ tcIgnored config
-- Strip leading "." and trailing "/"
location :: FilePath
location =
if root `equalFilePath` "."
then ""
else dropTrailingPathSeparator root
scanRepo scanRepo
:: MonadIO m :: MonadIO m
=> Rewrite -> FormatsSupport -> TraversalConfig -> FilePath -> m ScanResult => Rewrite -> FormatsSupport -> TraversalConfig -> FilePath -> m ScanResult
@ -116,36 +142,33 @@ scanRepo rw formatsSupport config root = do
when (not $ isDirectory root) $ when (not $ isDirectory root) $
die $ "Repository's root does not seem to be a directory: " <> root die $ "Repository's root does not seem to be a directory: " <> root
_ Tree.:/ repoTree <- liftIO $ Tree.readDirectoryWithL processFile root (errs, fileInfos) <- liftIO
let (errs, fileInfos) = gatherScanErrs &&& gatherFileInfos $ (gatherScanErrs &&& gatherFileInfos)
$ dropSndMaybes . F.toList <$> readDirectoryWith config processFile root
$ Tree.zipPaths $ location Tree.:/ repoTree
return . ScanResult errs $ RepoInfo (M.fromList fileInfos)
where
isDirectory = readingSystem . doesDirectoryExist
gatherScanErrs = foldMap (snd . snd)
gatherFileInfos = map (bimap normaliseWithNoTrailing fst)
let dirs = fromList $ foldMap (getDirs . fst) fileInfos
return . ScanResult errs $ RepoInfo (M.fromList fileInfos) dirs
where
isDirectory :: FilePath -> Bool
isDirectory = readingSystem . doesDirectoryExist
-- Get all directories from filepath.
getDirs :: FilePath -> [FilePath]
getDirs = scanl (</>) "" . splitDirectories . takeDirectory
gatherScanErrs
:: [(FilePath, Maybe (FileInfo, [ScanError]))]
-> [ScanError]
gatherScanErrs = fold . mapMaybe (fmap snd . snd)
gatherFileInfos
:: [(FilePath, Maybe (FileInfo, [ScanError]))]
-> [(FilePath, Maybe FileInfo)]
gatherFileInfos = map (second (fmap fst))
processFile :: FilePath -> IO $ Maybe (FileInfo, [ScanError])
processFile file = do processFile file = do
let ext = takeExtension file let ext = takeExtension file
let mscanner = formatsSupport ext let mscanner = formatsSupport ext
if isIgnored file forM mscanner ($ file)
then pure Nothing
else forM mscanner ($ file)
dropSndMaybes l = [(a, b) | (a, Just b) <- l]
isIgnored = matchesGlobPatterns root $ tcIgnored config
-- The context location of the root.
-- This is done by removing the last component from the path.
-- > root = "./folder/file.md" ==> location = "./folder"
-- > root = "./folder/subfolder" ==> location = "./folder"
-- > root = "./folder/subfolder/" ==> location = "./folder"
-- > root = "./folder/subfolder/./" ==> location = "./folder/subfolder"
-- > root = "." ==> location = ""
-- > root = "/absolute/path" ==> location = "/absolute"
-- > root = "/" ==> location = "/"
location =
if root `equalFilePath` "."
then ""
else takeDirectory $ dropTrailingPathSeparator root

View File

@ -57,8 +57,8 @@ import Network.HTTP.Req
HttpMethod, NoReqBody (..), defaultHttpConfig, ignoreResponse, req, runReq, useURI) HttpMethod, NoReqBody (..), defaultHttpConfig, ignoreResponse, req, runReq, useURI)
import Network.HTTP.Types.Header (hRetryAfter) import Network.HTTP.Types.Header (hRetryAfter)
import Network.HTTP.Types.Status (Status, statusCode, statusMessage) import Network.HTTP.Types.Status (Status, statusCode, statusMessage)
import System.Directory (doesDirectoryExist, doesFileExist) import System.FilePath
import System.FilePath (makeRelative, normalise, splitDirectories, takeDirectory, (</>)) (equalFilePath, joinPath, makeRelative, normalise, splitDirectories, takeDirectory, (</>))
import Text.ParserCombinators.ReadPrec qualified as ReadPrec (lift) import Text.ParserCombinators.ReadPrec qualified as ReadPrec (lift)
import Text.Regex.TDFA.Text (Regex, regexec) import Text.Regex.TDFA.Text (Regex, regexec)
import Text.URI (Authority (..), ParseExceptionBs, URI (..), mkURIBs) import Text.URI (Authority (..), ParseExceptionBs, URI (..), mkURIBs)
@ -260,13 +260,16 @@ verifyRepo
config@VerifyConfig{..} config@VerifyConfig{..}
mode mode
root root
repoInfo'@(RepoInfo repoInfo) repoInfo'@(RepoInfo files _)
= do = do
let toScan = do let toScan = do
(file, fileInfo) <- M.toList repoInfo (file, fileInfo) <- M.toList files
guard . not $ matchesGlobPatterns root vcNotScanned file guard . not $ matchesGlobPatterns root vcNotScanned file
ref <- _fiReferences fileInfo case fileInfo of
Just fi -> do
ref <- _fiReferences fi
return (file, ref) return (file, ref)
Nothing -> empty -- no support for such file, can do nothing
progressRef <- newIORef $ initVerifyProgress (map snd toScan) progressRef <- newIORef $ initVerifyProgress (map snd toScan)
@ -312,7 +315,7 @@ verifyReference
config@VerifyConfig{..} config@VerifyConfig{..}
mode mode
progressRef progressRef
(RepoInfo repoInfo) (RepoInfo files dirs)
root root
fileWithReference fileWithReference
ref@Reference{..} ref@Reference{..}
@ -417,11 +420,30 @@ verifyReference
unless (isVirtual referredFile) do unless (isVirtual referredFile) do
checkReferredFileIsInsideRepo referredFile checkReferredFileIsInsideRepo referredFile
checkReferredFileExists referredFile checkReferredFileExists referredFile
case M.lookup referredFile repoInfo of case lookupFilePath referredFile $ M.toList files of
Nothing -> pass -- no support for such file, can do nothing Nothing -> pass -- no support for such file, can do nothing
Just referredFileInfo -> whenJust mAnchor $ Just referredFileInfo -> whenJust mAnchor $
checkAnchor referredFile (_fiAnchors referredFileInfo) checkAnchor referredFile (_fiAnchors referredFileInfo)
lookupFilePath :: FilePath -> [(FilePath, Maybe FileInfo)] -> Maybe FileInfo
lookupFilePath fp = snd <=< find (equalFilePath (expandIndirections fp) . fst)
-- expands ".." and "."
-- expandIndirections "a/b/../c" = "a/c"
-- expandIndirections "a/b/c/../../d" = "a/d"
-- expandIndirections "../../a" = "../../a"
-- expandIndirections "a/./b" = "a/b"
-- expandIndirections "a/b/./../c" = "a/c"
expandIndirections :: FilePath -> FilePath
expandIndirections = joinPath . reverse . expand 0 . reverse . splitDirectories
where
expand :: Int -> [FilePath] -> [FilePath]
expand acc ("..":xs) = expand (acc+1) xs
expand acc (".":xs) = expand acc xs
expand 0 (x:xs) = x : expand 0 xs
expand acc (_:xs) = expand (acc-1) xs
expand acc [] = replicate acc ".."
checkReferredFileIsInsideRepo file = unless checkReferredFileIsInsideRepo file = unless
(noNegativeNesting $ makeRelative root file) $ (noNegativeNesting $ makeRelative root file) $
throwError (LocalFileOutsideRepo file) throwError (LocalFileOutsideRepo file)
@ -439,11 +461,17 @@ verifyReference
nestingChange _ = 1 nestingChange _ = 1
checkReferredFileExists file = do checkReferredFileExists file = do
let fileExists = readingSystem $ doesFileExist file
let dirExists = readingSystem $ doesDirectoryExist file
unless (fileExists || dirExists) $ unless (fileExists || dirExists) $
throwError (LocalFileDoesNotExist file) throwError (LocalFileDoesNotExist file)
where
matchesFilePath :: FilePath -> Bool
matchesFilePath = equalFilePath $ expandIndirections file
fileExists :: Bool
fileExists = any matchesFilePath $ M.keys files
dirExists :: Bool
dirExists = any matchesFilePath dirs
checkAnchor file fileAnchors anchor = do checkAnchor file fileAnchors anchor = do
checkAnchorReferenceAmbiguity file fileAnchors anchor checkAnchorReferenceAmbiguity file fileAnchors anchor

View File

@ -198,7 +198,7 @@ test_tooManyRequests = testGroup "429 response tests"
verifyReferenceWithProgress reference progRef = do verifyReferenceWithProgress reference progRef = do
fmap wrlItem <$> verifyReference fmap wrlItem <$> verifyReference
((cVerification $ defConfig GitHub) { vcIgnoreRefs = [] }) FullMode ((cVerification $ defConfig GitHub) { vcIgnoreRefs = [] }) FullMode
progRef (RepoInfo M.empty) "." "" reference progRef (RepoInfo M.empty mempty) "." "" reference
-- | When called for the first time, returns with a 429 and `Retry-After: @retryAfter@`. -- | When called for the first time, returns with a 429 and `Retry-After: @retryAfter@`.
-- Subsequent calls will respond with @status@. -- Subsequent calls will respond with @status@.

View File

@ -26,7 +26,7 @@ test_slash = testGroup "Trailing forward slash detection" $
testCase ("All the files within the root \"" <> testCase ("All the files within the root \"" <>
root <> root <>
"\" should exist") $ do "\" should exist") $ do
(ScanResult _ (RepoInfo repoInfo)) <- allowRewrite False $ \rw -> (ScanResult _ (RepoInfo repoInfo _)) <- allowRewrite False $ \rw ->
scanRepo rw format TraversalConfig{ tcIgnored = [] } root scanRepo rw format TraversalConfig{ tcIgnored = [] } root
nonExistentFiles <- lefts <$> forM (keys repoInfo) (\filePath -> do nonExistentFiles <- lefts <$> forM (keys repoInfo) (\filePath -> do
predicate <- doesFileExist filePath predicate <- doesFileExist filePath

View File

@ -2,12 +2,7 @@
traversal: traversal:
# Glob patterns describing files which we pretend do not exist # Glob patterns describing files which we pretend do not exist
# (so they are neither analyzed nor can be referenced). # (so they are neither analyzed nor can be referenced).
ignored: ignored: []
# Git files
- .git/**/*
# Stack files
- .stack-work/**/*
# Verification parameters. # Verification parameters.
verification: verification:

View File

@ -0,0 +1,58 @@
#!/usr/bin/env bats
# SPDX-FileCopyrightText: 2022 Serokell <https://serokell.io>
#
# SPDX-License-Identifier: MPL-2.0
load '../helpers/bats-support/load'
load '../helpers/bats-assert/load'
load '../helpers/bats-file/load'
load '../helpers'
@test "Git: not a repo" {
cd $TEST_TEMP_DIR
run xrefcheck
assert_output --partial "fatal: not a git repository"
}
@test "Git: file not tracked" {
cd $TEST_TEMP_DIR
git init
echo "[a](/a.md)" >> "git.md"
run xrefcheck
assert_output --partial "All repository links are valid."
}
@test "Git: file tracked, check failure" {
cd $TEST_TEMP_DIR
git init
echo "[a](./a.md)" >> "git.md"
git add git.md
to_temp xrefcheck
assert_diff - <<EOF
=== Invalid references found ===
➥ In file git.md
bad reference (relative) at src:1:1-11:
- text: "a"
- link: ./a.md
- anchor: -
⛀ File does not exist:
a.md
Invalid references dumped, 1 in total.
EOF
}

View File

@ -37,5 +37,47 @@ load '../helpers'
@test "Ignore file with broken xrefcheck annotation: directory, check failure" { @test "Ignore file with broken xrefcheck annotation: directory, check failure" {
to_temp xrefcheck --ignored ./to-ignore/inner-directory/ to_temp xrefcheck --ignored ./to-ignore/inner-directory/
assert_diff expected.gold assert_diff - <<EOF
=== Scan errors found ===
➥ In file to-ignore/inner-directory/broken_annotation.md
scan error at src:9:1-30:
⛀ Annotation "ignore file" must be at the top of markdown or right after comments at the top
Scan errors dumped, 1 in total.
EOF
}
@test "Ignore referenced file, check error" {
to_temp xrefcheck --ignored referenced-file.md
assert_diff - <<EOF
=== Scan errors found ===
➥ In file to-ignore/inner-directory/broken_annotation.md
scan error at src:9:1-30:
⛀ Annotation "ignore file" must be at the top of markdown or right after comments at the top
Scan errors dumped, 1 in total.
=== Invalid references found ===
➥ In file check-ignored.md
bad reference (absolute) at src:7:1-37:
- text: "Good reference"
- link: /referenced-file.md
- anchor: -
⛀ File does not exist:
./referenced-file.md
Invalid references dumped, 1 in total.
EOF
} }

View File

@ -0,0 +1,7 @@
<!--
- SPDX-FileCopyrightText: 2022 Serokell <https://serokell.io>
-
- SPDX-License-Identifier: MPL-2.0
-->
[Good reference](/referenced-file.md)

View File

@ -1,10 +0,0 @@
=== Scan errors found ===
➥ In file ./to-ignore/inner-directory/broken_annotation.md
scan error at src:9:1-30:
⛀ Annotation "ignore file" must be at the top of markdown or right after comments at the top
Scan errors dumped, 1 in total.

View File

@ -0,0 +1,7 @@
<!--
- SPDX-FileCopyrightText: 2022 Serokell <https://serokell.io>
-
- SPDX-License-Identifier: MPL-2.0
-->
referenced file

View File

@ -14,11 +14,8 @@
[existing-file-rel-3](../dir2/.././d1f1.md) [existing-file-rel-3](../dir2/.././d1f1.md)
[existing-file-rel-4](d2f3.yaml) [existing-file-rel-4](d2f3.yaml)
Currently our behavior is wrong, see https://github.com/serokell/xrefcheck/issues/195
[slash-file-rel](d2f2.md/) [slash-file-rel](d2f2.md/)
[existing-dir-rel-1](..) [existing-dir-rel-1](..)
[existing-dir-rel-2](../dir2) [existing-dir-rel-2](../dir2)
[existing-dir-rel-3](../dir2/) [existing-dir-rel-3](../dir2/)

View File

@ -10,17 +10,7 @@
➥ In file dir1/dir2/d2f1.md ➥ In file dir1/dir2/d2f1.md
bad reference (relative) at src:18:1-26: bad reference (relative) at src:27:1-43:
- text: "slash-file-rel"
- link: d2f2.md/
- anchor: -
⛀ File does not exist:
dir1/dir2/d2f2.md/
➥ In file dir1/dir2/d2f1.md
bad reference (relative) at src:30:1-43:
- text: "bad-file-rel" - text: "bad-file-rel"
- link: ../a/b/c/unexisting-file.md - link: ../a/b/c/unexisting-file.md
- anchor: - - anchor: -
@ -30,7 +20,7 @@
➥ In file dir1/dir2/d2f1.md ➥ In file dir1/dir2/d2f1.md
bad reference (relative) at src:31:1-31: bad reference (relative) at src:28:1-31:
- text: "bad-casing-file-rel" - text: "bad-casing-file-rel"
- link: D2F2.md/ - link: D2F2.md/
- anchor: - - anchor: -
@ -40,7 +30,7 @@
➥ In file dir1/dir2/d2f1.md ➥ In file dir1/dir2/d2f1.md
bad reference (relative) at src:32:1-32: bad reference (relative) at src:29:1-32:
- text: "bad-casing-folder-rel" - text: "bad-casing-folder-rel"
- link: ../DIR2 - link: ../DIR2
- anchor: - - anchor: -
@ -50,7 +40,7 @@
➥ In file dir1/dir2/d2f1.md ➥ In file dir1/dir2/d2f1.md
bad reference (relative) at src:34:1-38: bad reference (relative) at src:31:1-38:
- text: "bad-anchor-rel-1" - text: "bad-anchor-rel-1"
- link: d2f2.md - link: d2f2.md
- anchor: bad-anchor - anchor: bad-anchor
@ -59,7 +49,7 @@
➥ In file dir1/dir2/d2f1.md ➥ In file dir1/dir2/d2f1.md
bad reference (relative) at src:35:1-49: bad reference (relative) at src:32:1-49:
- text: "bad-anchor-rel-2" - text: "bad-anchor-rel-2"
- link: unexisting-file.md - link: unexisting-file.md
- anchor: bad-anchor - anchor: bad-anchor
@ -69,7 +59,7 @@
➥ In file dir1/dir2/d2f1.md ➥ In file dir1/dir2/d2f1.md
bad reference (absolute) at src:45:1-22: bad reference (absolute) at src:42:1-22:
- text: "file-abs-2" - text: "file-abs-2"
- link: /d1f1.md - link: /d1f1.md
- anchor: - - anchor: -
@ -79,7 +69,7 @@
➥ In file dir1/dir2/d2f1.md ➥ In file dir1/dir2/d2f1.md
bad reference (absolute) at src:46:1-27: bad reference (absolute) at src:43:1-27:
- text: "file-abs-3" - text: "file-abs-3"
- link: /dir2/d2f2.md - link: /dir2/d2f2.md
- anchor: - - anchor: -
@ -89,7 +79,7 @@
➥ In file dir1/dir2/d2f1.md ➥ In file dir1/dir2/d2f1.md
bad reference (absolute) at src:47:1-32: bad reference (absolute) at src:44:1-32:
- text: "file-abs-4" - text: "file-abs-4"
- link: /./dir2/../d1f1.md - link: /./dir2/../d1f1.md
- anchor: - - anchor: -
@ -99,7 +89,7 @@
➥ In file dir1/dir2/d2f1.md ➥ In file dir1/dir2/d2f1.md
bad reference (absolute) at src:48:1-37: bad reference (absolute) at src:45:1-37:
- text: "file-abs-slash" - text: "file-abs-slash"
- link: /./dir2/../d1f1.md/ - link: /./dir2/../d1f1.md/
- anchor: - - anchor: -
@ -109,7 +99,7 @@
➥ In file dir1/dir2/d2f1.md ➥ In file dir1/dir2/d2f1.md
bad reference (absolute) at src:49:1-55: bad reference (absolute) at src:46:1-55:
- text: "anchor-abs-3" - text: "anchor-abs-3"
- link: /./dir2/../d1f1.md - link: /./dir2/../d1f1.md
- anchor: existing-anchor-d1f1 - anchor: existing-anchor-d1f1
@ -119,7 +109,7 @@
➥ In file dir1/dir2/d2f1.md ➥ In file dir1/dir2/d2f1.md
bad reference (absolute) at src:60:1-16: bad reference (absolute) at src:57:1-16:
- text: "A" - text: "A"
- link: /../../a.md - link: /../../a.md
- anchor: - - anchor: -
@ -129,7 +119,7 @@
➥ In file dir1/dir2/d2f1.md ➥ In file dir1/dir2/d2f1.md
bad reference (absolute) at src:61:1-18: bad reference (absolute) at src:58:1-18:
- text: "B" - text: "B"
- link: /b/../../b.md - link: /b/../../b.md
- anchor: - - anchor: -
@ -138,4 +128,4 @@
./b/../../b.md ./b/../../b.md
Invalid references dumped, 14 in total. Invalid references dumped, 13 in total.

View File

@ -10,17 +10,7 @@
➥ In file dir1/dir2/d2f1.md ➥ In file dir1/dir2/d2f1.md
bad reference (relative) at src:18:1-26: bad reference (relative) at src:27:1-43:
- text: "slash-file-rel"
- link: d2f2.md/
- anchor: -
⛀ File does not exist:
dir1/dir2/d2f2.md/
➥ In file dir1/dir2/d2f1.md
bad reference (relative) at src:30:1-43:
- text: "bad-file-rel" - text: "bad-file-rel"
- link: ../a/b/c/unexisting-file.md - link: ../a/b/c/unexisting-file.md
- anchor: - - anchor: -
@ -30,7 +20,7 @@
➥ In file dir1/dir2/d2f1.md ➥ In file dir1/dir2/d2f1.md
bad reference (relative) at src:31:1-31: bad reference (relative) at src:28:1-31:
- text: "bad-casing-file-rel" - text: "bad-casing-file-rel"
- link: D2F2.md/ - link: D2F2.md/
- anchor: - - anchor: -
@ -40,7 +30,7 @@
➥ In file dir1/dir2/d2f1.md ➥ In file dir1/dir2/d2f1.md
bad reference (relative) at src:32:1-32: bad reference (relative) at src:29:1-32:
- text: "bad-casing-folder-rel" - text: "bad-casing-folder-rel"
- link: ../DIR2 - link: ../DIR2
- anchor: - - anchor: -
@ -50,7 +40,7 @@
➥ In file dir1/dir2/d2f1.md ➥ In file dir1/dir2/d2f1.md
bad reference (relative) at src:34:1-38: bad reference (relative) at src:31:1-38:
- text: "bad-anchor-rel-1" - text: "bad-anchor-rel-1"
- link: d2f2.md - link: d2f2.md
- anchor: bad-anchor - anchor: bad-anchor
@ -59,7 +49,7 @@
➥ In file dir1/dir2/d2f1.md ➥ In file dir1/dir2/d2f1.md
bad reference (relative) at src:35:1-49: bad reference (relative) at src:32:1-49:
- text: "bad-anchor-rel-2" - text: "bad-anchor-rel-2"
- link: unexisting-file.md - link: unexisting-file.md
- anchor: bad-anchor - anchor: bad-anchor
@ -69,7 +59,7 @@
➥ In file dir1/dir2/d2f1.md ➥ In file dir1/dir2/d2f1.md
bad reference (absolute) at src:39:1-29: bad reference (absolute) at src:36:1-29:
- text: "file-abs-1" - text: "file-abs-1"
- link: /dir1/./d1f1.md - link: /dir1/./d1f1.md
- anchor: - - anchor: -
@ -79,7 +69,7 @@
➥ In file dir1/dir2/d2f1.md ➥ In file dir1/dir2/d2f1.md
bad reference (absolute) at src:40:1-21: bad reference (absolute) at src:37:1-21:
- text: "folder-abs-1" - text: "folder-abs-1"
- link: /dir1 - link: /dir1
- anchor: - - anchor: -
@ -89,7 +79,7 @@
➥ In file dir1/dir2/d2f1.md ➥ In file dir1/dir2/d2f1.md
bad reference (absolute) at src:41:1-30: bad reference (absolute) at src:38:1-30:
- text: "folder-abs-2" - text: "folder-abs-2"
- link: /dir1/dir2/../ - link: /dir1/dir2/../
- anchor: - - anchor: -
@ -99,7 +89,7 @@
➥ In file dir1/dir2/d2f1.md ➥ In file dir1/dir2/d2f1.md
bad reference (absolute) at src:42:1-58: bad reference (absolute) at src:39:1-58:
- text: "anchor-abs-1" - text: "anchor-abs-1"
- link: /dir1/../dir1/d1f1.md - link: /dir1/../dir1/d1f1.md
- anchor: existing-anchor-d1f1 - anchor: existing-anchor-d1f1
@ -109,7 +99,7 @@
➥ In file dir1/dir2/d2f1.md ➥ In file dir1/dir2/d2f1.md
bad reference (absolute) at src:43:1-73: bad reference (absolute) at src:40:1-73:
- text: "anchor-abs-2" - text: "anchor-abs-2"
- link: /dir1/dir2/../../dir1/./dir2/d2f2.md - link: /dir1/dir2/../../dir1/./dir2/d2f2.md
- anchor: existing-anchor-d2f2 - anchor: existing-anchor-d2f2
@ -119,17 +109,7 @@
➥ In file dir1/dir2/d2f1.md ➥ In file dir1/dir2/d2f1.md
bad reference (absolute) at src:48:1-37: bad reference (relative) at src:51:1-42:
- text: "file-abs-slash"
- link: /./dir2/../d1f1.md/
- anchor: -
⛀ File does not exist:
dir1/./dir2/../d1f1.md/
➥ In file dir1/dir2/d2f1.md
bad reference (relative) at src:54:1-42:
- text: "path-through-top-dir" - text: "path-through-top-dir"
- link: ../../dir1/d1f1.md - link: ../../dir1/d1f1.md
- anchor: - - anchor: -
@ -139,7 +119,7 @@
➥ In file dir1/dir2/d2f1.md ➥ In file dir1/dir2/d2f1.md
bad reference (relative) at src:55:1-75: bad reference (relative) at src:52:1-75:
- text: "path-through-top-dir-with-anchor" - text: "path-through-top-dir-with-anchor"
- link: ../../dir1/d1f1.md - link: ../../dir1/d1f1.md
- anchor: existing-anchor-d1f1 - anchor: existing-anchor-d1f1
@ -149,7 +129,7 @@
➥ In file dir1/dir2/d2f1.md ➥ In file dir1/dir2/d2f1.md
bad reference (relative) at src:56:1-26: bad reference (relative) at src:53:1-26:
- text: "ref-to-d0" - text: "ref-to-d0"
- link: ../../d0f1.md - link: ../../d0f1.md
- anchor: - - anchor: -
@ -159,7 +139,7 @@
➥ In file dir1/dir2/d2f1.md ➥ In file dir1/dir2/d2f1.md
bad reference (absolute) at src:60:1-16: bad reference (absolute) at src:57:1-16:
- text: "A" - text: "A"
- link: /../../a.md - link: /../../a.md
- anchor: - - anchor: -
@ -169,7 +149,7 @@
➥ In file dir1/dir2/d2f1.md ➥ In file dir1/dir2/d2f1.md
bad reference (absolute) at src:61:1-18: bad reference (absolute) at src:58:1-18:
- text: "B" - text: "B"
- link: /b/../../b.md - link: /b/../../b.md
- anchor: - - anchor: -
@ -178,4 +158,4 @@
dir1/b/../../b.md dir1/b/../../b.md
Invalid references dumped, 18 in total. Invalid references dumped, 16 in total.

View File

@ -10,17 +10,7 @@
➥ In file dir1/dir2/d2f1.md ➥ In file dir1/dir2/d2f1.md
bad reference (relative) at src:18:1-26: bad reference (relative) at src:27:1-43:
- text: "slash-file-rel"
- link: d2f2.md/
- anchor: -
⛀ File does not exist:
dir1/dir2/d2f2.md/
➥ In file dir1/dir2/d2f1.md
bad reference (relative) at src:30:1-43:
- text: "bad-file-rel" - text: "bad-file-rel"
- link: ../a/b/c/unexisting-file.md - link: ../a/b/c/unexisting-file.md
- anchor: - - anchor: -
@ -30,7 +20,7 @@
➥ In file dir1/dir2/d2f1.md ➥ In file dir1/dir2/d2f1.md
bad reference (relative) at src:31:1-31: bad reference (relative) at src:28:1-31:
- text: "bad-casing-file-rel" - text: "bad-casing-file-rel"
- link: D2F2.md/ - link: D2F2.md/
- anchor: - - anchor: -
@ -40,7 +30,7 @@
➥ In file dir1/dir2/d2f1.md ➥ In file dir1/dir2/d2f1.md
bad reference (relative) at src:34:1-38: bad reference (relative) at src:31:1-38:
- text: "bad-anchor-rel-1" - text: "bad-anchor-rel-1"
- link: d2f2.md - link: d2f2.md
- anchor: bad-anchor - anchor: bad-anchor
@ -49,7 +39,7 @@
➥ In file dir1/dir2/d2f1.md ➥ In file dir1/dir2/d2f1.md
bad reference (relative) at src:35:1-49: bad reference (relative) at src:32:1-49:
- text: "bad-anchor-rel-2" - text: "bad-anchor-rel-2"
- link: unexisting-file.md - link: unexisting-file.md
- anchor: bad-anchor - anchor: bad-anchor
@ -59,7 +49,7 @@
➥ In file dir1/dir2/d2f1.md ➥ In file dir1/dir2/d2f1.md
bad reference (absolute) at src:39:1-29: bad reference (absolute) at src:36:1-29:
- text: "file-abs-1" - text: "file-abs-1"
- link: /dir1/./d1f1.md - link: /dir1/./d1f1.md
- anchor: - - anchor: -
@ -69,7 +59,7 @@
➥ In file dir1/dir2/d2f1.md ➥ In file dir1/dir2/d2f1.md
bad reference (absolute) at src:40:1-21: bad reference (absolute) at src:37:1-21:
- text: "folder-abs-1" - text: "folder-abs-1"
- link: /dir1 - link: /dir1
- anchor: - - anchor: -
@ -79,7 +69,7 @@
➥ In file dir1/dir2/d2f1.md ➥ In file dir1/dir2/d2f1.md
bad reference (absolute) at src:41:1-30: bad reference (absolute) at src:38:1-30:
- text: "folder-abs-2" - text: "folder-abs-2"
- link: /dir1/dir2/../ - link: /dir1/dir2/../
- anchor: - - anchor: -
@ -89,7 +79,7 @@
➥ In file dir1/dir2/d2f1.md ➥ In file dir1/dir2/d2f1.md
bad reference (absolute) at src:42:1-58: bad reference (absolute) at src:39:1-58:
- text: "anchor-abs-1" - text: "anchor-abs-1"
- link: /dir1/../dir1/d1f1.md - link: /dir1/../dir1/d1f1.md
- anchor: existing-anchor-d1f1 - anchor: existing-anchor-d1f1
@ -99,7 +89,7 @@
➥ In file dir1/dir2/d2f1.md ➥ In file dir1/dir2/d2f1.md
bad reference (absolute) at src:43:1-73: bad reference (absolute) at src:40:1-73:
- text: "anchor-abs-2" - text: "anchor-abs-2"
- link: /dir1/dir2/../../dir1/./dir2/d2f2.md - link: /dir1/dir2/../../dir1/./dir2/d2f2.md
- anchor: existing-anchor-d2f2 - anchor: existing-anchor-d2f2
@ -109,17 +99,7 @@
➥ In file dir1/dir2/d2f1.md ➥ In file dir1/dir2/d2f1.md
bad reference (absolute) at src:48:1-37: bad reference (relative) at src:51:1-42:
- text: "file-abs-slash"
- link: /./dir2/../d1f1.md/
- anchor: -
⛀ File does not exist:
dir1/./dir2/../d1f1.md/
➥ In file dir1/dir2/d2f1.md
bad reference (relative) at src:54:1-42:
- text: "path-through-top-dir" - text: "path-through-top-dir"
- link: ../../dir1/d1f1.md - link: ../../dir1/d1f1.md
- anchor: - - anchor: -
@ -129,7 +109,7 @@
➥ In file dir1/dir2/d2f1.md ➥ In file dir1/dir2/d2f1.md
bad reference (relative) at src:55:1-75: bad reference (relative) at src:52:1-75:
- text: "path-through-top-dir-with-anchor" - text: "path-through-top-dir-with-anchor"
- link: ../../dir1/d1f1.md - link: ../../dir1/d1f1.md
- anchor: existing-anchor-d1f1 - anchor: existing-anchor-d1f1
@ -138,4 +118,4 @@
dir1/dir2/../../dir1/d1f1.md dir1/dir2/../../dir1/d1f1.md
Invalid references dumped, 14 in total. Invalid references dumped, 12 in total.

View File

@ -1,42 +1,43 @@
=== Scan errors found === === Scan errors found ===
➥ In file ./check-scan-errors.md
➥ In file check-scan-errors.md
scan error at src:9:1-30: scan error at src:9:1-30:
⛀ Annotation "ignore file" must be at the top of markdown or right after comments at the top ⛀ Annotation "ignore file" must be at the top of markdown or right after comments at the top
➥ In file ./check-scan-errors.md ➥ In file check-scan-errors.md
scan error at src:13:1-36: scan error at src:13:1-36:
⛀ Expected a PARAGRAPH after "ignore paragraph" annotation, but found HEADING ⛀ Expected a PARAGRAPH after "ignore paragraph" annotation, but found HEADING
➥ In file ./check-scan-errors.md ➥ In file check-scan-errors.md
scan error at src:17:1-31: scan error at src:17:1-31:
⛀ Expected a LINK after "ignore link" annotation ⛀ Expected a LINK after "ignore link" annotation
➥ In file ./check-scan-errors.md ➥ In file check-scan-errors.md
scan error at src:21:1-50: scan error at src:21:1-50:
⛀ Unrecognised option "unrecognised-annotation" perhaps you meant <"ignore link"|"ignore paragraph"|"ignore file"> ⛀ Unrecognised option "unrecognised-annotation" perhaps you meant <"ignore link"|"ignore paragraph"|"ignore file">
➥ In file ./check-second-file.md ➥ In file check-second-file.md
scan error at src:9:1-30: scan error at src:9:1-30:
⛀ Annotation "ignore file" must be at the top of markdown or right after comments at the top ⛀ Annotation "ignore file" must be at the top of markdown or right after comments at the top
➥ In file ./no_link_eof.md ➥ In file no_link_eof.md
scan error at src:9:1-31: scan error at src:9:1-31:
⛀ Expected a LINK after "ignore link" annotation ⛀ Expected a LINK after "ignore link" annotation
➥ In file ./no_paragraph_eof.md ➥ In file no_paragraph_eof.md
scan error at src:9:1-36: scan error at src:9:1-36:
⛀ Expected a PARAGRAPH after "ignore paragraph" annotation, but found EOF ⛀ Expected a PARAGRAPH after "ignore paragraph" annotation, but found EOF

View File

@ -8,7 +8,7 @@ let
src = (import ./ci.nix).project-src; src = (import ./ci.nix).project-src;
pkgs = if linux-static then nixpkgs.pkgsCross.musl64 else if windows then nixpkgs.pkgsCross.mingwW64 else nixpkgs; pkgs = if linux-static then nixpkgs.pkgsCross.musl64 else if windows then nixpkgs.pkgsCross.mingwW64 else nixpkgs;
project = pkgs.haskell-nix.stackProject { project = pkgs.haskell-nix.stackProject {
src = pkgs.haskell-nix.haskellLib.cleanGit { src = ./.; }; src = pkgs.haskell-nix.haskellLib.cleanGit { src = ./.; keepGitDir = true; };
modules = [{ modules = [{
packages.xrefcheck = { packages.xrefcheck = {
ghcOptions = ghcOptions =
@ -38,6 +38,7 @@ let
''; '';
testFlags = [ "--ftp-host" "ftp://localhost:2221" ]; testFlags = [ "--ftp-host" "ftp://localhost:2221" ];
}; };
xrefcheck-tests.build-tools = [ pkgs.git ];
}; };
}; };
}]; }];