Allow directive/-s to override shebang blacklist (fixes #974)
This commit is contained in:
parent
b8ee7436e5
commit
5005dc0fa1
|
@ -118,10 +118,9 @@ defaultSpec root = AnalysisSpec {
|
||||||
|
|
||||||
pScript s =
|
pScript s =
|
||||||
let
|
let
|
||||||
pSpec = ParseSpec {
|
pSpec = newParseSpec {
|
||||||
psFilename = "script",
|
psFilename = "script",
|
||||||
psScript = s,
|
psScript = s
|
||||||
psCheckSourced = False
|
|
||||||
}
|
}
|
||||||
in prRoot . runIdentity $ parseScript (mockedSystemInterface []) pSpec
|
in prRoot . runIdentity $ parseScript (mockedSystemInterface []) pSpec
|
||||||
|
|
||||||
|
|
|
@ -52,10 +52,11 @@ checkScript sys spec = do
|
||||||
}
|
}
|
||||||
where
|
where
|
||||||
checkScript contents = do
|
checkScript contents = do
|
||||||
result <- parseScript sys ParseSpec {
|
result <- parseScript sys newParseSpec {
|
||||||
psFilename = csFilename spec,
|
psFilename = csFilename spec,
|
||||||
psScript = contents,
|
psScript = contents,
|
||||||
psCheckSourced = csCheckSourced spec
|
psCheckSourced = csCheckSourced spec,
|
||||||
|
psShellTypeOverride = csShellTypeOverride spec
|
||||||
}
|
}
|
||||||
let parseMessages = prComments result
|
let parseMessages = prComments result
|
||||||
let analysisMessages =
|
let analysisMessages =
|
||||||
|
@ -136,6 +137,21 @@ prop_optionDisablesIssue2 =
|
||||||
csExcludedWarnings = [2148, 1037]
|
csExcludedWarnings = [2148, 1037]
|
||||||
}
|
}
|
||||||
|
|
||||||
|
prop_wontParseBadShell =
|
||||||
|
[1071] == check "#!/usr/bin/python\ntrue $1\n"
|
||||||
|
|
||||||
|
prop_optionDisablesBadShebang =
|
||||||
|
null $ getErrors
|
||||||
|
(mockedSystemInterface [])
|
||||||
|
emptyCheckSpec {
|
||||||
|
csScript = "#!/usr/bin/python\ntrue\n",
|
||||||
|
csShellTypeOverride = Just Sh
|
||||||
|
}
|
||||||
|
|
||||||
|
prop_annotationDisablesBadShebang =
|
||||||
|
[] == check "#!/usr/bin/python\n# shellcheck shell=sh\ntrue\n"
|
||||||
|
|
||||||
|
|
||||||
prop_canParseDevNull =
|
prop_canParseDevNull =
|
||||||
[] == check "source /dev/null"
|
[] == check "source /dev/null"
|
||||||
|
|
||||||
|
@ -180,7 +196,7 @@ prop_filewideAnnotation1 = null $
|
||||||
prop_filewideAnnotation2 = null $
|
prop_filewideAnnotation2 = null $
|
||||||
check "#!/bin/sh\n# shellcheck disable=2086\ntrue\necho $1"
|
check "#!/bin/sh\n# shellcheck disable=2086\ntrue\necho $1"
|
||||||
prop_filewideAnnotation3 = null $
|
prop_filewideAnnotation3 = null $
|
||||||
check "#!/bin/sh\n#unerlated\n# shellcheck disable=2086\ntrue\necho $1"
|
check "#!/bin/sh\n#unrelated\n# shellcheck disable=2086\ntrue\necho $1"
|
||||||
prop_filewideAnnotation4 = null $
|
prop_filewideAnnotation4 = null $
|
||||||
check "#!/bin/sh\n# shellcheck disable=2086\n#unrelated\ntrue\necho $1"
|
check "#!/bin/sh\n# shellcheck disable=2086\n#unrelated\ntrue\necho $1"
|
||||||
prop_filewideAnnotation5 = null $
|
prop_filewideAnnotation5 = null $
|
||||||
|
@ -197,6 +213,5 @@ prop_filewideAnnotation8 = null $
|
||||||
prop_sourcePartOfOriginalScript = -- #1181: -x disabled posix warning for 'source'
|
prop_sourcePartOfOriginalScript = -- #1181: -x disabled posix warning for 'source'
|
||||||
2039 `elem` checkWithIncludes [("./saywhat.sh", "echo foo")] "#!/bin/sh\nsource ./saywhat.sh"
|
2039 `elem` checkWithIncludes [("./saywhat.sh", "echo foo")] "#!/bin/sh\nsource ./saywhat.sh"
|
||||||
|
|
||||||
|
|
||||||
return []
|
return []
|
||||||
runTests = $quickCheckAll
|
runTests = $quickCheckAll
|
||||||
|
|
|
@ -52,11 +52,20 @@ emptyCheckSpec = CheckSpec {
|
||||||
csShellTypeOverride = Nothing
|
csShellTypeOverride = Nothing
|
||||||
}
|
}
|
||||||
|
|
||||||
|
newParseSpec :: ParseSpec
|
||||||
|
newParseSpec = ParseSpec {
|
||||||
|
psFilename = "",
|
||||||
|
psScript = "",
|
||||||
|
psCheckSourced = False,
|
||||||
|
psShellTypeOverride = Nothing
|
||||||
|
}
|
||||||
|
|
||||||
-- Parser input and output
|
-- Parser input and output
|
||||||
data ParseSpec = ParseSpec {
|
data ParseSpec = ParseSpec {
|
||||||
psFilename :: String,
|
psFilename :: String,
|
||||||
psScript :: String,
|
psScript :: String,
|
||||||
psCheckSourced :: Bool
|
psCheckSourced :: Bool,
|
||||||
|
psShellTypeOverride :: Maybe Shell
|
||||||
} deriving (Show, Eq)
|
} deriving (Show, Eq)
|
||||||
|
|
||||||
data ParseResult = ParseResult {
|
data ParseResult = ParseResult {
|
||||||
|
|
|
@ -305,7 +305,8 @@ initialSystemState = SystemState {
|
||||||
|
|
||||||
data Environment m = Environment {
|
data Environment m = Environment {
|
||||||
systemInterface :: SystemInterface m,
|
systemInterface :: SystemInterface m,
|
||||||
checkSourced :: Bool
|
checkSourced :: Bool,
|
||||||
|
shellTypeOverride :: Maybe Shell
|
||||||
}
|
}
|
||||||
|
|
||||||
parseProblem level code msg = do
|
parseProblem level code msg = do
|
||||||
|
@ -2965,17 +2966,24 @@ readScriptFile = do
|
||||||
parseProblem ErrorC 1082
|
parseProblem ErrorC 1082
|
||||||
"This file has a UTF-8 BOM. Remove it with: LC_CTYPE=C sed '1s/^...//' < yourscript ."
|
"This file has a UTF-8 BOM. Remove it with: LC_CTYPE=C sed '1s/^...//' < yourscript ."
|
||||||
sb <- option "" readShebang
|
sb <- option "" readShebang
|
||||||
verifyShell pos (getShell sb)
|
allspacing
|
||||||
if isValidShell (getShell sb) /= Just False
|
annotationStart <- startSpan
|
||||||
|
annotations <- readAnnotations
|
||||||
|
annotationId <- endSpan annotationStart
|
||||||
|
let shellAnnotationSpecified =
|
||||||
|
any (\x -> case x of ShellOverride {} -> True; _ -> False) annotations
|
||||||
|
shellFlagSpecified <- isJust <$> Mr.asks shellTypeOverride
|
||||||
|
let ignoreShebang = shellAnnotationSpecified || shellFlagSpecified
|
||||||
|
|
||||||
|
unless ignoreShebang $
|
||||||
|
verifyShebang pos (getShell sb)
|
||||||
|
if ignoreShebang || isValidShell (getShell sb) /= Just False
|
||||||
then do
|
then do
|
||||||
allspacing
|
|
||||||
annotationStart <- startSpan
|
|
||||||
annotations <- readAnnotations
|
|
||||||
annotationId <- endSpan annotationStart
|
|
||||||
commands <- withAnnotations annotations readCompoundListOrEmpty
|
commands <- withAnnotations annotations readCompoundListOrEmpty
|
||||||
id <- endSpan start
|
id <- endSpan start
|
||||||
verifyEof
|
verifyEof
|
||||||
let script = T_Annotation annotationId annotations $ T_Script id sb commands
|
let script = T_Annotation annotationId annotations $
|
||||||
|
T_Script id sb commands
|
||||||
reparseIndices script
|
reparseIndices script
|
||||||
else do
|
else do
|
||||||
many anyChar
|
many anyChar
|
||||||
|
@ -2993,7 +3001,7 @@ readScriptFile = do
|
||||||
then second
|
then second
|
||||||
else basename first
|
else basename first
|
||||||
|
|
||||||
verifyShell pos s =
|
verifyShebang pos s = do
|
||||||
case isValidShell s of
|
case isValidShell s of
|
||||||
Just True -> return ()
|
Just True -> return ()
|
||||||
Just False -> parseProblemAt pos ErrorC 1071 "ShellCheck only supports sh/bash/dash/ksh scripts. Sorry!"
|
Just False -> parseProblemAt pos ErrorC 1071 "ShellCheck only supports sh/bash/dash/ksh scripts. Sorry!"
|
||||||
|
@ -3055,16 +3063,16 @@ debugParseScript string =
|
||||||
}
|
}
|
||||||
where
|
where
|
||||||
result = runIdentity $
|
result = runIdentity $
|
||||||
parseScript (mockedSystemInterface []) $ ParseSpec {
|
parseScript (mockedSystemInterface []) $ newParseSpec {
|
||||||
psFilename = "debug",
|
psFilename = "debug",
|
||||||
psScript = string,
|
psScript = string
|
||||||
psCheckSourced = False
|
|
||||||
}
|
}
|
||||||
|
|
||||||
testEnvironment =
|
testEnvironment =
|
||||||
Environment {
|
Environment {
|
||||||
systemInterface = (mockedSystemInterface []),
|
systemInterface = (mockedSystemInterface []),
|
||||||
checkSourced = False
|
checkSourced = False,
|
||||||
|
shellTypeOverride = Nothing
|
||||||
}
|
}
|
||||||
|
|
||||||
|
|
||||||
|
@ -3230,7 +3238,8 @@ parseScript sys spec =
|
||||||
where
|
where
|
||||||
env = Environment {
|
env = Environment {
|
||||||
systemInterface = sys,
|
systemInterface = sys,
|
||||||
checkSourced = psCheckSourced spec
|
checkSourced = psCheckSourced spec,
|
||||||
|
shellTypeOverride = psShellTypeOverride spec
|
||||||
}
|
}
|
||||||
|
|
||||||
-- Same as 'try' but emit syntax errors if the parse fails.
|
-- Same as 'try' but emit syntax errors if the parse fails.
|
||||||
|
|
Loading…
Reference in New Issue