Add support for `.shellcheckrc` files

This commit is contained in:
Vidar Holen 2019-03-03 18:53:43 -08:00
parent 293c3b27b8
commit 581bcc3907
7 changed files with 226 additions and 24 deletions

View File

@ -2,6 +2,7 @@
### Added ### Added
- Preliminary support for fix suggestions - Preliminary support for fix suggestions
- 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`
- SC2246: Warn if a shebang's interpreter ends with / - SC2246: Warn if a shebang's interpreter ends with /
- SC2245: Warn that Ksh ignores all but the first glob result in `[` - SC2245: Warn that Ksh ignores all but the first glob result in `[`
- SC2243/SC2244: Suggest using explicit -n for `[ $foo ]` - SC2243/SC2244: Suggest using explicit -n for `[ $foo ]`

View File

@ -96,14 +96,15 @@ executable shellcheck
array, array,
base >= 4 && < 5, base >= 4 && < 5,
bytestring, bytestring,
deepseq >= 1.4.0.0,
ShellCheck,
containers, containers,
deepseq >= 1.4.0.0,
directory, directory,
mtl >= 2.2.1, mtl >= 2.2.1,
filepath,
parsec >= 3.0, parsec >= 3.0,
QuickCheck >= 2.7.4, QuickCheck >= 2.7.4,
regex-tdfa regex-tdfa,
ShellCheck
main-is: shellcheck.hs main-is: shellcheck.hs
test-suite test-shellcheck test-suite test-shellcheck
@ -113,13 +114,14 @@ test-suite test-shellcheck
array, array,
base >= 4 && < 5, base >= 4 && < 5,
bytestring, bytestring,
deepseq >= 1.4.0.0,
ShellCheck,
containers, containers,
deepseq >= 1.4.0.0,
directory, directory,
mtl >= 2.2.1, mtl >= 2.2.1,
filepath,
parsec, parsec,
QuickCheck >= 2.7.4, QuickCheck >= 2.7.4,
regex-tdfa regex-tdfa,
ShellCheck
main-is: test/shellcheck.hs main-is: test/shellcheck.hs

View File

@ -63,6 +63,10 @@ not warn at all, as `ksh` supports decimals in arithmetic contexts.
standard output. Subsequent **-f** options are ignored, see **FORMATS** standard output. Subsequent **-f** options are ignored, see **FORMATS**
below for more information. below for more information.
**--norc**
: Don't try to look for .shellcheckrc configuration files.
**-S**\ *SEVERITY*,\ **--severity=***severity* **-S**\ *SEVERITY*,\ **--severity=***severity*
: Specify minimum severity of errors to consider. Valid values are *error*, : Specify minimum severity of errors to consider. Valid values are *error*,
@ -192,6 +196,31 @@ Valid keys are:
files meant to be included (and thus lacking a shebang), or possibly files meant to be included (and thus lacking a shebang), or possibly
as a more targeted alternative to 'disable=2039'. as a more targeted alternative to 'disable=2039'.
# RC FILES
Unless `--norc` is used, ShellCheck will look for a file `.shellcheckrc` or
`shellcheckrc` in the script's directory and each parent directory. If found,
it will read `key=value` pairs from it and treat them as file-wide directives.
Here is an example `.shellcheckrc`:
# Don't suggest using -n in [ $var ]
disable=SC2244
# Allow using `which` since it gives full paths and is common enough
disable=SC2230
If no `.shellcheckrc` is found in any of the parent directories, ShellCheck
will look in `~/.shellcheckrc` followed by the XDG config directory
(usually `~/.config/shellcheckrc`) on Unix, or %APPDATA%/shellcheckrc` on
Windows. Only the first file found will be used.
Note for Snap users: the Snap sandbox disallows access to hidden files.
Use `shellcheckrc` without the dot instead.
Note for Docker users: ShellCheck will only be able to look for files that
are mounted in the container, so `~/.shellcheckrc` will not be read.
# ENVIRONMENT VARIABLES # ENVIRONMENT VARIABLES
The environment variable `SHELLCHECK_OPTS` can be set with default flags: The environment variable `SHELLCHECK_OPTS` can be set with default flags:

View File

@ -47,6 +47,7 @@ import System.Console.GetOpt
import System.Directory import System.Directory
import System.Environment import System.Environment
import System.Exit import System.Exit
import System.FilePath
import System.IO import System.IO
data Flag = Flag String String data Flag = Flag String String
@ -95,6 +96,8 @@ options = [
Option "f" ["format"] Option "f" ["format"]
(ReqArg (Flag "format") "FORMAT") $ (ReqArg (Flag "format") "FORMAT") $
"Output format (" ++ formatList ++ ")", "Output format (" ++ formatList ++ ")",
Option "" ["norc"]
(NoArg $ Flag "norc" "true") "Don't look for .shellcheckrc files",
Option "s" ["shell"] Option "s" ["shell"]
(ReqArg (Flag "shell") "SHELLNAME") (ReqArg (Flag "shell") "SHELLNAME")
"Specify dialect (sh, bash, dash, ksh)", "Specify dialect (sh, bash, dash, ksh)",
@ -330,7 +333,16 @@ parseOption flag options =
} }
} }
_ -> return options Flag "norc" _ ->
return options {
checkSpec = (checkSpec options) {
csIgnoreRC = True
}
}
Flag str _ -> do
printErr $ "Internal error for --" ++ str ++ ". Please file a bug :("
return options
where where
die s = do die s = do
printErr s printErr s
@ -345,12 +357,15 @@ parseOption flag options =
ioInterface options files = do ioInterface options files = do
inputs <- mapM normalize files inputs <- mapM normalize files
cache <- newIORef emptyCache cache <- newIORef emptyCache
configCache <- newIORef ("", Nothing)
return SystemInterface { return SystemInterface {
siReadFile = get cache inputs siReadFile = get cache inputs,
siGetConfig = getConfig configCache
} }
where where
emptyCache :: Map.Map FilePath String emptyCache :: Map.Map FilePath String
emptyCache = Map.empty emptyCache = Map.empty
get cache inputs file = do get cache inputs file = do
map <- readIORef cache map <- readIORef cache
case Map.lookup file map of case Map.lookup file map of
@ -367,7 +382,6 @@ ioInterface options files = do
return $ Right contents return $ Right contents
) `catch` handler ) `catch` handler
else return $ Left (file ++ " was not specified as input (see shellcheck -x).") else return $ Left (file ++ " was not specified as input (see shellcheck -x).")
where where
handler :: IOException -> IO (Either ErrorMessage String) handler :: IOException -> IO (Either ErrorMessage String)
handler ex = return . Left $ show ex handler ex = return . Left $ show ex
@ -385,6 +399,58 @@ ioInterface options files = do
fallback :: FilePath -> IOException -> IO FilePath fallback :: FilePath -> IOException -> IO FilePath
fallback path _ = return path fallback path _ = return path
-- Returns the name and contents of .shellcheckrc for the given file
getConfig cache filename = do
path <- normalize filename
let dir = takeDirectory path
(previousPath, result) <- readIORef cache
if dir == previousPath
then return result
else do
paths <- getConfigPaths dir
result <- findConfig paths
writeIORef cache (dir, result)
return result
findConfig paths =
case paths of
(file:rest) -> do
contents <- readConfig file
if isJust contents
then return contents
else findConfig rest
[] -> return Nothing
-- Get a list of candidate filenames. This includes .shellcheckrc
-- in all parent directories, plus the user's home dir and xdg dir.
-- The dot is optional for Windows and Snap users.
getConfigPaths dir = do
let next = takeDirectory dir
rest <- if next /= dir
then getConfigPaths next
else defaultPaths `catch`
((const $ return []) :: IOException -> IO [FilePath])
return $ (dir </> ".shellcheckrc") : (dir </> "shellcheckrc") : rest
defaultPaths = do
home <- getAppUserDataDirectory "shellcheckrc"
xdg <- getXdgDirectory XdgConfig "shellcheckrc"
return [home, xdg]
readConfig file = do
exists <- doesPathExist file
if exists
then do
(contents, _) <- inputFile file `catch` handler file
return $ Just (file, contents)
else
return Nothing
where
handler :: FilePath -> IOException -> IO (String, Bool)
handler file err = do
putStrLn $ file ++ ": " ++ show err
return ("", True)
inputFile file = do inputFile file = do
(handle, shouldCache) <- (handle, shouldCache) <-
if file == "-" if file == "-"

