Merge branch 'master' into master

This commit is contained in:
LuizMuller 2019-07-24 15:28:03 -03:00 committed by GitHub
commit ded04820b8
No known key found for this signature in database
GPG Key ID: 4AEE18F83AFDEB23
22 changed files with 744 additions and 148 deletions

6
.dockerignore Normal file
View File

@ -0,0 +1,6 @@
*
!LICENSE
!Setup.hs
!ShellCheck.cabal
!shellcheck.hs
!src

View File

@ -1,6 +1,7 @@
## Since previous release ## Since previous release
### Added ### Added
- Preliminary support for fix suggestions - Preliminary support for fix suggestions
- New `-f diff` unified diff format for auto-fixes
- 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` - Directory wide directives can now be placed in a `.shellcheckrc`
- Optional checks: Use `--list-optional` to show a list of tests, - Optional checks: Use `--list-optional` to show a list of tests,
@ -8,6 +9,10 @@
- Source paths: Use `-P dir1:dir2` or a `source-path=dir1` directive - Source paths: Use `-P dir1:dir2` or a `source-path=dir1` directive
to specify search paths for sourced files. to specify search paths for sourced files.
- json1 format like --format=json but treats tabs as single characters - json1 format like --format=json but treats tabs as single characters
- Recognize FLAGS variables created by the shflags library.
- Site-specific changes can now be made in Custom.hs for ease of patching
- SC2154: Also warn about unassigned uppercase variables (optional)
- SC2252: Warn about `[ $a != x ] || [ $a != y ]`, similar to SC2055
- SC2251: Inform about ineffectual ! in front of commands - SC2251: Inform about ineffectual ! in front of commands
- SC2250: Warn about variable references without braces (optional) - SC2250: Warn about variable references without braces (optional)
- SC2249: Warn about `case` with missing default case (optional) - SC2249: Warn about `case` with missing default case (optional)
@ -16,12 +21,16 @@
- 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 ]` (optional) - SC2243/SC2244: Suggest using explicit -n for `[ $foo ]` (optional)
- SC1135: Suggest not ending double quotes just to make $ literal
### Changed ### Changed
- If a directive or shebang is not specified, a `.bash/.bats/.dash/.ksh` - If a directive or shebang is not specified, a `.bash/.bats/.dash/.ksh`
extension will be used to infer the shell type when present. extension will be used to infer the shell type when present.
- Disabling SC2120 on a function now disables SC2119 on call sites - Disabling SC2120 on a function now disables SC2119 on call sites
### Fixed
- SC2183 no longer warns about missing printf args for `%()T`
## v0.6.0 - 2018-12-02 ## v0.6.0 - 2018-12-02
### Added ### Added
- Command line option --severity/-S for filtering by minimum severity - Command line option --severity/-S for filtering by minimum severity

View File

@ -57,6 +57,7 @@ library
bytestring, bytestring,
containers >= 0.5, containers >= 0.5,
deepseq >= 1.4.0.0, deepseq >= 1.4.0.0,
Diff >= 0.2.0,
directory >= 1.2.3.0, directory >= 1.2.3.0,
mtl >= 2.2.1, mtl >= 2.2.1,
filepath, filepath,
@ -73,13 +74,16 @@ library
ShellCheck.AnalyzerLib ShellCheck.AnalyzerLib
ShellCheck.Checker ShellCheck.Checker
ShellCheck.Checks.Commands ShellCheck.Checks.Commands
ShellCheck.Checks.Custom
ShellCheck.Checks.ShellSupport ShellCheck.Checks.ShellSupport
ShellCheck.Data ShellCheck.Data
ShellCheck.Fixer ShellCheck.Fixer
ShellCheck.Formatter.Format ShellCheck.Formatter.Format
ShellCheck.Formatter.CheckStyle ShellCheck.Formatter.CheckStyle
ShellCheck.Formatter.Diff
ShellCheck.Formatter.GCC ShellCheck.Formatter.GCC
ShellCheck.Formatter.JSON ShellCheck.Formatter.JSON
ShellCheck.Formatter.JSON1
ShellCheck.Formatter.TTY ShellCheck.Formatter.TTY
ShellCheck.Formatter.Quiet ShellCheck.Formatter.Quiet
ShellCheck.Interface ShellCheck.Interface
@ -99,6 +103,7 @@ executable shellcheck
bytestring, bytestring,
containers, containers,
deepseq >= 1.4.0.0, deepseq >= 1.4.0.0,
Diff >= 0.2.0,
directory >= 1.2.3.0, directory >= 1.2.3.0,
mtl >= 2.2.1, mtl >= 2.2.1,
filepath, filepath,
@ -117,6 +122,7 @@ test-suite test-shellcheck
bytestring, bytestring,
containers, containers,
deepseq >= 1.4.0.0, deepseq >= 1.4.0.0,
Diff >= 0.2.0,
directory >= 1.2.3.0, directory >= 1.2.3.0,
mtl >= 2.2.1, mtl >= 2.2.1,
filepath, filepath,

View File

@ -152,28 +152,47 @@ not warn at all, as `ksh` supports decimals in arithmetic contexts.
... ...
</checkstyle> </checkstyle>
**diff**
: Auto-fixes in unified diff format. Can be piped to `git apply` or `patch -p1`
to automatically apply fixes.
--- a/test.sh
+++ b/test.sh
@@ -2,6 +2,6 @@
## Example of a broken script.
for f in $(ls *.m3u)
do
- grep -qi hq.*mp3 $f \
+ grep -qi hq.*mp3 "$f" \
&& echo -e 'Playlist $f contains a HQ file in mp3 format'
done
**json1** **json1**
: Json is a popular serialization format that is more suitable for web : Json is a popular serialization format that is more suitable for web
applications. ShellCheck's json is compact and contains only the bare applications. ShellCheck's json is compact and contains only the bare
minimum. Tabs are counted as 1 character. minimum. Tabs are counted as 1 character.
[ {
{ comments: [
"file": "filename", {
"line": lineNumber, "file": "filename",
"column": columnNumber, "line": lineNumber,
"level": "severitylevel", "column": columnNumber,
"code": errorCode, "level": "severitylevel",
"message": "warning message" "code": errorCode,
}, "message": "warning message"
... },
] ...
]
}
**json** **json**
: This is a legacy version of the **json1** format, with a tab stop : This is a legacy version of the **json1** format. It's a raw array of
of 8 instead of 1. comments, and all offsets have a tab stop of 8.
**quiet** **quiet**
@ -251,6 +270,9 @@ Here is an example `.shellcheckrc`:
# Turn on warnings for unquoted variables with safe values # Turn on warnings for unquoted variables with safe values
enable=quote-safe-variables enable=quote-safe-variables
# Turn on warnings for unassigned uppercase variables
enable=check-unassigned-uppercase
# Allow using `which` since it gives full paths and is common enough # Allow using `which` since it gives full paths and is common enough
disable=SC2230 disable=SC2230

View File

@ -25,8 +25,10 @@ import ShellCheck.Regex
import qualified ShellCheck.Formatter.CheckStyle import qualified ShellCheck.Formatter.CheckStyle
import ShellCheck.Formatter.Format import ShellCheck.Formatter.Format
import qualified ShellCheck.Formatter.Diff
import qualified ShellCheck.Formatter.GCC import qualified ShellCheck.Formatter.GCC
import qualified ShellCheck.Formatter.JSON import qualified ShellCheck.Formatter.JSON
import qualified ShellCheck.Formatter.JSON1
import qualified ShellCheck.Formatter.TTY import qualified ShellCheck.Formatter.TTY
import qualified ShellCheck.Formatter.Quiet import qualified ShellCheck.Formatter.Quiet
@ -140,9 +142,10 @@ parseArguments argv =
formats :: FormatterOptions -> Map.Map String (IO Formatter) formats :: FormatterOptions -> Map.Map String (IO Formatter)
formats options = Map.fromList [ formats options = Map.fromList [
("checkstyle", ShellCheck.Formatter.CheckStyle.format), ("checkstyle", ShellCheck.Formatter.CheckStyle.format),
("diff", ShellCheck.Formatter.Diff.format options),
("gcc", ShellCheck.Formatter.GCC.format), ("gcc", ShellCheck.Formatter.GCC.format),
("json", ShellCheck.Formatter.JSON.format False), -- JSON with 8-char tabs ("json", ShellCheck.Formatter.JSON.format),
("json1", ShellCheck.Formatter.JSON.format True), -- JSON with 1-char tabs ("json1", ShellCheck.Formatter.JSON1.format),
("tty", ShellCheck.Formatter.TTY.format options), ("tty", ShellCheck.Formatter.TTY.format options),
("quiet", ShellCheck.Formatter.Quiet.format options) ("quiet", ShellCheck.Formatter.Quiet.format options)
] ]
@ -497,8 +500,8 @@ ioInterface options files = do
find original original find original original
where where
find filename deflt = do find filename deflt = do
sources <- filterM ((allowable inputs) `andM` doesFileExist) sources <- filterM ((allowable inputs) `andM` doesFileExist) $
(map (</> filename) $ map adjustPath $ sourcePathFlag ++ sourcePathAnnotation) (adjustPath filename):(map (</> filename) $ map adjustPath $ sourcePathFlag ++ sourcePathAnnotation)
case sources of case sources of
[] -> return deflt [] -> return deflt
(first:_) -> return first (first:_) -> return first

View File

@ -121,7 +121,7 @@ data Token =
| T_Rbrace Id | T_Rbrace Id
| T_Redirecting Id [Token] Token | T_Redirecting Id [Token] Token
| T_Rparen Id | T_Rparen Id
| T_Script Id String [Token] | T_Script Id Token [Token] -- Shebang T_Literal, followed by script.
| T_Select Id | T_Select Id
| T_SelectIn Id String [Token] [Token] | T_SelectIn Id String [Token] [Token]
| T_Semi Id | T_Semi Id

