Fix #1369 (Use file extension to detect shell)

The precedence order that is used to determine the shell
is the following:
1. ShellCheck directive
2. Shebang
3. File extension
A new field `asFallbackShell` has been
added to the record type `AnalysisSpec`.
This commit is contained in:
Tito Sacchi 2019-01-14 14:16:12 +01:00
parent e0a4241baa
commit a4b9cec9f0
3 changed files with 19 additions and 5 deletions

View File

@ -175,7 +175,7 @@ makeCommentWithFix severity id code str fix =
makeParameters spec = makeParameters spec =
let params = Parameters { let params = Parameters {
rootNode = root, rootNode = root,
shellType = fromMaybe (determineShell root) $ asShellType spec, shellType = fromMaybe (determineShell (asFallbackShell spec) root) $ asShellType spec,
hasSetE = containsSetE root, hasSetE = containsSetE root,
hasLastpipe = hasLastpipe =
case shellType params of case shellType params of
@ -227,11 +227,13 @@ prop_determineShell4 = determineShellTest "#!/bin/ksh\n#shellcheck shell=sh\nfoo
prop_determineShell5 = determineShellTest "#shellcheck shell=sh\nfoo" == Sh prop_determineShell5 = determineShellTest "#shellcheck shell=sh\nfoo" == Sh
prop_determineShell6 = determineShellTest "#! /bin/sh" == Sh prop_determineShell6 = determineShellTest "#! /bin/sh" == Sh
prop_determineShell7 = determineShellTest "#! /bin/ash" == Dash prop_determineShell7 = determineShellTest "#! /bin/ash" == Dash
prop_determineShell8 = determineShellTest' (Just Ksh) "#!/bin/sh" == Sh
determineShellTest = determineShell . fromJust . prRoot . pScript determineShellTest = determineShellTest' Nothing
determineShell t = fromMaybe Bash $ do determineShellTest' fallbackShell = determineShell fallbackShell . fromJust . prRoot . pScript
determineShell fallbackShell t = fromMaybe Bash $ do
shellString <- foldl mplus Nothing $ getCandidates t shellString <- foldl mplus Nothing $ getCandidates t
shellForExecutable shellString shellForExecutable shellString `mplus` fallbackShell
where where
forAnnotation t = forAnnotation t =
case t of case t of

View File

@ -48,6 +48,15 @@ tokenToPosition startMap t = fromMaybe fail $ do
where where
fail = error "Internal shellcheck error: id doesn't exist. Please report!" fail = error "Internal shellcheck error: id doesn't exist. Please report!"
shellFromFilename filename = foldl mplus Nothing candidates
where
shellExtensions = [(".ksh", Ksh)
,(".sh", Sh)
,(".bash", Bash)
,(".dash", Dash)]
candidates =
map (\(ext,sh) -> if ext `isSuffixOf` filename then Just sh else Nothing) shellExtensions
checkScript :: Monad m => SystemInterface m -> CheckSpec -> m CheckResult checkScript :: Monad m => SystemInterface m -> CheckSpec -> m CheckResult
checkScript sys spec = do checkScript sys spec = do
results <- checkScript (csScript spec) results <- checkScript (csScript spec)
@ -69,6 +78,7 @@ checkScript sys spec = do
as { as {
asScript = root, asScript = root,
asShellType = csShellTypeOverride spec, asShellType = csShellTypeOverride spec,
asFallbackShell = shellFromFilename $ csFilename spec,
asCheckSourced = csCheckSourced spec, asCheckSourced = csCheckSourced spec,
asExecutionMode = Executed, asExecutionMode = Executed,
asTokenPositions = tokenPositions asTokenPositions = tokenPositions

View File

@ -25,7 +25,7 @@ module ShellCheck.Interface
, CheckResult(crFilename, crComments) , CheckResult(crFilename, crComments)
, ParseSpec(psFilename, psScript, psCheckSourced, psShellTypeOverride) , ParseSpec(psFilename, psScript, psCheckSourced, psShellTypeOverride)
, ParseResult(prComments, prTokenPositions, prRoot) , ParseResult(prComments, prTokenPositions, prRoot)
, AnalysisSpec(asScript, asShellType, asExecutionMode, asCheckSourced, asTokenPositions) , AnalysisSpec(asScript, asShellType, asFallbackShell, asExecutionMode, asCheckSourced, asTokenPositions)
, AnalysisResult(arComments) , AnalysisResult(arComments)
, FormatterOptions(foColorOption, foWikiLinkCount) , FormatterOptions(foColorOption, foWikiLinkCount)
, Shell(Ksh, Sh, Bash, Dash) , Shell(Ksh, Sh, Bash, Dash)
@ -138,6 +138,7 @@ newParseResult = ParseResult {
data AnalysisSpec = AnalysisSpec { data AnalysisSpec = AnalysisSpec {
asScript :: Token, asScript :: Token,
asShellType :: Maybe Shell, asShellType :: Maybe Shell,
asFallbackShell :: Maybe Shell,
asExecutionMode :: ExecutionMode, asExecutionMode :: ExecutionMode,
asCheckSourced :: Bool, asCheckSourced :: Bool,
asTokenPositions :: Map.Map Id (Position, Position) asTokenPositions :: Map.Map Id (Position, Position)
@ -146,6 +147,7 @@ data AnalysisSpec = AnalysisSpec {
newAnalysisSpec token = AnalysisSpec { newAnalysisSpec token = AnalysisSpec {
asScript = token, asScript = token,
asShellType = Nothing, asShellType = Nothing,
asFallbackShell = Nothing,
asExecutionMode = Executed, asExecutionMode = Executed,
asCheckSourced = False, asCheckSourced = False,
asTokenPositions = Map.empty asTokenPositions = Map.empty