Add support for source-path directives (fixes #1577)

This commit is contained in:
Vidar Holen 2019-05-09 19:54:30 -07:00
parent aa4b24e458
commit d9e419d60f
7 changed files with 67 additions and 17 deletions

View File

@ -4,7 +4,8 @@
- Files containing Bats tests can now be checked - Files containing Bats tests can now be checked
- Directory wide directives can now be placed in a `.shellcheckrc` - Directory wide directives can now be placed in a `.shellcheckrc`
- Verbose mode: Use `-S verbose` for especially pedantic suggestions - Verbose mode: Use `-S verbose` for especially pedantic suggestions
- Source paths: Use `-P dir1:dir2` to specify path for sourced files - Source paths: Use `-P dir1:dir2` or a `source-path=dir1` directive
to specify search paths for sourced files.
- SC2249: Warn about `case` with missing default case (verbose) - SC2249: Warn about `case` with missing default case (verbose)
- SC2248: Warn about unquoted variables without special chars (verbose) - SC2248: Warn about unquoted variables without special chars (verbose)
- SC2247: Warn about $"(cmd)" and $"{var}" - SC2247: Warn about $"(cmd)" and $"{var}"

View File

@ -70,10 +70,8 @@ not warn at all, as `ksh` supports decimals in arithmetic contexts.
**-P**\ *SOURCEPATH*,\ **--source-path=***SOURCEPATH* **-P**\ *SOURCEPATH*,\ **--source-path=***SOURCEPATH*
: Specify paths to search for sourced files, separated by `:` on Unix and : Specify paths to search for sourced files, separated by `:` on Unix and
`;` on Windows. Absolute paths will also be rooted in these. The special `;` on Windows. This is equivalent to specifying `search-path`
path `SCRIPTDIR` can be used to specify the currently checked script's directives.
directory, as in `-P SCRIPTDIR` or `-P SCRIPTDIR/../libs`. Subsequent
`-P` flags accumulate and take predecence.
**-s**\ *shell*,\ **--shell=***shell* **-s**\ *shell*,\ **--shell=***shell*
@ -201,6 +199,14 @@ Valid keys are:
used to tell shellcheck where to look for a file whose name is determined used to tell shellcheck where to look for a file whose name is determined
at runtime, or to skip a source by telling it to use `/dev/null`. at runtime, or to skip a source by telling it to use `/dev/null`.
**source-path**
: Add a directory to the search path for `source`/`.` statements (by default,
only ShellCheck's working directory is included). Absolute paths will also
be rooted in these paths. The special path `SCRIPTDIR` can be used to
specify the currently checked script's directory, as in
`source-path=SCRIPTDIR` or `source-path=SCRIPTDIR/../libs`. Multiple
paths accumulate, and `-P` takes precedence over them.
**shell** **shell**
: Overrides the shell detected from the shebang. This is useful for : Overrides the shell detected from the shebang. This is useful for
files meant to be included (and thus lacking a shebang), or possibly files meant to be included (and thus lacking a shebang), or possibly
@ -213,8 +219,10 @@ it will read `key=value` pairs from it and treat them as file-wide directives.
Here is an example `.shellcheckrc`: Here is an example `.shellcheckrc`:
# Don't suggest using -n in [ $var ] # Look for 'source'd files relative to the checked script,
disable=SC2244 # and also look for absolute paths in /mnt/chroot
source-path=SCRIPTDIR
source-path=/mnt/chroot
# Allow using `which` since it gives full paths and is common enough # Allow using `which` since it gives full paths and is common enough
disable=SC2230 disable=SC2230

View File

@ -471,7 +471,7 @@ ioInterface options files = do
first <- a arg first <- a arg
if not first then return False else b arg if not first then return False else b arg
findSourceFile inputs sourcePaths currentScript original = findSourceFile inputs sourcePathFlag currentScript sourcePathAnnotation original =
if isAbsolute original if isAbsolute original
then then
let (_, relative) = splitDrive original let (_, relative) = splitDrive original
@ -481,7 +481,7 @@ ioInterface options files = do
where where
find filename deflt = do find filename deflt = do
sources <- filterM ((allowable inputs) `andM` doesFileExist) sources <- filterM ((allowable inputs) `andM` doesFileExist)
(map (</> filename) $ map adjustPath sourcePaths) (map (</> filename) $ map adjustPath $ sourcePathFlag ++ sourcePathAnnotation)
case sources of case sources of
[] -> return deflt [] -> return deflt
(first:_) -> return first (first:_) -> return first

View File

@ -146,6 +146,7 @@ data Annotation =
DisableComment Integer DisableComment Integer
| SourceOverride String | SourceOverride String
| ShellOverride String | ShellOverride String
| SourcePath String
deriving (Show, Eq) deriving (Show, Eq)
data ConditionType = DoubleBracket | SingleBracket deriving (Show, Eq) data ConditionType = DoubleBracket | SingleBracket deriving (Show, Eq)

View File

@ -215,6 +215,7 @@ prop_worksWhenSourcingWithDashDash =
prop_worksWhenDotting = prop_worksWhenDotting =
null $ checkWithIncludes [("lib", "bar=1")] ". lib; echo \"$bar\"" null $ checkWithIncludes [("lib", "bar=1")] ". lib; echo \"$bar\""
-- FIXME: This should really be giving [1093], "recursively sourced"
prop_noInfiniteSourcing = prop_noInfiniteSourcing =
[] == checkWithIncludes [("lib", "source lib")] "source lib" [] == checkWithIncludes [("lib", "source lib")] "source lib"
@ -236,6 +237,12 @@ prop_recursiveAnalysis =
prop_recursiveParsing = prop_recursiveParsing =
[1037] == checkRecursive [("lib", "echo \"$10\"")] "source lib" [1037] == checkRecursive [("lib", "echo \"$10\"")] "source lib"
prop_nonRecursiveAnalysis =
[] == checkWithIncludes [("lib", "echo $1")] "source lib"
prop_nonRecursiveParsing =
[] == checkWithIncludes [("lib", "echo \"$10\"")] "source lib"
prop_sourceDirectiveDoesntFollowFile = prop_sourceDirectiveDoesntFollowFile =
null $ checkWithIncludes null $ checkWithIncludes
[("foo", "source bar"), ("bar", "baz=3")] [("foo", "source bar"), ("bar", "baz=3")]
@ -342,17 +349,26 @@ prop_brokenRcGetsWarning = result == [1134, 2086]
prop_sourcePathRedirectsName = result == [2086] prop_sourcePathRedirectsName = result == [2086]
where where
f "dir/myscript" "lib" = return "foo/lib" f "dir/myscript" _ "lib" = return "foo/lib"
result = checkWithIncludesAndSourcePath [("foo/lib", "echo $1")] f emptyCheckSpec { result = checkWithIncludesAndSourcePath [("foo/lib", "echo $1")] f emptyCheckSpec {
csScript = "#!/bin/bash\nsource lib", csScript = "#!/bin/bash\nsource lib",
csFilename = "dir/myscript", csFilename = "dir/myscript",
csCheckSourced = True csCheckSourced = True
} }
prop_sourcePathAddsAnnotation = result == [2086]
where
f "dir/myscript" ["mypath"] "lib" = return "foo/lib"
result = checkWithIncludesAndSourcePath [("foo/lib", "echo $1")] f emptyCheckSpec {
csScript = "#!/bin/bash\n# shellcheck source-path=mypath\nsource lib",
csFilename = "dir/myscript",
csCheckSourced = True
}
prop_sourcePathRedirectsDirective = result == [2086] prop_sourcePathRedirectsDirective = result == [2086]
where where
f "dir/myscript" "lib" = return "foo/lib" f "dir/myscript" _ "lib" = return "foo/lib"
f _ _ = return "/dev/null" f _ _ _ = return "/dev/null"
result = checkWithIncludesAndSourcePath [("foo/lib", "echo $1")] f emptyCheckSpec { result = checkWithIncludesAndSourcePath [("foo/lib", "echo $1")] f emptyCheckSpec {
csScript = "#!/bin/bash\n# shellcheck source=lib\nsource kittens", csScript = "#!/bin/bash\n# shellcheck source=lib\nsource kittens",
csFilename = "dir/myscript", csFilename = "dir/myscript",

View File

@ -73,8 +73,12 @@ import qualified Data.Map as Map
data SystemInterface m = SystemInterface { data SystemInterface m = SystemInterface {
-- Read a file by filename, or return an error -- Read a file by filename, or return an error
siReadFile :: String -> m (Either ErrorMessage String), siReadFile :: String -> m (Either ErrorMessage String),
-- Given the current script and a sourced file, find the sourced file -- Given:
siFindSource :: String -> String -> m FilePath, -- the current script,
-- a list of source-path annotations in effect,
-- and a sourced file,
-- find the sourced file
siFindSource :: String -> [String] -> String -> m FilePath,
-- Get the configuration file (name, contents) for a filename -- Get the configuration file (name, contents) for a filename
siGetConfig :: String -> m (Maybe (FilePath, String)) siGetConfig :: String -> m (Maybe (FilePath, String))
} }
@ -297,7 +301,7 @@ mockedSystemInterface files = SystemInterface {
case filter ((== file) . fst) files of case filter ((== file) . fst) files of
[] -> return $ Left "File not included in mock." [] -> return $ Left "File not included in mock."
[(_, contents)] -> return $ Right contents [(_, contents)] -> return $ Right contents
fs _ file = return file fs _ _ file = return file
mockRcFile rcfile mock = mock { mockRcFile rcfile mock = mock {
siGetConfig = const . return $ Just (".shellcheckrc", rcfile) siGetConfig = const . return $ Just (".shellcheckrc", rcfile)

View File

@ -264,6 +264,15 @@ shouldIgnoreCode code = do
disabling' (DisableComment n) = code == n disabling' (DisableComment n) = code == n
disabling' _ = False disabling' _ = False
getCurrentAnnotations includeSource =
concatMap get . takeWhile (not . isBoundary) <$> getCurrentContexts
where
get (ContextAnnotation list) = list
get _ = []
isBoundary (ContextSource _) = not includeSource
isBoundary _ = False
shouldFollow file = do shouldFollow file = do
context <- getCurrentContexts context <- getCurrentContexts
if any isThisFile context if any isThisFile context
@ -966,7 +975,7 @@ readAnnotationWithoutPrefix = do
where where
readKey = do readKey = do
keyPos <- getPosition keyPos <- getPosition
key <- many1 letter key <- many1 (letter <|> char '-')
char '=' <|> fail "Expected '=' after directive key" char '=' <|> fail "Expected '=' after directive key"
annotations <- case key of annotations <- case key of
"disable" -> readCode `sepBy` char ',' "disable" -> readCode `sepBy` char ','
@ -980,6 +989,10 @@ readAnnotationWithoutPrefix = do
filename <- many1 $ noneOf " \n" filename <- many1 $ noneOf " \n"
return [SourceOverride filename] return [SourceOverride filename]
"source-path" -> do
dirname <- many1 $ noneOf " \n"
return [SourcePath dirname]
"shell" -> do "shell" -> do
pos <- getPosition pos <- getPosition
shell <- many1 $ noneOf " \n" shell <- many1 $ noneOf " \n"
@ -2079,6 +2092,7 @@ readSource t@(T_Redirecting _ _ (T_SimpleCommand cmdId _ (cmd:file':rest'))) = d
proceed <- shouldFollow filename proceed <- shouldFollow filename
if not proceed if not proceed
then do then do
-- FIXME: This actually gets squashed without -a
parseNoteAtId (getId file) InfoC 1093 parseNoteAtId (getId file) InfoC 1093
"This file appears to be recursively sourced. Ignoring." "This file appears to be recursively sourced. Ignoring."
return t return t
@ -2089,7 +2103,8 @@ readSource t@(T_Redirecting _ _ (T_SimpleCommand cmdId _ (cmd:file':rest'))) = d
then return (Right "") then return (Right "")
else do else do
currentScript <- Mr.asks currentFilename currentScript <- Mr.asks currentFilename
filename' <- system $ siFindSource sys currentScript filename paths <- mapMaybe getSourcePath <$> getCurrentAnnotations True
filename' <- system $ siFindSource sys currentScript paths filename
system $ siReadFile sys filename' system $ siReadFile sys filename'
case input of case input of
Left err -> do Left err -> do
@ -2118,6 +2133,11 @@ readSource t@(T_Redirecting _ _ (T_SimpleCommand cmdId _ (cmd:file':rest'))) = d
x -> file x -> file
getFile file _ = file getFile file _ = file
getSourcePath t =
case t of
SourcePath x -> Just x
_ -> Nothing
subRead name script = subRead name script =
withContext (ContextSource name) $ withContext (ContextSource name) $
inSeparateContext $ inSeparateContext $