View File

@ -72,6 +72,7 @@ checkScript sys spec = do
psFilename = csFilename spec, psFilename = csFilename spec,
psScript = contents, psScript = contents,
psCheckSourced = csCheckSourced spec, psCheckSourced = csCheckSourced spec,
psIgnoreRC = csIgnoreRC spec,
psShellTypeOverride = csShellTypeOverride spec psShellTypeOverride = csShellTypeOverride spec
} }
let parseMessages = prComments result let parseMessages = prComments result
@ -146,6 +147,9 @@ checkOptionIncludes includes src =
csCheckSourced = True csCheckSourced = True
} }
checkWithRc rc = getErrors
(mockRcFile rc $ mockedSystemInterface [])
prop_findsParseIssue = check "echo \"$12\"" == [1037] prop_findsParseIssue = check "echo \"$12\"" == [1037]
prop_commentDisablesParseIssue1 = prop_commentDisablesParseIssue1 =
@ -299,5 +303,34 @@ prop_optionIncludes4 =
-- expect 2086 & 2154, only 2154 included, so only that's reported -- expect 2086 & 2154, only 2154 included, so only that's reported
[2154] == checkOptionIncludes (Just [2154]) "#!/bin/sh\n var='a b'\n echo $var\n echo $bar" [2154] == checkOptionIncludes (Just [2154]) "#!/bin/sh\n var='a b'\n echo $var\n echo $bar"
prop_readsRcFile = result == []
where
result = checkWithRc "disable=2086" emptyCheckSpec {
csScript = "#!/bin/sh\necho $1",
csIgnoreRC = False
}
prop_canUseNoRC = result == [2086]
where
result = checkWithRc "disable=2086" emptyCheckSpec {
csScript = "#!/bin/sh\necho $1",
csIgnoreRC = True
}
prop_NoRCWontLookAtFile = result == [2086]
where
result = checkWithRc (error "Fail") emptyCheckSpec {
csScript = "#!/bin/sh\necho $1",
csIgnoreRC = True
}
prop_brokenRcGetsWarning = result == [1134, 2086]
where
result = checkWithRc "rofl" emptyCheckSpec {
csScript = "#!/bin/sh\necho $1",
csIgnoreRC = False
}
return [] return []
runTests = $quickCheckAll runTests = $quickCheckAll

