Skip to content

Commit

Permalink
Add support for .shellcheckrc files
Browse files Browse the repository at this point in the history
  • Loading branch information
koalaman committed Mar 4, 2019
1 parent 293c3b2 commit 581bcc3
Show file tree
Hide file tree
Showing 7 changed files with 226 additions and 24 deletions.
1 change: 1 addition & 0 deletions CHANGELOG.md
Original file line number Diff line number Diff line change
Expand Up @@ -2,6 +2,7 @@
### Added
- Preliminary support for fix suggestions
- 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 /
- SC2245: Warn that Ksh ignores all but the first glob result in `[`
- SC2243/SC2244: Suggest using explicit -n for `[ $foo ]`
Expand Down
14 changes: 8 additions & 6 deletions ShellCheck.cabal
Original file line number Diff line number Diff line change
Expand Up @@ -96,14 +96,15 @@ executable shellcheck
array,
base >= 4 && < 5,
bytestring,
deepseq >= 1.4.0.0,
ShellCheck,
containers,
deepseq >= 1.4.0.0,
directory,
mtl >= 2.2.1,
filepath,
parsec >= 3.0,
QuickCheck >= 2.7.4,
regex-tdfa
regex-tdfa,
ShellCheck
main-is: shellcheck.hs

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

29 changes: 29 additions & 0 deletions shellcheck.1.md
Original file line number Diff line number Diff line change
Expand Up @@ -63,6 +63,10 @@ not warn at all, as `ksh` supports decimals in arithmetic contexts.
standard output. Subsequent **-f** options are ignored, see **FORMATS**
below for more information.

**--norc**

: Don't try to look for .shellcheckrc configuration files.

**-S**\ *SEVERITY*,\ **--severity=***severity*

: Specify minimum severity of errors to consider. Valid values are *error*,
Expand Down Expand Up @@ -192,6 +196,31 @@ Valid keys are:
files meant to be included (and thus lacking a shebang), or possibly
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
The environment variable `SHELLCHECK_OPTS` can be set with default flags:

Expand Down
72 changes: 69 additions & 3 deletions shellcheck.hs
Original file line number Diff line number Diff line change
Expand Up @@ -47,6 +47,7 @@ import System.Console.GetOpt
import System.Directory
import System.Environment
import System.Exit
import System.FilePath
import System.IO

data Flag = Flag String String
Expand Down Expand Up @@ -95,6 +96,8 @@ options = [
Option "f" ["format"]
(ReqArg (Flag "format") "FORMAT") $
"Output format (" ++ formatList ++ ")",
Option "" ["norc"]
(NoArg $ Flag "norc" "true") "Don't look for .shellcheckrc files",
Option "s" ["shell"]
(ReqArg (Flag "shell") "SHELLNAME")
"Specify dialect (sh, bash, dash, ksh)",
Expand Down Expand Up @@ -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
die s = do
printErr s
Expand All @@ -345,12 +357,15 @@ parseOption flag options =
ioInterface options files = do
inputs <- mapM normalize files
cache <- newIORef emptyCache
configCache <- newIORef ("", Nothing)
return SystemInterface {
siReadFile = get cache inputs
siReadFile = get cache inputs,
siGetConfig = getConfig configCache
}
where
emptyCache :: Map.Map FilePath String
emptyCache = Map.empty

get cache inputs file = do
map <- readIORef cache
case Map.lookup file map of
Expand All @@ -367,7 +382,6 @@ ioInterface options files = do
return $ Right contents
) `catch` handler
else return $ Left (file ++ " was not specified as input (see shellcheck -x).")

where
handler :: IOException -> IO (Either ErrorMessage String)
handler ex = return . Left $ show ex
Expand All @@ -385,6 +399,58 @@ ioInterface options files = do
fallback :: FilePath -> IOException -> IO FilePath
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
(handle, shouldCache) <-
if file == "-"
Expand Down
33 changes: 33 additions & 0 deletions src/ShellCheck/Checker.hs
Original file line number Diff line number Diff line change
Expand Up @@ -72,6 +72,7 @@ checkScript sys spec = do
psFilename = csFilename spec,
psScript = contents,
psCheckSourced = csCheckSourced spec,
psIgnoreRC = csIgnoreRC spec,
psShellTypeOverride = csShellTypeOverride spec
}
let parseMessages = prComments result
Expand Down Expand Up @@ -146,6 +147,9 @@ checkOptionIncludes includes src =
csCheckSourced = True
}