View File

@ -231,6 +231,13 @@ optionalTreeChecks = [
cdPositive = "var=hello; echo $var", cdPositive = "var=hello; echo $var",
cdNegative = "var=hello; echo ${var}" cdNegative = "var=hello; echo ${var}"
}, nodeChecksToTreeCheck [checkVariableBraces]) }, nodeChecksToTreeCheck [checkVariableBraces])
,(newCheckDescription {
cdName = "check-unassigned-uppercase",
cdDescription = "Warn when uppercase variables are unassigned",
cdPositive = "echo $VAR",
cdNegative = "VAR=hello; echo $VAR"
}, checkUnassignedReferences' True)
] ]
optionalCheckMap :: Map.Map String (Parameters -> Token -> [TokenComment]) optionalCheckMap :: Map.Map String (Parameters -> Token -> [TokenComment])
@ -266,7 +273,11 @@ producesComments :: (Parameters -> Token -> [TokenComment]) -> String -> Maybe B
producesComments f s = do producesComments f s = do
let pr = pScript s let pr = pScript s
prRoot pr prRoot pr
return . not . null $ runList (defaultSpec pr) [f] let spec = defaultSpec pr
let params = makeParameters spec
return . not . null $
filterByAnnotation spec params $
runList spec [f]
-- Copied from https://wiki.haskell.org/Edit_distance -- Copied from https://wiki.haskell.org/Edit_distance
dist :: Eq a => [a] -> [a] -> Int dist :: Eq a => [a] -> [a] -> Int
@ -527,7 +538,7 @@ indexOfSublists sub = f 0
prop_checkShebangParameters1 = verifyTree checkShebangParameters "#!/usr/bin/env bash -x\necho cow" prop_checkShebangParameters1 = verifyTree checkShebangParameters "#!/usr/bin/env bash -x\necho cow"
prop_checkShebangParameters2 = verifyNotTree checkShebangParameters "#! /bin/sh -l " prop_checkShebangParameters2 = verifyNotTree checkShebangParameters "#! /bin/sh -l "
checkShebangParameters p (T_Annotation _ _ t) = checkShebangParameters p t checkShebangParameters p (T_Annotation _ _ t) = checkShebangParameters p t
checkShebangParameters _ (T_Script id sb _) = checkShebangParameters _ (T_Script _ (T_Literal id sb) _) =
[makeComment ErrorC id 2096 "On most OS, shebangs can only specify a single parameter." | length (words sb) > 2] [makeComment ErrorC id 2096 "On most OS, shebangs can only specify a single parameter." | length (words sb) > 2]
prop_checkShebang1 = verifyNotTree checkShebang "#!/usr/bin/env bash -x\necho cow" prop_checkShebang1 = verifyNotTree checkShebang "#!/usr/bin/env bash -x\necho cow"
@ -547,7 +558,7 @@ checkShebang params (T_Annotation _ list t) =
where where
isOverride (ShellOverride _) = True isOverride (ShellOverride _) = True
isOverride _ = False isOverride _ = False
checkShebang params (T_Script id sb _) = execWriter $ do checkShebang params (T_Script _ (T_Literal id sb) _) = execWriter $ do
unless (shellTypeSpecified params) $ do unless (shellTypeSpecified params) $ do
when (sb == "") $ when (sb == "") $
err id 2148 "Tips depend on target shell and yours is unknown. Add a shebang." err id 2148 "Tips depend on target shell and yours is unknown. Add a shebang."
@ -829,6 +840,7 @@ prop_checkArrayWithoutIndex6 = verifyTree checkArrayWithoutIndex "echo $PIPESTAT
prop_checkArrayWithoutIndex7 = verifyTree checkArrayWithoutIndex "a=(a b); a+=c" prop_checkArrayWithoutIndex7 = verifyTree checkArrayWithoutIndex "a=(a b); a+=c"
prop_checkArrayWithoutIndex8 = verifyTree checkArrayWithoutIndex "declare -a foo; foo=bar;" prop_checkArrayWithoutIndex8 = verifyTree checkArrayWithoutIndex "declare -a foo; foo=bar;"
prop_checkArrayWithoutIndex9 = verifyTree checkArrayWithoutIndex "read -r -a arr <<< 'foo bar'; echo \"$arr\"" prop_checkArrayWithoutIndex9 = verifyTree checkArrayWithoutIndex "read -r -a arr <<< 'foo bar'; echo \"$arr\""
prop_checkArrayWithoutIndex10= verifyTree checkArrayWithoutIndex "read -ra arr <<< 'foo bar'; echo \"$arr\""
checkArrayWithoutIndex params _ = checkArrayWithoutIndex params _ =
doVariableFlowAnalysis readF writeF defaultMap (variableFlow params) doVariableFlowAnalysis readF writeF defaultMap (variableFlow params)
where where
@ -917,6 +929,8 @@ prop_checkSingleQuotedVariables14= verifyNot checkSingleQuotedVariables "[ -v 'b
prop_checkSingleQuotedVariables15= verifyNot checkSingleQuotedVariables "git filter-branch 'test $GIT_COMMIT'" prop_checkSingleQuotedVariables15= verifyNot checkSingleQuotedVariables "git filter-branch 'test $GIT_COMMIT'"
prop_checkSingleQuotedVariables16= verify checkSingleQuotedVariables "git '$a'" prop_checkSingleQuotedVariables16= verify checkSingleQuotedVariables "git '$a'"
prop_checkSingleQuotedVariables17= verifyNot checkSingleQuotedVariables "rename 's/(.)a/$1/g' *" prop_checkSingleQuotedVariables17= verifyNot checkSingleQuotedVariables "rename 's/(.)a/$1/g' *"
prop_checkSingleQuotedVariables18= verifyNot checkSingleQuotedVariables "echo '``'"
prop_checkSingleQuotedVariables19= verifyNot checkSingleQuotedVariables "echo '```'"
checkSingleQuotedVariables params t@(T_SingleQuoted id s) = checkSingleQuotedVariables params t@(T_SingleQuoted id s) =
when (s `matches` re) $ when (s `matches` re) $
@ -962,7 +976,7 @@ checkSingleQuotedVariables params t@(T_SingleQuoted id s) =
TC_Unary _ _ "-v" _ -> True TC_Unary _ _ "-v" _ -> True
_ -> False _ -> False
re = mkRegex "\\$[{(0-9a-zA-Z_]|`.*`" re = mkRegex "\\$[{(0-9a-zA-Z_]|`[^`]+`"
sedContra = mkRegex "\\$[{dpsaic]($|[^a-zA-Z])" sedContra = mkRegex "\\$[{dpsaic]($|[^a-zA-Z])"
getFindCommand (T_SimpleCommand _ _ words) = getFindCommand (T_SimpleCommand _ _ words) =
@ -1348,14 +1362,39 @@ prop_checkOrNeq2 = verify checkOrNeq "(( a!=lol || a!=foo ))"
prop_checkOrNeq3 = verify checkOrNeq "[ \"$a\" != lol || \"$a\" != foo ]" prop_checkOrNeq3 = verify checkOrNeq "[ \"$a\" != lol || \"$a\" != foo ]"
prop_checkOrNeq4 = verifyNot checkOrNeq "[ a != $cow || b != $foo ]" prop_checkOrNeq4 = verifyNot checkOrNeq "[ a != $cow || b != $foo ]"
prop_checkOrNeq5 = verifyNot checkOrNeq "[[ $a != /home || $a != */public_html/* ]]" prop_checkOrNeq5 = verifyNot checkOrNeq "[[ $a != /home || $a != */public_html/* ]]"
prop_checkOrNeq6 = verify checkOrNeq "[ $a != a ] || [ $a != b ]"
prop_checkOrNeq7 = verify checkOrNeq "[ $a != a ] || [ $a != b ] || true"
prop_checkOrNeq8 = verifyNot checkOrNeq "[[ $a != x || $a != x ]]"
-- This only catches the most idiomatic cases. Fixme? -- This only catches the most idiomatic cases. Fixme?
checkOrNeq _ (TC_Or id typ op (TC_Binary _ _ op1 lhs1 rhs1 ) (TC_Binary _ _ op2 lhs2 rhs2))
| lhs1 == lhs2 && (op1 == op2 && (op1 == "-ne" || op1 == "!=")) && not (any isGlob [rhs1,rhs2]) =
warn id 2055 $ "You probably wanted " ++ (if typ == SingleBracket then "-a" else "&&") ++ " here."
-- For test-level "or": [ x != y -o x != z ]
checkOrNeq _ (TC_Or id typ op (TC_Binary _ _ op1 lhs1 rhs1 ) (TC_Binary _ _ op2 lhs2 rhs2))
| (op1 == op2 && (op1 == "-ne" || op1 == "!=")) && lhs1 == lhs2 && rhs1 /= rhs2 && not (any isGlob [rhs1,rhs2]) =
warn id 2055 $ "You probably wanted " ++ (if typ == SingleBracket then "-a" else "&&") ++ " here, otherwise it's always true."
-- For arithmetic context "or"
checkOrNeq _ (TA_Binary id "||" (TA_Binary _ "!=" word1 _) (TA_Binary _ "!=" word2 _)) checkOrNeq _ (TA_Binary id "||" (TA_Binary _ "!=" word1 _) (TA_Binary _ "!=" word2 _))
| word1 == word2 = | word1 == word2 =
warn id 2056 "You probably wanted && here." warn id 2056 "You probably wanted && here, otherwise it's always true."
-- For command level "or": [ x != y ] || [ x != z ]
checkOrNeq _ (T_OrIf id lhs rhs) = potentially $ do
(lhs1, op1, rhs1) <- getExpr lhs
(lhs2, op2, rhs2) <- getExpr rhs
guard $ op1 == op2 && op1 `elem` ["-ne", "!="]
guard $ lhs1 == lhs2 && rhs1 /= rhs2
guard . not $ any isGlob [rhs1, rhs2]
return $ warn id 2252 "You probably wanted && here, otherwise it's always true."
where
getExpr x =
case x of
T_OrIf _ lhs _ -> getExpr lhs -- Fetches x and y in `T_OrIf x (T_OrIf y z)`
T_Pipeline _ _ [x] -> getExpr x
T_Redirecting _ _ c -> getExpr c
T_Condition _ _ c -> getExpr c
TC_Binary _ _ op lhs rhs -> return (lhs, op, rhs)
_ -> fail ""
checkOrNeq _ _ = return () checkOrNeq _ _ = return ()
@ -2047,6 +2086,11 @@ prop_checkUnused38= verifyTree checkUnusedAssignments "(( a=42 ))"
prop_checkUnused39= verifyNotTree checkUnusedAssignments "declare -x -f foo" prop_checkUnused39= verifyNotTree checkUnusedAssignments "declare -x -f foo"
prop_checkUnused40= verifyNotTree checkUnusedAssignments "arr=(1 2); num=2; echo \"${arr[@]:num}\"" prop_checkUnused40= verifyNotTree checkUnusedAssignments "arr=(1 2); num=2; echo \"${arr[@]:num}\""
prop_checkUnused41= verifyNotTree checkUnusedAssignments "@test 'foo' {\ntrue\n}\n" prop_checkUnused41= verifyNotTree checkUnusedAssignments "@test 'foo' {\ntrue\n}\n"
prop_checkUnused42= verifyNotTree checkUnusedAssignments "DEFINE_string foo '' ''; echo \"${FLAGS_foo}\""
prop_checkUnused43= verifyTree checkUnusedAssignments "DEFINE_string foo '' ''"
prop_checkUnused44= verifyNotTree checkUnusedAssignments "DEFINE_string \"foo$ibar\" x y"
prop_checkUnused45= verifyTree checkUnusedAssignments "readonly foo=bar"
prop_checkUnused46= verifyTree checkUnusedAssignments "readonly foo=(bar)"
checkUnusedAssignments params t = execWriter (mapM_ warnFor unused) checkUnusedAssignments params t = execWriter (mapM_ warnFor unused)
where where
flow = variableFlow params flow = variableFlow params
@ -2106,7 +2150,10 @@ prop_checkUnassignedReferences34= verifyNotTree checkUnassignedReferences "decla
prop_checkUnassignedReferences35= verifyNotTree checkUnassignedReferences "echo ${arr[foo-bar]:?fail}" prop_checkUnassignedReferences35= verifyNotTree checkUnassignedReferences "echo ${arr[foo-bar]:?fail}"
prop_checkUnassignedReferences36= verifyNotTree checkUnassignedReferences "read -a foo -r <<<\"foo bar\"; echo \"$foo\"" prop_checkUnassignedReferences36= verifyNotTree checkUnassignedReferences "read -a foo -r <<<\"foo bar\"; echo \"$foo\""
prop_checkUnassignedReferences37= verifyNotTree checkUnassignedReferences "var=howdy; printf -v 'array[0]' %s \"$var\"; printf %s \"${array[0]}\";" prop_checkUnassignedReferences37= verifyNotTree checkUnassignedReferences "var=howdy; printf -v 'array[0]' %s \"$var\"; printf %s \"${array[0]}\";"
checkUnassignedReferences params t = warnings prop_checkUnassignedReferences38= verifyTree (checkUnassignedReferences' True) "echo $VAR"
checkUnassignedReferences = checkUnassignedReferences' False
checkUnassignedReferences' includeGlobals params t = warnings
where where
(readMap, writeMap) = execState (mapM tally $ variableFlow params) (Map.empty, Map.empty) (readMap, writeMap) = execState (mapM tally $ variableFlow params) (Map.empty, Map.empty)
defaultAssigned = Map.fromList $ map (\a -> (a, ())) $ filter (not . null) internalVariables defaultAssigned = Map.fromList $ map (\a -> (a, ())) $ filter (not . null) internalVariables
@ -2151,8 +2198,11 @@ checkUnassignedReferences params t = warnings
return $ " (did you mean '" ++ match ++ "'?)" return $ " (did you mean '" ++ match ++ "'?)"
warningFor var place = do warningFor var place = do
guard $ isVariableName var
guard . not $ isInArray var place || isGuarded place guard . not $ isInArray var place || isGuarded place
(if isLocal var then warningForLocals else warningForGlobals) var place (if includeGlobals || isLocal var
then warningForLocals
else warningForGlobals) var place
warnings = execWriter . sequence $ mapMaybe (uncurry warningFor) unassigned warnings = execWriter . sequence $ mapMaybe (uncurry warningFor) unassigned
@ -2299,27 +2349,18 @@ prop_checkCdAndBack4 = verify checkCdAndBack "cd $tmp; foo; cd -"
prop_checkCdAndBack5 = verifyNot checkCdAndBack "cd ..; foo; cd .." prop_checkCdAndBack5 = verifyNot checkCdAndBack "cd ..; foo; cd .."
prop_checkCdAndBack6 = verify checkCdAndBack "for dir in */; do cd \"$dir\"; some_cmd; cd ..; done" prop_checkCdAndBack6 = verify checkCdAndBack "for dir in */; do cd \"$dir\"; some_cmd; cd ..; done"
prop_checkCdAndBack7 = verifyNot checkCdAndBack "set -e; for dir in */; do cd \"$dir\"; some_cmd; cd ..; done" prop_checkCdAndBack7 = verifyNot checkCdAndBack "set -e; for dir in */; do cd \"$dir\"; some_cmd; cd ..; done"
checkCdAndBack params = doLists prop_checkCdAndBack8 = verifyNot checkCdAndBack "cd tmp\nfoo\n# shellcheck disable=SC2103\ncd ..\n"
checkCdAndBack params t =
unless (hasSetE params) $ mapM_ doList $ getCommandSequences t
where where
shell = shellType params
doLists (T_ForIn _ _ _ cmds) = doList cmds
doLists (T_ForArithmetic _ _ _ _ cmds) = doList cmds
doLists (T_WhileExpression _ _ cmds) = doList cmds
doLists (T_UntilExpression _ _ cmds) = doList cmds
doLists (T_Script _ _ cmds) = doList cmds
doLists (T_IfExpression _ thens elses) = do
mapM_ (\(_, l) -> doList l) thens
doList elses
doLists _ = return ()
isCdRevert t = isCdRevert t =
case oversimplify t of case oversimplify t of
["cd", p] -> p `elem` ["..", "-"] [_, p] -> p `elem` ["..", "-"]
_ -> False _ -> False
getCmd (T_Annotation id _ x) = getCmd x getCandidate (T_Annotation _ _ x) = getCandidate x
getCmd (T_Pipeline id _ [x]) = getCommandName x getCandidate (T_Pipeline id _ [x]) | x `isCommand` "cd" = return x
getCmd _ = Nothing getCandidate _ = Nothing
findCdPair list = findCdPair list =
case list of case list of
@ -2329,13 +2370,9 @@ checkCdAndBack params = doLists
else findCdPair (b:rest) else findCdPair (b:rest)
_ -> Nothing _ -> Nothing
doList list = doList list = potentially $ do
if hasSetE params cd <- findCdPair $ mapMaybe getCandidate list
then return () return $ info cd 2103 "Use a ( subshell ) to avoid having to cd back."
else let cds = filter ((== Just "cd") . getCmd) list
in potentially $ do
cd <- findCdPair cds
return $ info cd 2103 "Use a ( subshell ) to avoid having to cd back."
prop_checkLoopKeywordScope1 = verify checkLoopKeywordScope "continue 2" prop_checkLoopKeywordScope1 = verify checkLoopKeywordScope "continue 2"
prop_checkLoopKeywordScope2 = verify checkLoopKeywordScope "for f; do ( break; ); done" prop_checkLoopKeywordScope2 = verify checkLoopKeywordScope "for f; do ( break; ); done"
@ -3058,8 +3095,8 @@ checkSplittingInArrays params t =
&& not (getBracedReference (bracedString part) `elem` variablesWithoutSpaces) && not (getBracedReference (bracedString part) `elem` variablesWithoutSpaces)
-> warn id 2206 $ -> warn id 2206 $
if shellType params == Ksh if shellType params == Ksh
then "Quote to prevent word splitting, or split robustly with read -A or while read." then "Quote to prevent word splitting/globbing, or split robustly with read -A or while read."
else "Quote to prevent word splitting, or split robustly with mapfile or read -a." else "Quote to prevent word splitting/globbing, or split robustly with mapfile or read -a."
_ -> return () _ -> return ()
forCommand id = forCommand id =
@ -3358,18 +3395,23 @@ checkDefaultCase _ t =
pg <- wordToExactPseudoGlob pat pg <- wordToExactPseudoGlob pat
return $ pseudoGlobIsSuperSetof pg [PGMany] return $ pseudoGlobIsSuperSetof pg [PGMany]
prop_checkUselessBang1 = verify checkUselessBang "! true; rest" prop_checkUselessBang1 = verify checkUselessBang "set -e; ! true; rest"
prop_checkUselessBang2 = verify checkUselessBang "while true; do ! true; done" prop_checkUselessBang2 = verifyNot checkUselessBang "! true; rest"
prop_checkUselessBang3 = verifyNot checkUselessBang "if ! true; then true; fi" prop_checkUselessBang3 = verify checkUselessBang "set -e; while true; do ! true; done"
prop_checkUselessBang4 = verifyNot checkUselessBang "( ! true )" prop_checkUselessBang4 = verifyNot checkUselessBang "set -e; if ! true; then true; fi"
prop_checkUselessBang5 = verifyNot checkUselessBang "{ ! true; }" prop_checkUselessBang5 = verifyNot checkUselessBang "set -e; ( ! true )"
prop_checkUselessBang6 = verifyNot checkUselessBang "x() { ! [ x ]; }" prop_checkUselessBang6 = verify checkUselessBang "set -e; { ! true; }"
checkUselessBang params t = mapM_ check (getNonReturningCommands t) prop_checkUselessBang7 = verifyNot checkUselessBang "set -e; x() { ! [ x ]; }"
prop_checkUselessBang8 = verifyNot checkUselessBang "set -e; if { ! true; }; then true; fi"
prop_checkUselessBang9 = verifyNot checkUselessBang "set -e; while ! true; do true; done"
checkUselessBang params t = when (hasSetE params) $ mapM_ check (getNonReturningCommands t)
where where
check t = check t =
case t of case t of
T_Banged id _ -> T_Banged id cmd | not $ isCondition (getPath (parentMap params) t) ->
info id 2251 "This ! is not on a condition and skips errexit. Use { ! ...; } to errexit, or verify usage." addComment $ makeCommentWithFix InfoC id 2251
"This ! is not on a condition and skips errexit. Use `&& exit 1` instead, or make sure $? is checked."
(fixWith [replaceStart id params 1 "", replaceEnd (getId cmd) params 0 " && exit 1"])
_ -> return () _ -> return ()
-- Get all the subcommands that aren't likely to be the return value -- Get all the subcommands that aren't likely to be the return value
@ -3377,7 +3419,7 @@ checkUselessBang params t = mapM_ check (getNonReturningCommands t)
getNonReturningCommands t = getNonReturningCommands t =
case t of case t of
T_Script _ _ list -> dropLast list T_Script _ _ list -> dropLast list
T_BraceGroup _ list -> dropLast list T_BraceGroup _ list -> if isFunctionBody t then dropLast list else list
T_Subshell _ list -> dropLast list T_Subshell _ list -> dropLast list
T_WhileExpression _ conds cmds -> dropLast conds ++ cmds T_WhileExpression _ conds cmds -> dropLast conds ++ cmds
T_UntilExpression _ conds cmds -> dropLast conds ++ cmds T_UntilExpression _ conds cmds -> dropLast conds ++ cmds
@ -3388,6 +3430,11 @@ checkUselessBang params t = mapM_ check (getNonReturningCommands t)
concatMap (dropLast . fst) conds ++ concatMap snd conds ++ elses concatMap (dropLast . fst) conds ++ concatMap snd conds ++ elses
_ -> [] _ -> []
isFunctionBody t =
case getPath (parentMap params) t of
_:T_Function {}:_-> True
_ -> False
dropLast t = dropLast t =
case t of case t of
[_] -> [] [_] -> []

View File

@ -25,6 +25,7 @@ import ShellCheck.Interface
import Data.List import Data.List
import Data.Monoid import Data.Monoid
import qualified ShellCheck.Checks.Commands import qualified ShellCheck.Checks.Commands
import qualified ShellCheck.Checks.Custom
import qualified ShellCheck.Checks.ShellSupport import qualified ShellCheck.Checks.ShellSupport
@ -41,6 +42,7 @@ analyzeScript spec = newAnalysisResult {
checkers params = mconcat $ map ($ params) [ checkers params = mconcat $ map ($ params) [
ShellCheck.Checks.Commands.checker, ShellCheck.Checks.Commands.checker,
ShellCheck.Checks.Custom.checker,
ShellCheck.Checks.ShellSupport.checker ShellCheck.Checks.ShellSupport.checker
] ]

View File

@ -206,7 +206,7 @@ containsSetE root = isNothing $ doAnalysis (guard . not . isSetE) root
where where
isSetE t = isSetE t =
case t of case t of
T_Script _ str _ -> str `matches` re T_Script _ (T_Literal _ str) _ -> str `matches` re
T_SimpleCommand {} -> T_SimpleCommand {} ->
t `isUnqualifiedCommand` "set" && t `isUnqualifiedCommand` "set" &&
("errexit" `elem` oversimplify t || ("errexit" `elem` oversimplify t ||
@ -252,7 +252,7 @@ determineShell fallbackShell t = fromMaybe Bash $ do
getCandidates (T_Annotation _ annotations s) = getCandidates (T_Annotation _ annotations s) =
map forAnnotation annotations ++ map forAnnotation annotations ++
[Just $ fromShebang s] [Just $ fromShebang s]
fromShebang (T_Script _ s t) = executableFromShebang s fromShebang (T_Script _ (T_Literal _ s) _) = executableFromShebang s
-- Given a string like "/bin/bash" or "/usr/bin/env dash", -- Given a string like "/bin/bash" or "/usr/bin/env dash",
-- return the shell basename like "bash" or "dash" -- return the shell basename like "bash" or "dash"
@ -546,10 +546,6 @@ getReferencedVariableCommand base@(T_SimpleCommand _ _ (T_NormalWord _ (T_Litera
(not $ any (`elem` flags) ["f", "F"]) (not $ any (`elem` flags) ["f", "F"])
then concatMap getReference rest then concatMap getReference rest
else [] else []
"readonly" ->
if any (`elem` flags) ["f", "p"]
then []
else concatMap getReference rest
"trap" -> "trap" ->
case rest of case rest of
head:_ -> map (\x -> (head, head, x)) $ getVariablesFromLiteralToken head head:_ -> map (\x -> (head, head, x)) $ getVariablesFromLiteralToken head
@ -606,6 +602,11 @@ getModifiedVariableCommand base@(T_SimpleCommand _ _ (T_NormalWord _ (T_Literal
"mapfile" -> maybeToList $ getMapfileArray base rest "mapfile" -> maybeToList $ getMapfileArray base rest
"readarray" -> maybeToList $ getMapfileArray base rest "readarray" -> maybeToList $ getMapfileArray base rest
"DEFINE_boolean" -> maybeToList $ getFlagVariable rest
"DEFINE_float" -> maybeToList $ getFlagVariable rest
"DEFINE_integer" -> maybeToList $ getFlagVariable rest
"DEFINE_string" -> maybeToList $ getFlagVariable rest
_ -> [] _ -> []
where where
flags = map snd $ getAllFlags base flags = map snd $ getAllFlags base
@ -675,9 +676,22 @@ getModifiedVariableCommand base@(T_SimpleCommand _ _ (T_NormalWord _ (T_Literal
return (base, lastArg, name, DataArray SourceExternal) return (base, lastArg, name, DataArray SourceExternal)
-- get all the array variables used in read, e.g. read -a arr -- get all the array variables used in read, e.g. read -a arr
getReadArrayVariables args = do getReadArrayVariables args =
map (getLiteralArray . snd) map (getLiteralArray . snd)
(filter (\(x,_) -> getLiteralString x == Just "-a") (zip (args) (tail args))) (filter (isArrayFlag . fst) (zip args (tail args)))
isArrayFlag x = fromMaybe False $ do
str <- getLiteralString x
return $ case str of
'-':'-':_ -> False
'-':str -> 'a' `elem` str
_ -> False
-- get the FLAGS_ variable created by a shflags DEFINE_ call
getFlagVariable (n:v:_) = do
name <- getLiteralString n
return (base, n, "FLAGS_" ++ name, DataString $ SourceExternal)
getFlagVariable _ = Nothing
getModifiedVariableCommand _ = [] getModifiedVariableCommand _ = []
@ -777,7 +791,7 @@ isCommandMatch token matcher = fromMaybe False $
-- False: .*foo.* -- False: .*foo.*
isConfusedGlobRegex :: String -> Bool isConfusedGlobRegex :: String -> Bool
isConfusedGlobRegex ('*':_) = True isConfusedGlobRegex ('*':_) = True
isConfusedGlobRegex [x,'*'] | x /= '\\' = True isConfusedGlobRegex [x,'*'] | x `notElem` "\\." = True
isConfusedGlobRegex _ = False isConfusedGlobRegex _ = False
isVariableStartChar x = x == '_' || isAsciiLower x || isAsciiUpper x isVariableStartChar x = x == '_' || isAsciiLower x || isAsciiUpper x

View File

@ -94,6 +94,7 @@ commandChecks = [
,checkSudoRedirect ,checkSudoRedirect
,checkSudoArgs ,checkSudoArgs
,checkSourceArgs ,checkSourceArgs
,checkChmodDashr
] ]
buildCommandMap :: [CommandCheck] -> Map.Map CommandName (Token -> Analysis) buildCommandMap :: [CommandCheck] -> Map.Map CommandName (Token -> Analysis)
@ -213,6 +214,9 @@ prop_checkGrepRe17= verifyNot checkGrepRe "grep --exclude 'Foo*' file"
prop_checkGrepRe18= verifyNot checkGrepRe "grep --exclude-dir 'Foo*' file" prop_checkGrepRe18= verifyNot checkGrepRe "grep --exclude-dir 'Foo*' file"
prop_checkGrepRe19= verify checkGrepRe "grep -- 'Foo*' file" prop_checkGrepRe19= verify checkGrepRe "grep -- 'Foo*' file"
prop_checkGrepRe20= verifyNot checkGrepRe "grep --fixed-strings 'Foo*' file" prop_checkGrepRe20= verifyNot checkGrepRe "grep --fixed-strings 'Foo*' file"
prop_checkGrepRe21= verifyNot checkGrepRe "grep -o 'x*' file"
prop_checkGrepRe22= verifyNot checkGrepRe "grep --only-matching 'x*' file"
prop_checkGrepRe23= verifyNot checkGrepRe "grep '.*' file"
checkGrepRe = CommandCheck (Basename "grep") check where checkGrepRe = CommandCheck (Basename "grep") check where
check cmd = f cmd (arguments cmd) check cmd = f cmd (arguments cmd)
@ -245,7 +249,7 @@ checkGrepRe = CommandCheck (Basename "grep") check where
"Note that unlike globs, " ++ [char] ++ "* here matches '" ++ [char, char, char] ++ "' but not '" ++ wordStartingWith char ++ "'." "Note that unlike globs, " ++ [char] ++ "* here matches '" ++ [char, char, char] ++ "' but not '" ++ wordStartingWith char ++ "'."
where where
flags = map snd $ getAllFlags cmd flags = map snd $ getAllFlags cmd
grepGlobFlags = ["fixed-strings", "F", "include", "exclude", "exclude-dir"] grepGlobFlags = ["fixed-strings", "F", "include", "exclude", "exclude-dir", "o", "only-matching"]
wordStartingWith c = wordStartingWith c =
head . filter ([c] `isPrefixOf`) $ candidates head . filter ([c] `isPrefixOf`) $ candidates
@ -534,52 +538,83 @@ prop_checkPrintfVar15= verifyNot checkPrintfVar "printf '%*s\\n' 1 2"
prop_checkPrintfVar16= verifyNot checkPrintfVar "printf $'string'" prop_checkPrintfVar16= verifyNot checkPrintfVar "printf $'string'"
prop_checkPrintfVar17= verify checkPrintfVar "printf '%-*s\\n' 1" prop_checkPrintfVar17= verify checkPrintfVar "printf '%-*s\\n' 1"
prop_checkPrintfVar18= verifyNot checkPrintfVar "printf '%-*s\\n' 1 2" prop_checkPrintfVar18= verifyNot checkPrintfVar "printf '%-*s\\n' 1 2"
prop_checkPrintfVar19= verifyNot checkPrintfVar "printf '%(%s)T'"
prop_checkPrintfVar20= verifyNot checkPrintfVar "printf '%d %(%s)T' 42"
prop_checkPrintfVar21= verify checkPrintfVar "printf '%d %(%s)T'"
checkPrintfVar = CommandCheck (Exactly "printf") (f . arguments) where checkPrintfVar = CommandCheck (Exactly "printf") (f . arguments) where
f (doubledash:rest) | getLiteralString doubledash == Just "--" = f rest f (doubledash:rest) | getLiteralString doubledash == Just "--" = f rest
f (dashv:var:rest) | getLiteralString dashv == Just "-v" = f rest f (dashv:var:rest) | getLiteralString dashv == Just "-v" = f rest
f (format:params) = check format params f (format:params) = check format params
f _ = return () f _ = return ()
countFormats string =
case string of
'%':'%':rest -> countFormats rest
'%':'(':rest -> 1 + countFormats (dropWhile (/= ')') rest)
'%':rest -> regexBasedCountFormats rest + countFormats (dropWhile (/= '%') rest)
_:rest -> countFormats rest
[] -> 0
regexBasedCountFormats rest =
maybe 1 (foldl (\acc group -> acc + (if group == "*" then 1 else 0)) 1) (matchRegex re rest)
where
-- constructed based on specifications in "man printf"
re = mkRegex "#?-?\\+? ?0?(\\*|\\d*).?(\\d*|\\*)[diouxXfFeEgGaAcsb]"
-- \____ _____/\___ ____/ \____ ____/\________ ________/
-- V V V V
-- flags field width precision format character
-- field width and precision can be specified with a '*' instead of a digit,
-- in which case printf will accept one more argument for each '*' used
check format more = do check format more = do
fromMaybe (return ()) $ do fromMaybe (return ()) $ do
string <- getLiteralString format string <- getLiteralString format
let vars = countFormats string let formats = getPrintfFormats string
let formatCount = length formats
return $ do let argCount = length more
when (vars == 0 && more /= []) $
err (getId format) 2182
"This printf format string has no variables. Other arguments are ignored."
when (vars > 0
&& ((length more) `mod` vars /= 0 || null more)
&& all (not . mayBecomeMultipleArgs) more) $
warn (getId format) 2183 $
"This format string has " ++ show vars ++ " variables, but is passed " ++ show (length more) ++ " arguments."
return $
case () of
() | argCount == 0 && formatCount == 0 ->
return () -- This is fine
() | formatCount == 0 && argCount > 0 ->
err (getId format) 2182
"This printf format string has no variables. Other arguments are ignored."
() | any mayBecomeMultipleArgs more ->
return () -- We don't know so trust the user
() | argCount < formatCount && onlyTrailingTs formats argCount ->
return () -- Allow trailing %()Ts since they use the current time
() | argCount > 0 && argCount `mod` formatCount == 0 ->
return () -- Great: a suitable number of arguments
() ->
warn (getId format) 2183 $
"This format string has " ++ show formatCount ++ " variables, but is passed " ++ show argCount ++ " arguments."
unless ('%' `elem` concat (oversimplify format) || isLiteral format) $ unless ('%' `elem` concat (oversimplify format) || isLiteral format) $
info (getId format) 2059 info (getId format) 2059
"Don't use variables in the printf format string. Use printf \"..%s..\" \"$foo\"." "Don't use variables in the printf format string. Use printf \"..%s..\" \"$foo\"."
where
onlyTrailingTs format argCount =
all (== 'T') $ drop argCount format
prop_checkGetPrintfFormats1 = getPrintfFormats "%s" == "s"
prop_checkGetPrintfFormats2 = getPrintfFormats "%0*s" == "*s"
prop_checkGetPrintfFormats3 = getPrintfFormats "%(%s)T" == "T"
prop_checkGetPrintfFormats4 = getPrintfFormats "%d%%%(%s)T" == "dT"
prop_checkGetPrintfFormats5 = getPrintfFormats "%bPassed: %d, %bFailed: %d%b, Skipped: %d, %bErrored: %d%b\\n" == "bdbdbdbdb"
getPrintfFormats = getFormats
where
-- Get the arguments in the string as a string of type characters,
-- e.g. "Hello %s" -> "s" and "%(%s)T %0*d\n" -> "T*d"
getFormats :: String -> String
getFormats string =
case string of
'%':'%':rest -> getFormats rest
'%':'(':rest ->
case dropWhile (/= ')') rest of
')':c:trailing -> c : getFormats trailing
_ -> ""
'%':rest -> regexBasedGetFormats rest
_:rest -> getFormats rest
[] -> ""
regexBasedGetFormats rest =
case matchRegex re rest of
Just [width, precision, typ, rest] ->
(if width == "*" then "*" else "") ++
(if precision == "*" then "*" else "") ++
typ ++ getFormats rest
Nothing -> take 1 rest ++ getFormats rest
where
-- constructed based on specifications in "man printf"
re = mkRegex "#?-?\\+? ?0?(\\*|\\d*)\\.?(\\d*|\\*)([diouxXfFeEgGaAcsbq])(.*)"
-- \____ _____/\___ ____/ \____ ____/\_________ _________/ \ /
-- V V V V V
-- flags field width precision format character rest
-- field width and precision can be specified with a '*' instead of a digit,
-- in which case printf will accept one more argument for each '*' used
prop_checkUuoeCmd1 = verify checkUuoeCmd "echo $(date)" prop_checkUuoeCmd1 = verify checkUuoeCmd "echo $(date)"
@ -1042,5 +1077,16 @@ checkSourceArgs = CommandCheck (Exactly ".") f
"The dot command does not support arguments in sh/dash. Set them as variables." "The dot command does not support arguments in sh/dash. Set them as variables."
_ -> return () _ -> return ()
prop_checkChmodDashr1 = verify checkChmodDashr "chmod -r 0755 dir"
prop_checkChmodDashr2 = verifyNot checkChmodDashr "chmod -R 0755 dir"
prop_checkChmodDashr3 = verifyNot checkChmodDashr "chmod a-r dir"
checkChmodDashr = CommandCheck (Basename "chmod") f
where
f t = mapM_ check $ arguments t
check t = potentially $ do
flag <- getLiteralString t
guard $ flag == "-r"
return $ warn (getId t) 2253 "Use -R to recurse, or explicitly a-r to remove read permissions."
return [] return []
runTests = $( [| $(forAllProperties) (quickCheckWithResult (stdArgs { maxSuccess = 1 }) ) |]) runTests = $( [| $(forAllProperties) (quickCheckWithResult (stdArgs { maxSuccess = 1 }) ) |])

View File

@ -0,0 +1,21 @@
{-
This empty file is provided for ease of patching in site specific checks.
However, there are no guarantees regarding compatibility between versions.
-}
{-# LANGUAGE TemplateHaskell #-}
module ShellCheck.Checks.Custom (checker, ShellCheck.Checks.Custom.runTests) where
import ShellCheck.AnalyzerLib
import Test.QuickCheck
checker :: Parameters -> Checker
checker params = Checker {
perScript = const $ return (),
perToken = const $ return ()
}
prop_CustomTestsWork = True
return []
runTests = $quickCheckAll

View File

@ -174,6 +174,9 @@ prop_checkBashisms90 = verifyNot checkBashisms "#!/bin/sh\nset -o \"$opt\""
prop_checkBashisms91 = verify checkBashisms "#!/bin/sh\nwait -n" prop_checkBashisms91 = verify checkBashisms "#!/bin/sh\nwait -n"
prop_checkBashisms92 = verify checkBashisms "#!/bin/sh\necho $((16#FF))" prop_checkBashisms92 = verify checkBashisms "#!/bin/sh\necho $((16#FF))"
prop_checkBashisms93 = verify checkBashisms "#!/bin/sh\necho $(( 10#$(date +%m) ))" prop_checkBashisms93 = verify checkBashisms "#!/bin/sh\necho $(( 10#$(date +%m) ))"
prop_checkBashisms94 = verify checkBashisms "#!/bin/sh\n[ -v var ]"
prop_checkBashisms95 = verify checkBashisms "#!/bin/sh\necho $_"
prop_checkBashisms96 = verifyNot checkBashisms "#!/bin/dash\necho $_"
checkBashisms = ForShell [Sh, Dash] $ \t -> do checkBashisms = ForShell [Sh, Dash] $ \t -> do
params <- ask params <- ask
kludge params t kludge params t
@ -208,6 +211,8 @@ checkBashisms = ForShell [Sh, Dash] $ \t -> do
warnMsg id "== in place of = is" warnMsg id "== in place of = is"
bashism (TC_Binary id SingleBracket "=~" _ _) = bashism (TC_Binary id SingleBracket "=~" _ _) =
warnMsg id "=~ regex matching is" warnMsg id "=~ regex matching is"
bashism (TC_Unary id SingleBracket "-v" _) =
warnMsg id "unary -v (in place of [ -n \"${var+x}\" ]) is"
bashism (TC_Unary id _ "-a" _) = bashism (TC_Unary id _ "-a" _) =
warnMsg id "unary -a in place of -e is" warnMsg id "unary -a in place of -e is"
bashism (TA_Unary id op _) bashism (TA_Unary id op _)
@ -405,10 +410,11 @@ checkBashisms = ForShell [Sh, Dash] $ \t -> do
] ]
bashVars = [ bashVars = [
"OSTYPE", "MACHTYPE", "HOSTTYPE", "HOSTNAME", "OSTYPE", "MACHTYPE", "HOSTTYPE", "HOSTNAME",
"DIRSTACK", "EUID", "UID", "SHLVL", "PIPESTATUS", "SHELLOPTS" "DIRSTACK", "EUID", "UID", "SHLVL", "PIPESTATUS", "SHELLOPTS",
"_"
] ]
bashDynamicVars = [ "RANDOM", "SECONDS" ] bashDynamicVars = [ "RANDOM", "SECONDS" ]
dashVars = [ ] dashVars = [ "_" ]
isBashVariable var = isBashVariable var =
(var `elem` bashDynamicVars (var `elem` bashDynamicVars
|| var `elem` bashVars && not (isAssigned var)) || var `elem` bashVars && not (isAssigned var))

View File

@ -36,6 +36,11 @@ internalVariables = [
-- Ksh -- Ksh
, ".sh.version" , ".sh.version"
-- shflags
, "FLAGS_ARGC", "FLAGS_ARGV", "FLAGS_ERROR", "FLAGS_FALSE", "FLAGS_HELP",
"FLAGS_PARENT", "FLAGS_RESERVED", "FLAGS_TRUE", "FLAGS_VERSION",
"flags_error", "flags_return"
] ]
specialVariablesWithoutSpaces = [ specialVariablesWithoutSpaces = [
@ -45,6 +50,9 @@ variablesWithoutSpaces = specialVariablesWithoutSpaces ++ [
"BASHPID", "BASH_ARGC", "BASH_LINENO", "BASH_SUBSHELL", "EUID", "LINENO", "BASHPID", "BASH_ARGC", "BASH_LINENO", "BASH_SUBSHELL", "EUID", "LINENO",
"OPTIND", "PPID", "RANDOM", "SECONDS", "SHELLOPTS", "SHLVL", "UID", "OPTIND", "PPID", "RANDOM", "SECONDS", "SHELLOPTS", "SHLVL", "UID",
"COLUMNS", "HISTFILESIZE", "HISTSIZE", "LINES" "COLUMNS", "HISTFILESIZE", "HISTSIZE", "LINES"
-- shflags
, "FLAGS_ERROR", "FLAGS_FALSE", "FLAGS_TRUE"
] ]
specialVariables = specialVariablesWithoutSpaces ++ ["@", "*"] specialVariables = specialVariablesWithoutSpaces ++ ["@", "*"]

View File

@ -0,0 +1,255 @@
{-
Copyright 2019 Vidar 'koala_man' Holen
This file is part of ShellCheck.
https://www.shellcheck.net
ShellCheck is free software: you can redistribute it and/or modify
it under the terms of the GNU General Public License as published by
the Free Software Foundation, either version 3 of the License, or
(at your option) any later version.
ShellCheck is distributed in the hope that it will be useful,
but WITHOUT ANY WARRANTY; without even the implied warranty of
MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the
GNU General Public License for more details.
You should have received a copy of the GNU General Public License
along with this program. If not, see <https://www.gnu.org/licenses/>.
-}
{-# LANGUAGE TemplateHaskell #-}
module ShellCheck.Formatter.Diff (format, ShellCheck.Formatter.Diff.runTests) where
import ShellCheck.Interface
import ShellCheck.Fixer
import ShellCheck.Formatter.Format
import Control.Monad
import Data.Algorithm.Diff
import Data.Array
import Data.IORef
import Data.List
import qualified Data.Monoid as Monoid
import Data.Maybe
import qualified Data.Map as M
import GHC.Exts (sortWith)
import System.IO
import System.FilePath
import Test.QuickCheck
import Debug.Trace
ltt x = trace (show x) x
format :: FormatterOptions -> IO Formatter
format options = do
didOutput <- newIORef False
shouldColor <- shouldOutputColor (foColorOption options)
let color = if shouldColor then colorize else nocolor
return Formatter {
header = return (),
footer = checkFooter didOutput color,
onFailure = reportFailure color,
onResult = reportResult didOutput color
}
contextSize = 3
red = 31
green = 32
yellow = 33
cyan = 36
bold = 1
nocolor n = id
colorize n s = (ansi n) ++ s ++ (ansi 0)
ansi n = "\x1B[" ++ show n ++ "m"
printErr :: ColorFunc -> String -> IO ()
printErr color = hPutStrLn stderr . color bold . color red
reportFailure color file msg = printErr color $ file ++ ": " ++ msg
checkFooter didOutput color = do
output <- readIORef didOutput
unless output $
printErr color "Issues were detected, but none were auto-fixable. Use another format to see them."
type ColorFunc = (Int -> String -> String)
data LFStatus = LinefeedMissing | LinefeedOk
data DiffDoc a = DiffDoc String LFStatus [DiffRegion a]
data DiffRegion a = DiffRegion (Int, Int) (Int, Int) [Diff a]
reportResult :: (IORef Bool) -> ColorFunc -> CheckResult -> SystemInterface IO -> IO ()
reportResult didOutput color result sys = do
let comments = crComments result
let suggestedFixes = mapMaybe pcFix comments
let fixmap = buildFixMap suggestedFixes
mapM_ output $ M.toList fixmap
where
output (name, fix) = do
file <- (siReadFile sys) name
case file of
Right contents -> do
putStrLn $ formatDoc color $ makeDiff name contents fix
writeIORef didOutput True
Left msg -> reportFailure color name msg
hasTrailingLinefeed str =
case str of
[] -> True
_ -> last str == '\n'
coversLastLine regions =
case regions of
[] -> False
_ -> (fst $ last regions)
-- TODO: Factor this out into a unified diff library because we're doing a lot
-- of the heavy lifting anyways.
makeDiff :: String -> String -> Fix -> DiffDoc String
makeDiff name contents fix = do
let hunks = groupDiff $ computeDiff contents fix
let lf = if coversLastLine hunks && not (hasTrailingLinefeed contents)
then LinefeedMissing
else LinefeedOk
DiffDoc name lf $ findRegions hunks
computeDiff :: String -> Fix -> [Diff String]
computeDiff contents fix =
let old = lines contents
array = listArray (1, fromIntegral $ (length old)) old
new = applyFix fix array
in getDiff old new
-- Group changes into hunks
groupDiff :: [Diff a] -> [(Bool, [Diff a])]
groupDiff = filter (\(_, l) -> not (null l)) . hunt []
where
-- Churn through 'Both's until we find a difference
hunt current [] = [(False, reverse current)]
hunt current (x@Both {}:rest) = hunt (x:current) rest
hunt current list =
let (context, previous) = splitAt contextSize current
in (False, reverse previous) : gather context 0 list
-- Pick out differences until we find a run of Both's
gather current n [] =
let (extras, patch) = splitAt (max 0 $ n - contextSize) current
in [(True, reverse patch), (False, reverse extras)]
gather current n list@(Both {}:_) | n == contextSize*2 =
let (context, previous) = splitAt contextSize current
in (True, reverse previous) : hunt context list
gather current n (x@Both {}:rest) = gather (x:current) (n+1) rest
gather current n (x:rest) = gather (x:current) 0 rest
-- Get line numbers for hunks
findRegions :: [(Bool, [Diff String])] -> [DiffRegion String]
findRegions = find' 1 1
where
find' _ _ [] = []
find' left right ((output, run):rest) =
let (dl, dr) = countDelta run
remainder = find' (left+dl) (right+dr) rest
in
if output
then DiffRegion (left, dl) (right, dr) run : remainder
else remainder
-- Get left/right line counts for a hunk
countDelta :: [Diff a] -> (Int, Int)
countDelta = count' 0 0
where
count' left right [] = (left, right)
count' left right (x:rest) =
case x of
Both {} -> count' (left+1) (right+1) rest
First {} -> count' (left+1) right rest
Second {} -> count' left (right+1) rest
formatRegion :: ColorFunc -> LFStatus -> DiffRegion String -> String
formatRegion color lf (DiffRegion left right diffs) =
let header = color cyan ("@@ -" ++ (tup left) ++ " +" ++ (tup right) ++" @@")
in
unlines $ header : reverse (getStrings lf (reverse diffs))
where
noLF = "\\ No newline at end of file"
getStrings LinefeedOk list = map format list
getStrings LinefeedMissing list@((Both _ _):_) = noLF : map format list
getStrings LinefeedMissing list@((First _):_) = noLF : map format list
getStrings LinefeedMissing (last:rest) = format last : getStrings LinefeedMissing rest
tup (a,b) = (show a) ++ "," ++ (show b)
format (Both x _) = ' ':x
format (First x) = color red $ '-':x
format (Second x) = color green $ '+':x
splitLast [] = ([], [])
splitLast x =
let (last, rest) = splitAt 1 $ reverse x
in (reverse rest, last)
formatDoc color (DiffDoc name lf regions) =
let (most, last) = splitLast regions
in
(color bold $ "--- " ++ ("a" </> name)) ++ "\n" ++
(color bold $ "+++ " ++ ("b" </> name)) ++ "\n" ++
concatMap (formatRegion color LinefeedOk) most ++
concatMap (formatRegion color lf) last
-- Create a Map from filename to Fix
buildFixMap :: [Fix] -> M.Map String Fix
buildFixMap fixes = perFile
where
splitFixes = concatMap splitFixByFile fixes
perFile = groupByMap (posFile . repStartPos . head . fixReplacements) splitFixes
-- There are currently no multi-file fixes, but let's handle it anyways
splitFixByFile :: Fix -> [Fix]
splitFixByFile fix = map makeFix $ groupBy sameFile (fixReplacements fix)
where
sameFile rep1 rep2 = (posFile $ repStartPos rep1) == (posFile $ repStartPos rep2)
makeFix reps = newFix { fixReplacements = reps }
groupByMap :: (Ord k, Monoid v) => (v -> k) -> [v] -> M.Map k v
groupByMap f = M.fromListWith Monoid.mappend . map (\x -> (f x, x))
-- For building unit tests
b n = Both n n
l = First
r = Second
prop_identifiesProperContext = groupDiff [b 1, b 2, b 3, b 4, l 5, b 6, b 7, b 8, b 9] ==
[(False, [b 1]), -- Omitted
(True, [b 2, b 3, b 4, l 5, b 6, b 7, b 8]), -- A change with three lines of context
(False, [b 9])] -- Omitted
prop_includesContextFromStartIfNecessary = groupDiff [b 4, l 5, b 6, b 7, b 8, b 9] ==
[ -- Nothing omitted
(True, [b 4, l 5, b 6, b 7, b 8]), -- A change with three lines of context
(False, [b 9])] -- Omitted
prop_includesContextUntilEndIfNecessary = groupDiff [b 4, l 5] ==
[ -- Nothing omitted
(True, [b 4, l 5])
] -- Nothing Omitted
prop_splitsIntoMultipleHunks = groupDiff [l 1, b 1, b 2, b 3, b 4, b 5, b 6, b 7, r 8] ==
[ -- Nothing omitted
(True, [l 1, b 1, b 2, b 3]),
(False, [b 4]),
(True, [b 5, b 6, b 7, r 8])
] -- Nothing Omitted
prop_splitsIntoMultipleHunksUnlessTouching = groupDiff [l 1, b 1, b 2, b 3, b 4, b 5, b 6, r 7] ==
[
(True, [l 1, b 1, b 2, b 3, b 4, b 5, b 6, r 7])
]
prop_countDeltasWorks = countDelta [b 1, l 2, r 3, r 4, b 5] == (3,4)
prop_countDeltasWorks2 = countDelta [] == (0,0)
return []
runTests = $quickCheckAll

View File

@ -22,8 +22,12 @@ module ShellCheck.Formatter.Format where
import ShellCheck.Data import ShellCheck.Data
import ShellCheck.Interface import ShellCheck.Interface
import ShellCheck.Fixer import ShellCheck.Fixer
import Control.Monad import Control.Monad
import Data.Array import Data.Array
import Data.List
import System.IO
import System.Info
-- A formatter that carries along an arbitrary piece of data -- A formatter that carries along an arbitrary piece of data
data Formatter = Formatter { data Formatter = Formatter {
@ -59,6 +63,17 @@ makeNonVirtual comments contents =
fixReplacements = map (\r -> removeTabStops r arr) (fixReplacements f) fixReplacements = map (\r -> removeTabStops r arr) (fixReplacements f)
} }
fix c = (removeTabStops c arr) { fix c = (removeTabStops c arr) {
pcFix = liftM untabbedFix (pcFix c) pcFix = fmap untabbedFix (pcFix c)
} }
shouldOutputColor :: ColorOption -> IO Bool
shouldOutputColor colorOption = do
term <- hIsTerminalDevice stdout
let windows = "mingw" `isPrefixOf` os
let isUsableTty = term && not windows
let useColor = case colorOption of
ColorAlways -> True
ColorNever -> False
ColorAuto -> isUsableTty
return useColor

View File

@ -30,12 +30,12 @@ import GHC.Exts
import System.IO import System.IO
import qualified Data.ByteString.Lazy.Char8 as BL import qualified Data.ByteString.Lazy.Char8 as BL
format :: Bool -> IO Formatter format :: IO Formatter
format removeTabs = do format = do
ref <- newIORef [] ref <- newIORef []
return Formatter { return Formatter {
header = return (), header = return (),
onResult = collectResult removeTabs ref, onResult = collectResult ref,
onFailure = outputError, onFailure = outputError,
footer = finish ref footer = finish ref
} }
@ -98,19 +98,12 @@ instance ToJSON Fix where
outputError file msg = hPutStrLn stderr $ file ++ ": " ++ msg outputError file msg = hPutStrLn stderr $ file ++ ": " ++ msg
collectResult removeTabs ref cr sys = mapM_ f groups collectResult ref cr sys = mapM_ f groups
where where
comments = crComments cr comments = crComments cr
groups = groupWith sourceFile comments groups = groupWith sourceFile comments
f :: [PositionedComment] -> IO () f :: [PositionedComment] -> IO ()
f group = do f group = modifyIORef ref (\x -> comments ++ x)
let filename = sourceFile (head group)
result <- siReadFile sys filename
let contents = either (const "") id result
let comments' = if removeTabs
then makeNonVirtual comments contents
else comments
modifyIORef ref (\x -> comments' ++ x)
finish ref = do finish ref = do
list <- readIORef ref list <- readIORef ref

View File

@ -0,0 +1,127 @@
{-# LANGUAGE OverloadedStrings #-}
{-
Copyright 2012-2019 Vidar Holen
This file is part of ShellCheck.
https://www.shellcheck.net
ShellCheck is free software: you can redistribute it and/or modify
it under the terms of the GNU General Public License as published by
the Free Software Foundation, either version 3 of the License, or
(at your option) any later version.
ShellCheck is distributed in the hope that it will be useful,
but WITHOUT ANY WARRANTY; without even the implied warranty of
MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the
GNU General Public License for more details.
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.Formatter.JSON1 (format) where
import ShellCheck.Interface
import ShellCheck.Formatter.Format
import Data.Aeson
import Data.IORef
import Data.Monoid
import GHC.Exts
import System.IO
import qualified Data.ByteString.Lazy.Char8 as BL
format :: IO Formatter
format = do
ref <- newIORef []
return Formatter {
header = return (),
onResult = collectResult ref,
onFailure = outputError,
footer = finish ref
}
data Json1Output = Json1Output {
comments :: [PositionedComment]
}
instance ToJSON Json1Output where
toJSON result = object [
"comments" .= comments result
]
toEncoding result = pairs (
"comments" .= comments result
)
instance ToJSON Replacement where
toJSON replacement =
let start = repStartPos replacement
end = repEndPos replacement
str = repString replacement in
object [
"precedence" .= repPrecedence replacement,
"insertionPoint" .=
case repInsertionPoint replacement of
InsertBefore -> "beforeStart" :: String
InsertAfter -> "afterEnd",
"line" .= posLine start,
"column" .= posColumn start,
"endLine" .= posLine end,
"endColumn" .= posColumn end,
"replacement" .= str
]
instance ToJSON PositionedComment where
toJSON comment =
let start = pcStartPos comment
end = pcEndPos comment
c = pcComment comment in
object [
"file" .= posFile start,
"line" .= posLine start,
"endLine" .= posLine end,
"column" .= posColumn start,
"endColumn" .= posColumn end,
"level" .= severityText comment,
"code" .= cCode c,
"message" .= cMessage c,
"fix" .= pcFix comment
]
toEncoding comment =
let start = pcStartPos comment
end = pcEndPos comment
c = pcComment comment in
pairs (
"file" .= posFile start
<> "line" .= posLine start
<> "endLine" .= posLine end
<> "column" .= posColumn start
<> "endColumn" .= posColumn end
<> "level" .= severityText comment
<> "code" .= cCode c
<> "message" .= cMessage c
<> "fix" .= pcFix comment
)
instance ToJSON Fix where
toJSON fix = object [
"replacements" .= fixReplacements fix
]
outputError file msg = hPutStrLn stderr $ file ++ ": " ++ msg
collectResult ref cr sys = mapM_ f groups
where
comments = crComments cr
groups = groupWith sourceFile comments
f :: [PositionedComment] -> IO ()
f group = do
let filename = sourceFile (head group)
result <- siReadFile sys filename
let contents = either (const "") id result
let comments' = makeNonVirtual comments contents
modifyIORef ref (\x -> comments' ++ x)
finish ref = do
list <- readIORef ref
BL.putStrLn $ encode $ Json1Output { comments = list }

View File

@ -27,8 +27,7 @@ import Data.IORef
import System.Exit import System.Exit
format :: FormatterOptions -> IO Formatter format :: FormatterOptions -> IO Formatter
format options = do format options =
topErrorRef <- newIORef []
return Formatter { return Formatter {
header = return (), header = return (),
footer = return (), footer = return (),

View File

@ -188,13 +188,7 @@ code num = "SC" ++ show num
getColorFunc :: ColorOption -> IO ColorFunc getColorFunc :: ColorOption -> IO ColorFunc
getColorFunc colorOption = do getColorFunc colorOption = do
term <- hIsTerminalDevice stdout useColor <- shouldOutputColor colorOption
let windows = "mingw" `isPrefixOf` os
let isUsableTty = term && not windows
let useColor = case colorOption of
ColorAlways -> True
ColorNever -> False
ColorAuto -> isUsableTty
return $ if useColor then colorComment else const id return $ if useColor then colorComment else const id
where where
colorComment level comment = colorComment level comment =

View File

@ -138,7 +138,6 @@ almostSpace =
return ' ' return ' '
--------- Message/position annotation on top of user state --------- Message/position annotation on top of user state
data Note = Note Id Severity Code String deriving (Show, Eq)
data ParseNote = ParseNote SourcePos SourcePos Severity Code String deriving (Show, Eq) data ParseNote = ParseNote SourcePos SourcePos Severity Code String deriving (Show, Eq)
data Context = data Context =
ContextName SourcePos String ContextName SourcePos String
@ -166,10 +165,6 @@ initialUserState = UserState {
} }
codeForParseNote (ParseNote _ _ _ code _) = code codeForParseNote (ParseNote _ _ _ code _) = code
noteToParseNote map (Note id severity code message) =
ParseNote pos pos severity code message
where
pos = fromJust $ Map.lookup id map
getLastId = lastId <$> getState getLastId = lastId <$> getState
@ -1529,10 +1524,10 @@ ensureDollar =
readNormalDollar = do readNormalDollar = do
ensureDollar ensureDollar
readDollarExp <|> readDollarDoubleQuote <|> readDollarSingleQuote <|> readDollarLonely readDollarExp <|> readDollarDoubleQuote <|> readDollarSingleQuote <|> readDollarLonely False
readDoubleQuotedDollar = do readDoubleQuotedDollar = do
ensureDollar ensureDollar
readDollarExp <|> readDollarLonely readDollarExp <|> readDollarLonely True
prop_readDollarExpression1 = isOk readDollarExpression "$(((1) && 3))" prop_readDollarExpression1 = isOk readDollarExpression "$(((1) && 3))"
@ -1694,12 +1689,32 @@ readVariableName = do
rest <- many variableChars rest <- many variableChars
return (f:rest) return (f:rest)
readDollarLonely = do
prop_readDollarLonely1 = isWarning readNormalWord "\"$\"var"
prop_readDollarLonely2 = isWarning readNormalWord "\"$\"\"var\""
prop_readDollarLonely3 = isOk readNormalWord "\"$\"$var"
prop_readDollarLonely4 = isOk readNormalWord "\"$\"*"
prop_readDollarLonely5 = isOk readNormalWord "$\"str\""
readDollarLonely quoted = do
start <- startSpan start <- startSpan
char '$' char '$'
id <- endSpan start id <- endSpan start
n <- lookAhead (anyChar <|> (eof >> return '_')) when quoted $ do
isHack <- quoteForEscape
when isHack $
parseProblemAtId id StyleC 1135
"Prefer escape over ending quote to make $ literal. Instead of \"It costs $\"5, use \"It costs \\$5\"."
return $ T_Literal id "$" return $ T_Literal id "$"
where
quoteForEscape = option False $ try . lookAhead $ do
char '"'
-- Check for "foo $""bar"
optional $ char '"'
c <- anyVar
-- Don't trigger on [[ x == "$"* ]] or "$"$pattern
return $ c `notElem` "*$"
anyVar = variableStart <|> digit <|> specialVariable
prop_readHereDoc = isOk readScript "cat << foo\nlol\ncow\nfoo" prop_readHereDoc = isOk readScript "cat << foo\nlol\ncow\nfoo"
prop_readHereDoc2 = isNotOk readScript "cat <<- EOF\n cow\n EOF" prop_readHereDoc2 = isNotOk readScript "cat <<- EOF\n cow\n EOF"
@ -2750,7 +2765,7 @@ readAssignmentWordExt lenient = try $ do
variable <- readVariableName variable <- readVariableName
when lenient $ when lenient $
optional (readNormalDollar >> parseNoteAt pos ErrorC optional (readNormalDollar >> parseNoteAt pos ErrorC
1067 "For indirection, use (associative) arrays or 'read \"var$n\" <<< \"value\"'") 1067 "For indirection, use arrays, declare \"var$n=value\", or (for sh) read/eval.")
indices <- many readArrayIndex indices <- many readArrayIndex
hasLeftSpace <- fmap (not . null) spacing hasLeftSpace <- fmap (not . null) spacing
pos <- getPosition pos <- getPosition
@ -2790,10 +2805,11 @@ readAssignmentWordExt lenient = try $ do
string "=" >> return Assign string "=" >> return Assign
] ]
readEmptyLiteral = do
start <- startSpan readEmptyLiteral = do
id <- endSpan start start <- startSpan
return $ T_Literal id "" id <- endSpan start
return $ T_Literal id ""
readArrayIndex = do readArrayIndex = do
start <- startSpan start <- startSpan
@ -2941,12 +2957,14 @@ prop_readShebang5 = isWarning readShebang "\n#!/bin/sh"
prop_readShebang6 = isWarning readShebang " # Copyright \n!#/bin/bash" prop_readShebang6 = isWarning readShebang " # Copyright \n!#/bin/bash"
prop_readShebang7 = isNotOk readShebang "# Copyright \nfoo\n#!/bin/bash" prop_readShebang7 = isNotOk readShebang "# Copyright \nfoo\n#!/bin/bash"
readShebang = do readShebang = do
start <- startSpan
anyShebang <|> try readMissingBang <|> withHeader anyShebang <|> try readMissingBang <|> withHeader
many linewhitespace many linewhitespace
str <- many $ noneOf "\r\n" str <- many $ noneOf "\r\n"
id <- endSpan start
optional carriageReturn optional carriageReturn
optional linefeed optional linefeed
return str return $ T_Literal id str
where where
anyShebang = choice $ map try [ anyShebang = choice $ map try [
readCorrect, readCorrect,
@ -3077,7 +3095,8 @@ readScriptFile sourced = do
readUtf8Bom readUtf8Bom
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 shebang <- readShebang <|> readEmptyLiteral
let (T_Literal _ shebangString) = shebang
allspacing allspacing
annotationStart <- startSpan annotationStart <- startSpan
fileAnnotations <- readAnnotations fileAnnotations <- readAnnotations
@ -3094,19 +3113,19 @@ readScriptFile sourced = do
let ignoreShebang = shellAnnotationSpecified || shellFlagSpecified let ignoreShebang = shellAnnotationSpecified || shellFlagSpecified
unless ignoreShebang $ unless ignoreShebang $
verifyShebang pos (getShell sb) verifyShebang pos (getShell shebangString)
if ignoreShebang || isValidShell (getShell sb) /= Just False if ignoreShebang || isValidShell (getShell shebangString) /= Just False
then do then do
commands <- withAnnotations annotations readCompoundListOrEmpty commands <- withAnnotations annotations readCompoundListOrEmpty
id <- endSpan start id <- endSpan start
verifyEof verifyEof
let script = T_Annotation annotationId annotations $ let script = T_Annotation annotationId annotations $
T_Script id sb commands T_Script id shebang commands
reparseIndices script reparseIndices script
else do else do
many anyChar many anyChar
id <- endSpan start id <- endSpan start
return $ T_Script id sb [] return $ T_Script id shebang []
where where
basename s = reverse . takeWhile (/= '/') . reverse $ s basename s = reverse . takeWhile (/= '/') . reverse $ s

View File

@ -2,7 +2,7 @@
# For more information, see: https://docs.haskellstack.org/en/stable/yaml_configuration/ # For more information, see: https://docs.haskellstack.org/en/stable/yaml_configuration/
# Specifies the GHC version and set of packages available (e.g., lts-3.5, nightly-2015-09-21, ghc-7.10.2) # Specifies the GHC version and set of packages available (e.g., lts-3.5, nightly-2015-09-21, ghc-7.10.2)
resolver: lts-8.5 resolver: lts-13.26
# Local packages, usually specified by relative directory name # Local packages, usually specified by relative directory name
packages: packages:

View File

@ -6,8 +6,10 @@ import qualified ShellCheck.Analytics
import qualified ShellCheck.AnalyzerLib import qualified ShellCheck.AnalyzerLib
import qualified ShellCheck.Checker import qualified ShellCheck.Checker
import qualified ShellCheck.Checks.Commands import qualified ShellCheck.Checks.Commands
import qualified ShellCheck.Checks.Custom
import qualified ShellCheck.Checks.ShellSupport import qualified ShellCheck.Checks.ShellSupport
import qualified ShellCheck.Fixer import qualified ShellCheck.Fixer
import qualified ShellCheck.Formatter.Diff
import qualified ShellCheck.Parser import qualified ShellCheck.Parser
main = do main = do
@ -17,8 +19,10 @@ main = do
,ShellCheck.AnalyzerLib.runTests ,ShellCheck.AnalyzerLib.runTests
,ShellCheck.Checker.runTests ,ShellCheck.Checker.runTests
,ShellCheck.Checks.Commands.runTests ,ShellCheck.Checks.Commands.runTests
,ShellCheck.Checks.Custom.runTests
,ShellCheck.Checks.ShellSupport.runTests ,ShellCheck.Checks.ShellSupport.runTests
,ShellCheck.Fixer.runTests ,ShellCheck.Fixer.runTests
,ShellCheck.Formatter.Diff.runTests
,ShellCheck.Parser.runTests ,ShellCheck.Parser.runTests
] ]
if and results if and results