View File

@ -21,9 +21,9 @@
module ShellCheck.Interface module ShellCheck.Interface
( (
SystemInterface(..) SystemInterface(..)
, CheckSpec(csFilename, csScript, csCheckSourced, csIncludedWarnings, csExcludedWarnings, csShellTypeOverride, csMinSeverity) , CheckSpec(csFilename, csScript, csCheckSourced, csIncludedWarnings, csExcludedWarnings, csShellTypeOverride, csMinSeverity, csIgnoreRC)
, CheckResult(crFilename, crComments) , CheckResult(crFilename, crComments)
, ParseSpec(psFilename, psScript, psCheckSourced, psShellTypeOverride) , ParseSpec(psFilename, psScript, psCheckSourced, psIgnoreRC, psShellTypeOverride)
, ParseResult(prComments, prTokenPositions, prRoot) , ParseResult(prComments, prTokenPositions, prRoot)
, AnalysisSpec(asScript, asShellType, asFallbackShell, asExecutionMode, asCheckSourced, asTokenPositions) , AnalysisSpec(asScript, asShellType, asFallbackShell, asExecutionMode, asCheckSourced, asTokenPositions)
, AnalysisResult(arComments) , AnalysisResult(arComments)
@ -46,6 +46,7 @@ module ShellCheck.Interface
, newPosition , newPosition
, newTokenComment , newTokenComment
, mockedSystemInterface , mockedSystemInterface
, mockRcFile
, newParseSpec , newParseSpec
, emptyCheckSpec , emptyCheckSpec
, newPositionedComment , newPositionedComment
@ -69,9 +70,11 @@ import GHC.Generics (Generic)
import qualified Data.Map as Map import qualified Data.Map as Map
newtype 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),
-- Get the configuration file (name, contents) for a filename
siGetConfig :: String -> m (Maybe (FilePath, String))
} }
-- ShellCheck input and output -- ShellCheck input and output
@ -79,6 +82,7 @@ data CheckSpec = CheckSpec {
csFilename :: String, csFilename :: String,
csScript :: String, csScript :: String,
csCheckSourced :: Bool, csCheckSourced :: Bool,
csIgnoreRC :: Bool,
csExcludedWarnings :: [Integer], csExcludedWarnings :: [Integer],
csIncludedWarnings :: Maybe [Integer], csIncludedWarnings :: Maybe [Integer],
csShellTypeOverride :: Maybe Shell, csShellTypeOverride :: Maybe Shell,
@ -101,6 +105,7 @@ emptyCheckSpec = CheckSpec {
csFilename = "", csFilename = "",
csScript = "", csScript = "",
csCheckSourced = False, csCheckSourced = False,
csIgnoreRC = False,
csExcludedWarnings = [], csExcludedWarnings = [],
csIncludedWarnings = Nothing, csIncludedWarnings = Nothing,
csShellTypeOverride = Nothing, csShellTypeOverride = Nothing,
@ -112,6 +117,7 @@ newParseSpec = ParseSpec {
psFilename = "", psFilename = "",
psScript = "", psScript = "",
psCheckSourced = False, psCheckSourced = False,
psIgnoreRC = False,
psShellTypeOverride = Nothing psShellTypeOverride = Nothing
} }
@ -120,6 +126,7 @@ data ParseSpec = ParseSpec {
psFilename :: String, psFilename :: String,
psScript :: String, psScript :: String,
psCheckSourced :: Bool, psCheckSourced :: Bool,
psIgnoreRC :: Bool,
psShellTypeOverride :: Maybe Shell psShellTypeOverride :: Maybe Shell
} deriving (Show, Eq) } deriving (Show, Eq)
@ -279,7 +286,8 @@ data ColorOption =
-- For testing -- For testing
mockedSystemInterface :: [(String, String)] -> SystemInterface Identity mockedSystemInterface :: [(String, String)] -> SystemInterface Identity
mockedSystemInterface files = SystemInterface { mockedSystemInterface files = SystemInterface {
siReadFile = rf siReadFile = rf,
siGetConfig = const $ return Nothing
} }
where where
rf file = rf file =
@ -287,3 +295,7 @@ mockedSystemInterface files = SystemInterface {
[] -> return $ Left "File not included in mock." [] -> return $ Left "File not included in mock."
[(_, contents)] -> return $ Right contents [(_, contents)] -> return $ Right contents
mockRcFile rcfile mock = mock {
siGetConfig = const . return $ Just (".shellcheckrc", rcfile)
}

View File

@ -113,6 +113,7 @@ allspacing = do
allspacingOrFail = do allspacingOrFail = do
s <- allspacing s <- allspacing
when (null s) $ fail "Expected whitespace" when (null s) $ fail "Expected whitespace"
return s
readUnicodeQuote = do readUnicodeQuote = do
start <- startSpan start <- startSpan
@ -306,6 +307,8 @@ initialSystemState = SystemState {
data Environment m = Environment { data Environment m = Environment {
systemInterface :: SystemInterface m, systemInterface :: SystemInterface m,
checkSourced :: Bool, checkSourced :: Bool,
ignoreRC :: Bool,
currentFilename :: String,
shellTypeOverride :: Maybe Shell shellTypeOverride :: Maybe Shell
} }
@ -949,9 +952,12 @@ prop_readAnnotation6 = isOk readAnnotation "# shellcheck disable=SC1234 # shellc
readAnnotation = called "shellcheck directive" $ do readAnnotation = called "shellcheck directive" $ do
try readAnnotationPrefix try readAnnotationPrefix
many1 linewhitespace many1 linewhitespace
readAnnotationWithoutPrefix
readAnnotationWithoutPrefix = do
values <- many1 readKey values <- many1 readKey
optional readAnyComment optional readAnyComment
void linefeed <|> do void linefeed <|> eof <|> do
parseNote ErrorC 1125 "Invalid key=value pair? Ignoring the rest of this directive starting here." parseNote ErrorC 1125 "Invalid key=value pair? Ignoring the rest of this directive starting here."
many (noneOf "\n") many (noneOf "\n")
void linefeed <|> eof void linefeed <|> eof
@ -2104,7 +2110,7 @@ readSource t@(T_Redirecting _ _ (T_SimpleCommand cmdId _ (cmd:file:_))) = do
subRead name script = subRead name script =
withContext (ContextSource name) $ withContext (ContextSource name) $
inSeparateContext $ inSeparateContext $
subParse (initialPos name) readScript script subParse (initialPos name) (readScriptFile True) script
readSource t = return t readSource t = return t
@ -2980,12 +2986,55 @@ verifyEof = eof <|> choice [
try (lookAhead p) try (lookAhead p)
action action
prop_readScript1 = isOk readScriptFile "#!/bin/bash\necho hello world\n"
prop_readScript2 = isWarning readScriptFile "#!/bin/bash\r\necho hello world\n" readConfigFile :: Monad m => FilePath -> SCParser m [Annotation]
prop_readScript3 = isWarning readScriptFile "#!/bin/bash\necho hello\xA0world" readConfigFile filename = do
prop_readScript4 = isWarning readScriptFile "#!/usr/bin/perl\nfoo=(" shouldIgnore <- Mr.asks ignoreRC
prop_readScript5 = isOk readScriptFile "#!/bin/bash\n#This is an empty script\n\n" if shouldIgnore then return [] else read' filename
readScriptFile = do where
read' filename = do
sys <- Mr.asks systemInterface
contents <- system $ siGetConfig sys filename
case contents of
Nothing -> return []
Just (file, str) -> readConfig file str
readConfig filename contents = do
result <- lift $ runParserT readConfigKVs initialUserState filename contents
case result of
Right result ->
return result
Left err -> do
parseProblem ErrorC 1134 $ errorFor filename err
return []
errorFor filename err =
let line = "line " ++ (show . sourceLine $ errorPos err)
suggestion = getStringFromParsec $ errorMessages err
in
"Failed to process " ++ filename ++ ", " ++ line ++ ": "
++ suggestion
prop_readConfigKVs1 = isOk readConfigKVs "disable=1234"
prop_readConfigKVs2 = isOk readConfigKVs "# Comment\ndisable=1234 # Comment\n"
prop_readConfigKVs3 = isOk readConfigKVs ""
prop_readConfigKVs4 = isOk readConfigKVs "\n\n\n\n\t \n"
prop_readConfigKVs5 = isOk readConfigKVs "# shellcheck accepts annotation-like comments in rc files\ndisable=1234"
readConfigKVs = do
anySpacingOrComment
annotations <- many (readAnnotationWithoutPrefix <* anySpacingOrComment)
eof
return $ concat annotations
anySpacingOrComment =
many (void allspacingOrFail <|> void readAnyComment)
prop_readScript1 = isOk readScript "#!/bin/bash\necho hello world\n"
prop_readScript2 = isWarning readScript "#!/bin/bash\r\necho hello world\n"
prop_readScript3 = isWarning readScript "#!/bin/bash\necho hello\xA0world"
prop_readScript4 = isWarning readScript "#!/usr/bin/perl\nfoo=("
prop_readScript5 = isOk readScript "#!/bin/bash\n#This is an empty script\n\n"
readScriptFile sourced = do
start <- startSpan start <- startSpan
pos <- getPosition pos <- getPosition
optional $ do optional $ do
@ -2995,7 +3044,13 @@ readScriptFile = do
sb <- option "" readShebang sb <- option "" readShebang
allspacing allspacing
annotationStart <- startSpan annotationStart <- startSpan
annotations <- readAnnotations fileAnnotations <- readAnnotations
rcAnnotations <- if sourced
then return []
else do
filename <- Mr.asks currentFilename
readConfigFile filename
let annotations = fileAnnotations ++ rcAnnotations
annotationId <- endSpan annotationStart annotationId <- endSpan annotationStart
let shellAnnotationSpecified = let shellAnnotationSpecified =
any (\x -> case x of ShellOverride {} -> True; _ -> False) annotations any (\x -> case x of ShellOverride {} -> True; _ -> False) annotations
@ -3065,7 +3120,7 @@ readScriptFile = do
readUtf8Bom = called "Byte Order Mark" $ string "\xFEFF" readUtf8Bom = called "Byte Order Mark" $ string "\xFEFF"
readScript = readScriptFile readScript = readScriptFile False
-- Interactively run a specific parser in ghci: -- Interactively run a specific parser in ghci:
-- debugParse readSimpleCommand "echo 'hello world'" -- debugParse readSimpleCommand "echo 'hello world'"
@ -3100,6 +3155,8 @@ testEnvironment =
Environment { Environment {
systemInterface = (mockedSystemInterface []), systemInterface = (mockedSystemInterface []),
checkSourced = False, checkSourced = False,
currentFilename = "myscript",
ignoreRC = False,
shellTypeOverride = Nothing shellTypeOverride = Nothing
} }
@ -3275,6 +3332,8 @@ parseScript sys spec =
env = Environment { env = Environment {
systemInterface = sys, systemInterface = sys,
checkSourced = psCheckSourced spec, checkSourced = psCheckSourced spec,
currentFilename = psFilename spec,
ignoreRC = psIgnoreRC spec,
shellTypeOverride = psShellTypeOverride spec shellTypeOverride = psShellTypeOverride spec
} }