Replace verbose checks with optional checks

This commit is contained in:
Vidar Holen 2019-05-12 19:14:04 -07:00
parent 58205a3573
commit 5fb1da6814
11 changed files with 229 additions and 74 deletions

View File

@ -3,7 +3,8 @@
- Preliminary support for fix suggestions
- Files containing Bats tests can now be checked
- Directory wide directives can now be placed in a `.shellcheckrc`
- Verbose mode: Use `-S verbose` for especially pedantic suggestions
- Optional checks: Use `--list-optional` to show a list of tests,
Enable with `-o` flags or `enable=name` directives
- 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)

View File

@ -63,10 +63,21 @@ not warn at all, as `ksh` supports decimals in arithmetic contexts.
standard output. Subsequent **-f** options are ignored, see **FORMATS**
below for more information.
**--list-optional**
: Output a list of known optional checks. These can be enabled with **-o**
flags or **enable** directives.
**--norc**
: Don't try to look for .shellcheckrc configuration files.
**-o**\ *NAME1*[,*NAME2*...],\ **--enable=***NAME1*[,*NAME2*...]
: Enable optional checks. The special name *all* enables all of them.
Subsequent **-o** options accumulate. This is equivalent to specifying
**enable** directives.
**-P**\ *SOURCEPATH*,\ **--source-path=***SOURCEPATH*
: Specify paths to search for sourced files, separated by `:` on Unix and
@ -83,7 +94,7 @@ not warn at all, as `ksh` supports decimals in arithmetic contexts.
**-S**\ *SEVERITY*,\ **--severity=***severity*
: Specify minimum severity of errors to consider. Valid values in order of
severity are *error*, *warning*, *info*, *style* and *verbose*.
severity are *error*, *warning*, *info* and *style*.
The default is *style*.
**-V**,\ **--version**
@ -163,8 +174,9 @@ not warn at all, as `ksh` supports decimals in arithmetic contexts.
# DIRECTIVES
ShellCheck directives can be specified as comments in the shell script
before a command or block:
ShellCheck directives can be specified as comments in the shell script.
If they appear before the first command, they are considered file-wide.
Otherwise, they apply to the immediately following command or block:
# shellcheck key=value key=value
command-or-structure
@ -194,6 +206,10 @@ Valid keys are:
The command can be a simple command like `echo foo`, or a compound command
like a function definition, subshell block or loop.
**enable**
: Enable an optional check by name, as listed with **--list-optional**.
Only file-wide `enable` directives are considered.
**source**
: Overrides the filename included by a `source`/`.` statement. This can be
used to tell shellcheck where to look for a file whose name is determined
@ -224,6 +240,9 @@ Here is an example `.shellcheckrc`:
source-path=SCRIPTDIR
source-path=/mnt/chroot
# Turn on warnings for unquoted variables with safe values
enable=quote-safe-variables
# Allow using `which` since it gives full paths and is common enough
disable=SC2230

View File