checkWithRc rc = getErrors
(mockRcFile rc $ mockedSystemInterface [])

prop_findsParseIssue = check "echo \"$12\"" == [1037]

prop_commentDisablesParseIssue1 =
Expand Down Expand Up @@ -299,5 +303,34 @@ prop_optionIncludes4 =
-- 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"


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 []
runTests = $quickCheckAll
22 changes: 17 additions & 5 deletions src/ShellCheck/Interface.hs
Original file line number Diff line number Diff line change
Expand Up @@ -21,9 +21,9 @@
module ShellCheck.Interface
(
SystemInterface(..)
, CheckSpec(csFilename, csScript, csCheckSourced, csIncludedWarnings, csExcludedWarnings, csShellTypeOverride, csMinSeverity)
, CheckSpec(csFilename, csScript, csCheckSourced, csIncludedWarnings, csExcludedWarnings, csShellTypeOverride, csMinSeverity, csIgnoreRC)
, CheckResult(crFilename, crComments)
, ParseSpec(psFilename, psScript, psCheckSourced, psShellTypeOverride)
, ParseSpec(psFilename, psScript, psCheckSourced, psIgnoreRC, psShellTypeOverride)
, ParseResult(prComments, prTokenPositions, prRoot)
, AnalysisSpec(asScript, asShellType, asFallbackShell, asExecutionMode, asCheckSourced, asTokenPositions)
, AnalysisResult(arComments)
Expand All @@ -46,6 +46,7 @@ module ShellCheck.Interface
, newPosition
, newTokenComment
, mockedSystemInterface
, mockRcFile
, newParseSpec
, emptyCheckSpec
, newPositionedComment
Expand All @@ -69,16 +70,19 @@ import GHC.Generics (Generic)
import qualified Data.Map as Map


newtype SystemInterface m = SystemInterface {
data SystemInterface m = SystemInterface {
-- 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
data CheckSpec = CheckSpec {
csFilename :: String,
csScript :: String,
csCheckSourced :: Bool,
csIgnoreRC :: Bool,
csExcludedWarnings :: [Integer],
csIncludedWarnings :: Maybe [Integer],
csShellTypeOverride :: Maybe Shell,
Expand All @@ -101,6 +105,7 @@ emptyCheckSpec = CheckSpec {
csFilename = "",
csScript = "",
csCheckSourced = False,
csIgnoreRC = False,
csExcludedWarnings = [],
csIncludedWarnings = Nothing,
csShellTypeOverride = Nothing,
Expand All @@ -112,6 +117,7 @@ newParseSpec = ParseSpec {
psFilename = "",
psScript = "",
psCheckSourced = False,
psIgnoreRC = False,
psShellTypeOverride = Nothing
}

Expand All @@ -120,6 +126,7 @@ data ParseSpec = ParseSpec {
psFilename :: String,
psScript :: String,
psCheckSourced :: Bool,
psIgnoreRC :: Bool,
psShellTypeOverride :: Maybe Shell
} deriving (Show, Eq)

Expand Down Expand Up @@ -279,11 +286,16 @@ data ColorOption =
-- For testing
mockedSystemInterface :: [(String, String)] -> SystemInterface Identity
mockedSystemInterface files = SystemInterface {
siReadFile = rf
siReadFile = rf,
siGetConfig = const $ return Nothing
}
where
rf file =
case filter ((== file) . fst) files of
[] -> return $ Left "File not included in mock."
[(_, contents)] -> return $ Right contents

mockRcFile rcfile mock = mock {
siGetConfig = const . return $ Just (".shellcheckrc", rcfile)
}

0 comments on commit 581bcc3

Please sign in to comment.