@ -17,6 +17,7 @@
You should have received a copy of the GNU General Public License
along with this program. If not, see <https://www.gnu.org/licenses/>.
-}
import qualified ShellCheck.Analyzer
import ShellCheck.Checker
import ShellCheck.Data
import ShellCheck.Interface
@ -98,8 +99,13 @@ options = [
Option "f" ["format"]
(ReqArg (Flag "format") "FORMAT") $
"Output format (" ++ formatList ++ ")",
Option "" ["list-optional"]
(NoArg $ Flag "list-optional" "true") "List checks disabled by default",
Option "" ["norc"]
(NoArg $ Flag "norc" "true") "Don't look for .shellcheckrc files",
Option "o" ["enable"]
(ReqArg (Flag "enable") "check1,check2..")
"List of optional checks to enable (or 'all')",
Option "P" ["source-path"]
(ReqArg (Flag "source-path") "SOURCEPATHS")
"Specify path when looking for sourced files (\"SCRIPTDIR\" for script's dir)",
@ -108,7 +114,7 @@ options = [
"Specify dialect (sh, bash, dash, ksh)",
Option "S" ["severity"]
(ReqArg (Flag "severity") "SEVERITY")
"Minimum severity of errors to consider (error, warning, info, style, verbose)",
"Minimum severity of errors to consider (error, warning, info, style)",
Option "V" ["version"]
(NoArg $ Flag "version" "true") "Print version information",
Option "W" ["wiki-link-count"]
@ -259,8 +265,7 @@ parseSeverityOption value =
("error", ErrorC),
("warning", WarningC),
("info", InfoC),
("style", StyleC),
("verbose", VerboseC)
("style", StyleC)
]
parseOption flag options =
@ -299,6 +304,10 @@ parseOption flag options =
liftIO printVersion
throwError NoProblems
Flag "list-optional" _ -> do
liftIO printOptional
throwError NoProblems
Flag "help" _ -> do
liftIO $ putStrLn getUsageInfo
throwError NoProblems
@ -352,6 +361,13 @@ parseOption flag options =
}
}
Flag "enable" value ->
let cs = checkSpec options in return options {
checkSpec = cs {
csOptionalChecks = (csOptionalChecks cs) ++ split ',' value
}
}
-- This flag is handled specially in 'process'
Flag "format" _ -> return options
@ -547,3 +563,14 @@ printVersion = do
putStrLn $ "version: " ++ shellcheckVersion
putStrLn "license: GNU General Public License, version 3"
putStrLn "website: https://www.shellcheck.net"
printOptional = do
mapM f list
where
list = sortOn cdName ShellCheck.Analyzer.optionalChecks
f item = do
putStrLn $ "name: " ++ cdName item
putStrLn $ "desc: " ++ cdDescription item
putStrLn $ "example: " ++ cdPositive item
putStrLn $ "fix: " ++ cdNegative item
putStrLn ""

View File

@ -144,6 +144,7 @@ data Token =
data Annotation =
DisableComment Integer
| EnableComment String
| SourceOverride String
| ShellOverride String
| SourcePath String

View File

@ -19,7 +19,7 @@
-}
{-# LANGUAGE TemplateHaskell #-}
{-# LANGUAGE FlexibleContexts #-}
module ShellCheck.Analytics (runAnalytics, ShellCheck.Analytics.runTests) where
module ShellCheck.Analytics (runAnalytics, optionalChecks, ShellCheck.Analytics.runTests) where
import ShellCheck.AST
import ShellCheck.ASTLib
@ -49,11 +49,9 @@ import Test.QuickCheck.Test (quickCheckWithResult, stdArgs, maxSuccess)
-- Checks that are run on the AST root
treeChecks :: [Parameters -> Token -> [TokenComment]]
treeChecks = [
runNodeAnalysis
(\p t -> (mapM_ ((\ f -> f t) . (\ f -> f p))
nodeChecks))
nodeChecksToTreeCheck nodeChecks
,subshellAssignmentCheck
,checkVerboseSpacefulness
,checkSpacefulness
,checkQuotesInLiterals
,checkShebangParameters
,checkFunctionsUsedExternally
@ -69,7 +67,14 @@ treeChecks = [
runAnalytics :: AnalysisSpec -> [TokenComment]
runAnalytics options =
runList options treeChecks
runList options treeChecks ++ runList options optionalChecks
where
root = asScript options
optionals = getEnableDirectives root ++ asOptionalChecks options
optionalChecks =
if "all" `elem` optionals
then map snd optionalTreeChecks
else mapMaybe (\c -> Map.lookup c optionalCheckMap) optionals
runList :: AnalysisSpec -> [Parameters -> Token -> [TokenComment]]
-> [TokenComment]
@ -79,13 +84,27 @@ runList spec list = notes
params = makeParameters spec
notes = concatMap (\f -> f params root) list
getEnableDirectives root =
case root of
T_Annotation _ list _ -> mapMaybe getEnable list
_ -> []
where
getEnable t =
case t of
EnableComment s -> return s
_ -> Nothing
checkList l t = concatMap (\f -> f t) l
-- Checks that are run on each node in the AST
runNodeAnalysis f p t = execWriter (doAnalysis (f p) t)
-- Perform multiple node checks in a single iteration over the tree
nodeChecksToTreeCheck checkList =
runNodeAnalysis
(\p t -> (mapM_ ((\ f -> f t) . (\ f -> f p))
checkList))
nodeChecks :: [Parameters -> Token -> Writer [TokenComment] ()]
nodeChecks = [
checkUuoc
@ -170,11 +189,46 @@ nodeChecks = [
,checkSubshelledTests
,checkInvertedStringTest
,checkRedirectionToCommand
,checkNullaryExpansionTest
,checkDollarQuoteParen
,checkDefaultCase
]
optionalChecks = map fst optionalTreeChecks
prop_verifyOptionalExamples = all check optionalTreeChecks
where
check (desc, check) =
verifyTree check (cdPositive desc)
&& verifyNotTree check (cdNegative desc)
optionalTreeChecks :: [(CheckDescription, (Parameters -> Token -> [TokenComment]))]
optionalTreeChecks = [
(newCheckDescription {
cdName = "quote-safe-variables",
cdDescription = "Suggest quoting variables without metacharacters",
cdPositive = "var=hello; echo $var",
cdNegative = "var=hello; echo \"$var\""
}, checkVerboseSpacefulness)
,(newCheckDescription {
cdName = "avoid-nullary-conditions",
cdDescription = "Suggest explicitly using -n in `[ $var ]`",
cdPositive = "[ \"$var\" ]",
cdNegative = "[ -n \"$var\" ]"
}, nodeChecksToTreeCheck [checkNullaryExpansionTest])
,(newCheckDescription {
cdName = "add-default-case",
cdDescription = "Suggest adding a default case in `case` statements",
cdPositive = "case $? in 0) echo 'Success';; esac",
cdNegative = "case $? in 0) echo 'Success';; *) echo 'Fail' ;; esac"
}, nodeChecksToTreeCheck [checkDefaultCase])
]
optionalCheckMap :: Map.Map String (Parameters -> Token -> [TokenComment])
optionalCheckMap = Map.fromList $ map item optionalTreeChecks
where
item (desc, check) = (cdName desc, check)
wouldHaveBeenGlob s = '*' `elem` s
@ -1650,12 +1704,10 @@ prop_checkSpacefulness2 = verifyNotTree checkSpacefulness "a='cow moo'; [[ $a ]]
prop_checkSpacefulness3 = verifyNotTree checkSpacefulness "a='cow*.mp3'; echo \"$a\""
prop_checkSpacefulness4 = verifyTree checkSpacefulness "for f in *.mp3; do echo $f; done"
prop_checkSpacefulness4a= verifyNotTree checkSpacefulness "foo=3; foo=$(echo $foo)"
prop_checkSpacefulness4v= verifyTree checkVerboseSpacefulness "foo=3; foo=$(echo $foo)"
prop_checkSpacefulness5 = verifyTree checkSpacefulness "a='*'; b=$a; c=lol${b//foo/bar}; echo $c"
prop_checkSpacefulness6 = verifyTree checkSpacefulness "a=foo$(lol); echo $a"
prop_checkSpacefulness7 = verifyTree checkSpacefulness "a=foo\\ bar; rm $a"
prop_checkSpacefulness8 = verifyNotTree checkSpacefulness "a=foo\\ bar; a=foo; rm $a"
prop_checkSpacefulness8v= verifyTree checkVerboseSpacefulness "a=foo\\ bar; a=foo; rm $a"
prop_checkSpacefulness10= verifyTree checkSpacefulness "rm $1"
prop_checkSpacefulness11= verifyTree checkSpacefulness "rm ${10//foo/bar}"
prop_checkSpacefulness12= verifyNotTree checkSpacefulness "(( $1 + 3 ))"
@ -1675,7 +1727,6 @@ prop_checkSpacefulness25= verifyTree checkSpacefulness "a='s/[0-9]//g'; sed $a"
prop_checkSpacefulness26= verifyTree checkSpacefulness "a='foo bar'; echo {1,2,$a}"
prop_checkSpacefulness27= verifyNotTree checkSpacefulness "echo ${a:+'foo'}"
prop_checkSpacefulness28= verifyNotTree checkSpacefulness "exec {n}>&1; echo $n"
prop_checkSpacefulness28v = verifyTree checkVerboseSpacefulness "exec {n}>&1; echo $n"
prop_checkSpacefulness29= verifyNotTree checkSpacefulness "n=$(stuff); exec {n}>&-;"
prop_checkSpacefulness30= verifyTree checkSpacefulness "file='foo bar'; echo foo > $file;"
prop_checkSpacefulness31= verifyNotTree checkSpacefulness "echo \"`echo \\\"$1\\\"`\""
@ -1684,22 +1735,53 @@ prop_checkSpacefulness33= verifyTree checkSpacefulness "for file; do echo $file;
prop_checkSpacefulness34= verifyTree checkSpacefulness "declare foo$n=$1"
prop_checkSpacefulness35= verifyNotTree checkSpacefulness "echo ${1+\"$1\"}"
prop_checkSpacefulness36= verifyNotTree checkSpacefulness "arg=$#; echo $arg"
prop_checkSpacefulness36v = verifyTree checkVerboseSpacefulness "arg=$#; echo $arg"
prop_checkSpacefulness37= verifyNotTree checkSpacefulness "@test 'status' {\n [ $status -eq 0 ]\n}"
prop_checkSpacefulness37v = verifyTree checkVerboseSpacefulness "@test 'status' {\n [ $status -eq 0 ]\n}"
-- This is slightly awkward because we want the tests to
-- discriminate between normal and verbose output.
checkSpacefulness params t = checkSpacefulness' False params t
checkVerboseSpacefulness params t = checkSpacefulness' True params t
checkSpacefulness' alsoVerbose params t =
-- This is slightly awkward because we want to support structured
-- optional checks based on nearly the same logic
checkSpacefulness params = checkSpacefulness' onFind params
where
emit x = tell [x]
onFind spaces token _ =
when spaces $
if isDefaultAssignment (parentMap params) token
then
emit $ makeComment InfoC (getId token) 2223
"This default assignment may cause DoS due to globbing. Quote it."
else
emit $ makeCommentWithFix InfoC (getId token) 2086
"Double quote to prevent globbing and word splitting."
(addDoubleQuotesAround params token)
isDefaultAssignment parents token =
let modifier = getBracedModifier $ bracedString token in
any (`isPrefixOf` modifier) ["=", ":="]
&& isParamTo parents ":" token
prop_checkSpacefulness4v= verifyTree checkVerboseSpacefulness "foo=3; foo=$(echo $foo)"
prop_checkSpacefulness8v= verifyTree checkVerboseSpacefulness "a=foo\\ bar; a=foo; rm $a"
prop_checkSpacefulness28v = verifyTree checkVerboseSpacefulness "exec {n}>&1; echo $n"
prop_checkSpacefulness36v = verifyTree checkVerboseSpacefulness "arg=$#; echo $arg"
checkVerboseSpacefulness params = checkSpacefulness' onFind params
where
onFind spaces token name =
when (not spaces && name `notElem` specialVariablesWithoutSpaces) $
tell [makeCommentWithFix StyleC (getId token) 2248
"Prefer double quoting even when variables don't contain special characters."
(addDoubleQuotesAround params token)]
addDoubleQuotesAround params token = (surroundWidth (getId token) params "\"")
checkSpacefulness'
:: (Bool -> Token -> String -> Writer [TokenComment] ()) ->
Parameters -> Token -> [TokenComment]
checkSpacefulness' onFind params t =
doVariableFlowAnalysis readF writeF (Map.fromList defaults) (variableFlow params)
where
defaults = zip variablesWithoutSpaces (repeat False)
hasSpaces name = do
map <- get
return $ Map.findWithDefault True name map
hasSpaces name = gets (Map.findWithDefault True name)
setSpaces name bool =
modify $ Map.insert name bool
@ -1714,24 +1796,9 @@ checkSpacefulness' alsoVerbose params t =
&& not (isQuotedAlternativeReference token)
&& not (usedAsCommandName parents token)
return . execWriter $ when needsQuoting $
if spaces
then
if isDefaultAssignment (parentMap params) token
then
emit $ makeComment InfoC (getId token) 2223
"This default assignment may cause DoS due to globbing. Quote it."
else
emit $ makeCommentWithFix InfoC (getId token) 2086
"Double quote to prevent globbing and word splitting."
(fixFor token)
else
when (alsoVerbose && name `notElem` specialVariablesWithoutSpaces) $
emit $ makeCommentWithFix VerboseC (getId token) 2248
"Prefer double quoting even when variables don't contain special characters."
(fixFor token)
return . execWriter $ when needsQuoting $ onFind spaces token name
where
fixFor token = (surroundWidth (getId token) params "\"")
emit x = tell [x]
writeF _ _ name (DataString SourceExternal) = setSpaces name True >> return []
@ -1771,12 +1838,6 @@ checkSpacefulness' alsoVerbose params t =
globspace = "*?[] \t\n"
containsAny s = any (`elem` s)
isDefaultAssignment parents token =
let modifier = getBracedModifier $ bracedString token in
isExpansion token
&& any (`isPrefixOf` modifier) ["=", ":="]
&& isParamTo parents ":" token
prop_checkQuotesInLiterals1 = verifyTree checkQuotesInLiterals "param='--foo=\"bar\"'; app $param"
prop_checkQuotesInLiterals1a= verifyTree checkQuotesInLiterals "param=\"--foo='lolbar'\"; app $param"
prop_checkQuotesInLiterals2 = verifyNotTree checkQuotesInLiterals "param='--foo=\"bar\"'; app \"$param\""
@ -3224,11 +3285,11 @@ checkNullaryExpansionTest params t =
TC_Nullary _ _ word ->
case getWordParts word of
[t] | isCommandSubstitution t ->
verboseWithFix id 2243 "Prefer explicit -n to check for output (or run command without [/[[ to check for success)." fix
styleWithFix id 2243 "Prefer explicit -n to check for output (or run command without [/[[ to check for success)." fix
-- If they're constant, you get SC2157 &co
x | all (not . isConstant) x ->
verboseWithFix id 2244 "Prefer explicit -n to check non-empty string (or use =/-ne to check boolean/integer)." fix
styleWithFix id 2244 "Prefer explicit -n to check non-empty string (or use =/-ne to check boolean/integer)." fix
_ -> return ()
where
id = getId word
@ -3256,7 +3317,7 @@ checkDefaultCase _ t =
case t of
T_CaseExpression id _ list ->
unless (any canMatchAny list) $
verbose id 2249 "Consider adding a default *) case, even if it just exits with error."
info id 2249 "Consider adding a default *) case, even if it just exits with error."
_ -> return ()
where
canMatchAny (_, list, _) = any canMatchAny' list

View File

@ -17,7 +17,7 @@
You should have received a copy of the GNU General Public License
along with this program. If not, see <https://www.gnu.org/licenses/>.
-}
module ShellCheck.Analyzer (analyzeScript) where
module ShellCheck.Analyzer (analyzeScript, ShellCheck.Analyzer.optionalChecks) where
import ShellCheck.Analytics
import ShellCheck.AnalyzerLib
@ -43,3 +43,7 @@ checkers params = mconcat $ map ($ params) [
ShellCheck.Checks.Commands.checker,
ShellCheck.Checks.ShellSupport.checker
]
optionalChecks = mconcat $ [
ShellCheck.Analytics.optionalChecks
]

View File

@ -77,14 +77,22 @@ composeAnalyzers :: (a -> Analysis) -> (a -> Analysis) -> a -> Analysis
composeAnalyzers f g x = f x >> g x
data Parameters = Parameters {
hasLastpipe :: Bool, -- Whether this script has the 'lastpipe' option set/default.
hasSetE :: Bool, -- Whether this script has 'set -e' anywhere.
variableFlow :: [StackData], -- A linear (bad) analysis of data flow
parentMap :: Map.Map Id Token, -- A map from Id to parent Token
shellType :: Shell, -- The shell type, such as Bash or Ksh
shellTypeSpecified :: Bool, -- True if shell type was forced via flags
rootNode :: Token, -- The root node of the AST
tokenPositions :: Map.Map Id (Position, Position) -- map from token id to start and end position
-- Whether this script has the 'lastpipe' option set/default.
hasLastpipe :: Bool,
-- Whether this script has 'set -e' anywhere.
hasSetE :: Bool,
-- A linear (bad) analysis of data flow
variableFlow :: [StackData],
-- A map from Id to parent Token
parentMap :: Map.Map Id Token,
-- The shell type, such as Bash or Ksh
shellType :: Shell,
-- True if shell type was forced via flags
shellTypeSpecified :: Bool,
-- The root node of the AST
rootNode :: Token,
-- map from token id to start and end position
tokenPositions :: Map.Map Id (Position, Position)
} deriving (Show)
-- TODO: Cache results of common AST ops here
@ -154,14 +162,11 @@ warn id code str = addComment $ makeComment WarningC id code str
err id code str = addComment $ makeComment ErrorC id code str
info id code str = addComment $ makeComment InfoC id code str
style id code str = addComment $ makeComment StyleC id code str
verbose id code str = addComment $ makeComment VerboseC id code str
warnWithFix :: MonadWriter [TokenComment] m => Id -> Code -> String -> Fix -> m ()
warnWithFix = addCommentWithFix WarningC
styleWithFix :: MonadWriter [TokenComment] m => Id -> Code -> String -> Fix -> m ()
styleWithFix = addCommentWithFix StyleC
verboseWithFix :: MonadWriter [TokenComment] m => Id -> Code -> String -> Fix -> m ()
verboseWithFix = addCommentWithFix VerboseC
addCommentWithFix :: MonadWriter [TokenComment] m => Severity -> Id -> Code -> String -> Fix -> m ()
addCommentWithFix severity id code str fix =

View File

@ -84,7 +84,8 @@ checkScript sys spec = do
asFallbackShell = shellFromFilename $ csFilename spec,
asCheckSourced = csCheckSourced spec,
asExecutionMode = Executed,
asTokenPositions = tokenPositions
asTokenPositions = tokenPositions,
asOptionalChecks = csOptionalChecks spec
} where as = newAnalysisSpec root
let analysisMessages =
fromMaybe [] $
@ -302,6 +303,14 @@ prop_sourcedFileUsesOriginalShellExtension = result == [2079]
csCheckSourced = True
}
prop_canEnableOptionalsWithSpec = result == [2244]
where
result = checkWithSpec [] emptyCheckSpec {
csFilename = "file.sh",
csScript = "#!/bin/sh\n[ \"$1\" ]",
csOptionalChecks = ["avoid-nullary-conditions"]
}
prop_optionIncludes1 =
-- expect 2086, but not included, so nothing reported
null $ checkOptionIncludes (Just [2080]) "#!/bin/sh\n var='a b'\n echo $var"
@ -347,6 +356,12 @@ prop_brokenRcGetsWarning = result == [1134, 2086]
csIgnoreRC = False
}
prop_canEnableOptionalsWithRc = result == [2244]
where
result = checkWithRc "enable=avoid-nullary-conditions" emptyCheckSpec {
csScript = "#!/bin/sh\n[ \"$1\" ]"
}
prop_sourcePathRedirectsName = result == [2086]
where
f "dir/myscript" _ "lib" = return "foo/lib"

View File

@ -47,7 +47,6 @@ severityText pc =
WarningC -> "warning"
InfoC -> "info"
StyleC -> "style"
VerboseC -> "verbose"
-- Realign comments from a tabstop of 8 to 1
makeNonVirtual comments contents =

View File

@ -21,18 +21,18 @@
module ShellCheck.Interface
(
SystemInterface(..)
, CheckSpec(csFilename, csScript, csCheckSourced, csIncludedWarnings, csExcludedWarnings, csShellTypeOverride, csMinSeverity, csIgnoreRC)
, CheckSpec(csFilename, csScript, csCheckSourced, csIncludedWarnings, csExcludedWarnings, csShellTypeOverride, csMinSeverity, csIgnoreRC, csOptionalChecks)
, CheckResult(crFilename, crComments)
, ParseSpec(psFilename, psScript, psCheckSourced, psIgnoreRC, psShellTypeOverride)
, ParseResult(prComments, prTokenPositions, prRoot)
, AnalysisSpec(asScript, asShellType, asFallbackShell, asExecutionMode, asCheckSourced, asTokenPositions)
, AnalysisSpec(asScript, asShellType, asFallbackShell, asExecutionMode, asCheckSourced, asTokenPositions, asOptionalChecks)
, AnalysisResult(arComments)
, FormatterOptions(foColorOption, foWikiLinkCount)
, Shell(Ksh, Sh, Bash, Dash)
, ExecutionMode(Executed, Sourced)
, ErrorMessage
, Code
, Severity(ErrorC, WarningC, InfoC, StyleC, VerboseC)
, Severity(ErrorC, WarningC, InfoC, StyleC)
, Position(posFile, posLine, posColumn)
, Comment(cSeverity, cCode, cMessage)
, PositionedComment(pcStartPos , pcEndPos , pcComment, pcFix)
@ -56,6 +56,8 @@ module ShellCheck.Interface
, InsertionPoint(InsertBefore, InsertAfter)
, Replacement(repStartPos, repEndPos, repString, repPrecedence, repInsertionPoint)
, newReplacement
, CheckDescription(cdName, cdDescription, cdPositive, cdNegative)
, newCheckDescription
) where
import ShellCheck.AST
@ -92,7 +94,8 @@ data CheckSpec = CheckSpec {
csExcludedWarnings :: [Integer],
csIncludedWarnings :: Maybe [Integer],
csShellTypeOverride :: Maybe Shell,
csMinSeverity :: Severity
csMinSeverity :: Severity,
csOptionalChecks :: [String]
} deriving (Show, Eq)
data CheckResult = CheckResult {
@ -115,7 +118,8 @@ emptyCheckSpec = CheckSpec {
csExcludedWarnings = [],
csIncludedWarnings = Nothing,
csShellTypeOverride = Nothing,
csMinSeverity = StyleC
csMinSeverity = StyleC,
csOptionalChecks = []
}
newParseSpec :: ParseSpec
@ -156,6 +160,7 @@ data AnalysisSpec = AnalysisSpec {
asFallbackShell :: Maybe Shell,
asExecutionMode :: ExecutionMode,
asCheckSourced :: Bool,
asOptionalChecks :: [String],
asTokenPositions :: Map.Map Id (Position, Position)
}
@ -165,6 +170,7 @@ newAnalysisSpec token = AnalysisSpec {
asFallbackShell = Nothing,
asExecutionMode = Executed,
asCheckSourced = False,
asOptionalChecks = [],
asTokenPositions = Map.empty
}
@ -187,6 +193,19 @@ newFormatterOptions = FormatterOptions {
foWikiLinkCount = 3
}
data CheckDescription = CheckDescription {
cdName :: String,
cdDescription :: String,
cdPositive :: String,
cdNegative :: String
}
newCheckDescription = CheckDescription {
cdName = "",
cdDescription = "",
cdPositive = "",
cdNegative = ""
}
-- Supporting data types
data Shell = Ksh | Sh | Bash | Dash deriving (Show, Eq)
@ -195,7 +214,7 @@ data ExecutionMode = Executed | Sourced deriving (Show, Eq)
type ErrorMessage = String
type Code = Integer
data Severity = ErrorC | WarningC | InfoC | StyleC | VerboseC
data Severity = ErrorC | WarningC | InfoC | StyleC
deriving (Show, Eq, Ord, Generic, NFData)
data Position = Position {
posFile :: String, -- Filename

View File

@ -985,6 +985,10 @@ readAnnotationWithoutPrefix = do
int <- many1 digit
return $ DisableComment (read int)
"enable" -> readName `sepBy` char ','
where
readName = EnableComment <$> many1 (letter <|> char '-')
"source" -> do
filename <- many1 $ noneOf " \n"
return [SourceOverride filename]