module ShellCheck.Analytics where
import ShellCheck.AST
import ShellCheck.Data
import ShellCheck.Parser
import Control.Monad
import Control.Monad.State
import qualified Data.Map as Map
import Data.Char
import Data.Functor
import Data.List
import Data.Maybe
import Debug.Trace
import Text.Regex
import Data.Maybe
data Shell = Ksh | Zsh | Sh | Bash
deriving (Show, Eq)
genericChecks = [
runBasicAnalysis (\x -> mapM_ (flip ($) x) basicChecks)
,runBasicTreeAnalysis treeChecks
,subshellAssignmentCheck
,checkSpacefulness
,checkQuotesInLiterals
,checkShebang
,checkFunctionsUsedExternally
,checkUnusedAssignments
,checkWrongArithmeticAssignment
]
checksFor Sh = map runBasicAnalysis [
checkBashisms
,checkTimeParameters
,checkCdAndBack Sh
]
checksFor Ksh = map runBasicAnalysis [
checkEchoSed
,checkCdAndBack Ksh
]
checksFor Zsh = map runBasicAnalysis [
checkTimeParameters
,checkEchoSed
,checkCdAndBack Zsh
]
checksFor Bash = map runBasicAnalysis [
checkTimeParameters
,checkBraceExpansionVars
,checkEchoSed
,checkCdAndBack Bash
]
runAllAnalytics root m = addToMap notes m
where shell = determineShell root
notes = checkList ((checksFor shell) ++ genericChecks) root
checkList l t = concatMap (\f -> f t) l
addToMap list map = foldr (\(id,note) m -> Map.adjust (\(Metadata pos notes) -> Metadata pos (note:notes)) id m) map list
prop_determineShell0 = determineShell (T_Script (Id 0) "#!/bin/sh" []) == Sh
prop_determineShell1 = determineShell (T_Script (Id 0) "#!/usr/bin/env ksh" []) == Ksh
prop_determineShell2 = determineShell (T_Script (Id 0) "" []) == Bash
determineShell (T_Script _ shebang _) = normalize $ shellFor shebang
where shellFor s | "/env " `isInfixOf` s = head ((drop 1 $ words s)++[""])
shellFor s = reverse . takeWhile (/= '/') . reverse $ s
normalize "sh" = Sh
normalize "ksh" = Ksh
normalize "zsh" = Zsh
normalize "bash" = Bash
normalize _ = Bash
runBasicAnalysis f t = snd $ runState (doAnalysis f t) []
basicChecks = [
checkUuoc
,checkPipePitfalls
,checkForInQuoted
,checkForInLs
,checkShorthandIf
,checkDollarStar
,checkUnquotedDollarAt
,checkStderrRedirect
,checkUnquotedN
,checkNumberComparisons
,checkSingleBracketOperators
,checkDoubleBracketOperators
,checkNoaryWasBinary
,checkConstantNoary
,checkForDecimals
,checkDivBeforeMult
,checkArithmeticDeref
,checkArithmeticBadOctal
,checkComparisonAgainstGlob
,checkPrintfVar
,checkCommarrays
,checkOrNeq
,checkEchoWc
,checkConstantIfs
,checkTr
,checkPipedAssignment
,checkAssignAteCommand
,checkUuoe
,checkFindNameGlob
,checkGrepRe
,checkNeedlessCommands
,checkQuotedCondRegex
,checkForInCat
,checkFindExec
,checkValidCondOps
,checkGlobbedRegex
,checkTrapQuotes
,checkTestRedirects
,checkIndirectExpansion
,checkSudoRedirect
,checkPS1Assignments
,checkBackticks
,checkInexplicablyUnquoted
,checkTildeInQuotes
,checkLonelyDotDash
,checkSpuriousExec
,checkSpuriousExpansion
,checkUnusedEchoEscapes
,checkDollarBrackets
,checkSshHereDoc
,checkSshCommandString
,checkGlobsAsOptions
,checkWhileReadPitfalls
,checkArithmeticOpCommand
,checkCharRangeGlob
]
treeChecks = [
checkUnquotedExpansions
,checkSingleQuotedVariables
,checkRedirectToSame
,checkPrefixAssignmentReference
]
runBasicTreeAnalysis checks token =
checkList (map runTree checks) token
where
parentTree = getParentTree token
runTree f t = runBasicAnalysis (flip f $ parentTree) t
filterByAnnotation token metadataMap =
Map.mapWithKey removeVals metadataMap
where
removeVals id (Metadata pos notes) =
Metadata pos $ filter (not . shouldIgnore id . numFor) notes
numFor (Note _ code _) = code
shouldIgnore id num =
any (shouldIgnoreFor num) $ getPath parents (T_Bang id)
shouldIgnoreFor num (T_Annotation _ anns _) =
any hasNum anns
where
hasNum (DisableComment ts) = num == ts
shouldIgnoreFor _ _ = False
parents = getParentTree token
addNoteFor id note = modify ((id, note):)
warn id code note = addNoteFor id $ Note WarningC code $ note
err id code note = addNoteFor id $ Note ErrorC code $ note
info id code note = addNoteFor id $ Note InfoC code $ note
style id code note = addNoteFor id $ Note StyleC code $ note
isVariableStartChar x = x == '_' || x >= 'a' && x <= 'z' || x >= 'A' && x <= 'Z'
isVariableChar x = isVariableStartChar x || x >= '0' && x <= '9'
prop_isVariableName1 = isVariableName "_fo123"
prop_isVariableName2 = not $ isVariableName "4"
prop_isVariableName3 = not $ isVariableName "test: "
isVariableName (x:r) = isVariableStartChar x && all isVariableChar r
isVariableName _ = False
willSplit x =
case x of
T_DollarBraced _ _ -> True
T_DollarExpansion _ _ -> True
T_Backticked _ _ -> True
T_BraceExpansion _ s -> True
T_Glob _ _ -> True
T_Extglob _ _ _ -> True
T_NormalWord _ l -> any willSplit l
_ -> False
isGlob (T_Extglob _ _ _) = True
isGlob (T_Glob _ _) = True
isGlob (T_NormalWord _ l) = any isGlob l
isGlob _ = False
wouldHaveBeenGlob s = '*' `elem` s
isConfusedGlobRegex ('*':_) = True
isConfusedGlobRegex [x,'*'] | x /= '\\' = True
isConfusedGlobRegex _ = False
isPotentiallyConfusedGlobRegex =
let re = mkRegex "[a-z1-9]\\*" in
isJust . matchRegex re
matches string regex = isJust $ matchRegex regex string
headOrDefault _ (a:_) = a
headOrDefault def _ = def
isConstant token =
case token of
T_NormalWord _ l -> all isConstant l
T_DoubleQuoted _ l -> all isConstant l
T_SingleQuoted _ _ -> True
T_Literal _ _ -> True
_ -> False
isEmpty token =
case token of
T_NormalWord _ l -> all isEmpty l
T_DoubleQuoted _ l -> all isEmpty l
T_SingleQuoted _ "" -> True
T_Literal _ "" -> True
_ -> False
makeSimple (T_NormalWord _ [f]) = f
makeSimple (T_Redirecting _ _ f) = f
makeSimple (T_Annotation _ _ f) = f
makeSimple t = t
simplify = doTransform makeSimple
deadSimple (T_NormalWord _ l) = [concat (concatMap (deadSimple) l)]
deadSimple (T_DoubleQuoted _ l) = [(concat (concatMap (deadSimple) l))]
deadSimple (T_SingleQuoted _ s) = [s]
deadSimple (T_DollarBraced _ _) = ["${VAR}"]
deadSimple (T_DollarArithmetic _ _) = ["${VAR}"]
deadSimple (T_DollarExpansion _ _) = ["${VAR}"]
deadSimple (T_Backticked _ _) = ["${VAR}"]
deadSimple (T_Glob _ s) = [s]
deadSimple (T_Pipeline _ [x]) = deadSimple x
deadSimple (T_Literal _ x) = [x]
deadSimple (T_SimpleCommand _ vars words) = concatMap (deadSimple) words
deadSimple (T_Redirecting _ _ foo) = deadSimple foo
deadSimple (T_DollarSingleQuoted _ s) = [s]
deadSimple (T_Annotation _ _ s) = deadSimple s
deadSimple _ = []
(!!!) list i =
case drop i list of
[] -> Nothing
(r:_) -> Just r
verify f s = checkBasic f s == Just True
verifyNot f s = checkBasic f s == Just False
verifyFull f s = checkFull f s == Just True
verifyNotFull f s = checkFull f s == Just False
verifyTree f s = checkTree f s == Just True
verifyNotTree f s = checkTree f s == Just False
checkBasic f s = checkFull (runBasicAnalysis f) s
checkTree f s = checkFull (runBasicTreeAnalysis [f]) s
checkFull f s = case parseShell "-" s of
(ParseResult (Just (t, m)) _) -> Just . not . null $ f t
_ -> Nothing
prop_checkEchoWc3 = verify checkEchoWc "n=$(echo $foo | wc -c)"
checkEchoWc (T_Pipeline id [a, b]) =
when (acmd == ["echo", "${VAR}"]) $
case bcmd of
["wc", "-c"] -> countMsg
["wc", "-m"] -> countMsg
_ -> return ()
where
acmd = deadSimple a
bcmd = deadSimple b
countMsg = style id 2000 $ "See if you can use ${#variable} instead."
checkEchoWc _ = return ()
prop_checkEchoSed1 = verify checkEchoSed "FOO=$(echo \"$cow\" | sed 's/foo/bar/g')"
prop_checkEchoSed2 = verify checkEchoSed "rm $(echo $cow | sed -e 's,foo,bar,')"
checkEchoSed (T_Pipeline id [a, b]) =
when (acmd == ["echo", "${VAR}"]) $
case bcmd of
["sed", v] -> checkIn v
["sed", "-e", v] -> checkIn v
_ -> return ()
where
sedRe = mkRegex "^s(.)(.*)\\1(.*)\\1g?$"
acmd = deadSimple a
bcmd = deadSimple b
checkIn s =
case matchRegex sedRe s of
Just _ -> style id 2001 $ "See if you can use ${variable//search/replace} instead."
_ -> return ()
checkEchoSed _ = return ()
prop_checkPipedAssignment1 = verify checkPipedAssignment "A=ls | grep foo"
prop_checkPipedAssignment2 = verifyNot checkPipedAssignment "A=foo cmd | grep foo"
prop_checkPipedAssignment3 = verifyNot checkPipedAssignment "A=foo"
checkPipedAssignment (T_Pipeline _ (T_Redirecting _ _ (T_SimpleCommand id (_:_) []):_:_)) =
warn id 2036 "If you wanted to assign the output of the pipeline, use a=$(b | c) ."
checkPipedAssignment _ = return ()
prop_checkAssignAteCommand1 = verify checkAssignAteCommand "A=ls -l"
prop_checkAssignAteCommand2 = verify checkAssignAteCommand "A=ls --sort=$foo"
prop_checkAssignAteCommand3 = verify checkAssignAteCommand "A=cat foo | grep bar"
prop_checkAssignAteCommand4 = verifyNot checkAssignAteCommand "A=foo ls -l"
prop_checkAssignAteCommand5 = verifyNot checkAssignAteCommand "PAGER=cat grep bar"
checkAssignAteCommand (T_SimpleCommand id ((T_Assignment _ _ _ _ assignmentTerm):[]) (firstWord:_)) =
when ("-" `isPrefixOf` (concat $ deadSimple firstWord) ||
(isCommonCommand (getLiteralString assignmentTerm) && not (isCommonCommand (getLiteralString firstWord)))) $
warn id 2037 "To assign the output of a command, use var=$(cmd) ."
where
isCommonCommand (Just s) = s `elem` commonCommands
isCommonCommand _ = False
checkAssignAteCommand _ = return ()
prop_checkArithmeticOpCommand1 = verify checkArithmeticOpCommand "i=i + 1"
prop_checkArithmeticOpCommand2 = verify checkArithmeticOpCommand "foo=bar * 2"
prop_checkArithmeticOpCommand3 = verifyNot checkArithmeticOpCommand "foo + opts"
checkArithmeticOpCommand (T_SimpleCommand id ((T_Assignment _ _ _ _ _):[]) (firstWord:_)) =
fromMaybe (return ()) $ check <$> getGlobOrLiteralString firstWord
where
check op =
when (op `elem` ["+", "-", "*", "/"]) $
warn (getId firstWord) 2099 $
"Use $((..)) for arithmetics, e.g. i=$((i " ++ op ++ " 2))"
checkArithmeticOpCommand _ = return ()
prop_checkWrongArit = verifyFull checkWrongArithmeticAssignment "i=i+1"
prop_checkWrongArit2 = verifyFull checkWrongArithmeticAssignment "n=2; i=n*2"
checkWrongArithmeticAssignment t = runBasicAnalysis f t
where
regex = mkRegex "^([_a-zA-Z][_a-zA-Z0-9]*)([+*-]).+$"
flow = getVariableFlow t
references = foldl (flip ($)) Map.empty (map insertRef flow)
insertRef (Assignment (_, _, name, _)) =
Map.insert name ()
insertRef _ = id
getNormalString (T_NormalWord _ words) = do
parts <- foldl (liftM2 (\x y -> x ++ [y])) (Just []) $ map getLiterals words
return $ concat parts
getNormalString _ = Nothing
getLiterals (T_Literal _ s) = return s
getLiterals (T_Glob _ s) = return s
getLiterals _ = Nothing
f (T_SimpleCommand id ((T_Assignment _ _ _ _ val):[]) []) =
fromMaybe (return ()) $ do
str <- getNormalString val
match <- matchRegex regex str
var <- match !!! 0
op <- match !!! 1
Map.lookup var references
return $ do
warn (getId val) 2100 $
"Use $((..)) for arithmetics, e.g. i=$((i " ++ op ++ " 2))"
f _ = return ()
prop_checkUuoc1 = verify checkUuoc "cat foo | grep bar"
prop_checkUuoc2 = verifyNot checkUuoc "cat * | grep bar"
prop_checkUuoc3 = verify checkUuoc "cat $var | grep bar"
prop_checkUuoc4 = verifyNot checkUuoc "cat $var"
checkUuoc (T_Pipeline _ ((T_Redirecting _ _ cmd):_:_)) = checkCommand "cat" f cmd
where
f [word] = when (isSimple word) $
style (getId word) 2002 "Useless cat. Consider 'cmd < file | ..' or 'cmd file | ..' instead."
f _ = return ()
isSimple (T_NormalWord _ parts) = all isSimple parts
isSimple (T_DollarBraced _ _) = True
isSimple x = not $ willSplit x
checkUuoc _ = return ()
prop_checkNeedlessCommands = verify checkNeedlessCommands "foo=$(expr 3 + 2)"
prop_checkNeedlessCommands2 = verify checkNeedlessCommands "foo=`echo \\`expr 3 + 2\\``"
prop_checkNeedlessCommands3 = verifyNot checkNeedlessCommands "foo=$(expr foo : regex)"
checkNeedlessCommands cmd@(T_SimpleCommand id _ _) |
cmd `isCommand` "expr" && (not $ ":" `elem` deadSimple cmd) =
style id 2003 "expr is antiquated. Consider rewriting this using $((..)), ${} or [[ ]]."
checkNeedlessCommands _ = return ()
prop_checkPipePitfalls3 = verify checkPipePitfalls "ls | grep -v mp3"
prop_checkPipePitfalls4 = verifyNot checkPipePitfalls "find . -print0 | xargs -0 foo"
prop_checkPipePitfalls5 = verifyNot checkPipePitfalls "ls -N | foo"
prop_checkPipePitfalls6 = verify checkPipePitfalls "find . | xargs foo"
checkPipePitfalls (T_Pipeline id commands) = do
for ["find", "xargs"] $
\(find:xargs:_) -> let args = deadSimple xargs in
when (not $ hasShortParameter args '0') $
warn (getId find) 2038 "Use either 'find .. -print0 | xargs -0 ..' or 'find .. -exec .. +' to allow for non-alphanumeric filenames."
for ["?", "echo"] $
\(_:echo:_) -> info (getId echo) 2008 "echo doesn't read from stdin, are you sure you should be piping to it?"
for' ["ps", "grep"] $
\x -> info x 2009 "Consider using pgrep instead of grepping ps output."
didLs <- liftM or . sequence $ [
for' ["ls", "grep"] $
\x -> warn x 2010 "Don't use ls | grep. Use a glob or a for loop with a condition to allow non-alphanumeric filenames.",
for' ["ls", "xargs"] $
\x -> warn x 2011 "Use 'find .. -print0 | xargs -0 ..' or 'find .. -exec .. +' to allow non-alphanumeric filenames."
]
when (not didLs) $ do
for ["ls", "?"] $
\(ls:_) -> (when (not $ hasShortParameter (deadSimple ls) 'N') $
info (getId ls) 2012 "Use find instead of ls to better handle non-alphanumeric filenames.")
return ()
where
for l f =
let indices = indexOfSublists l (map (headOrDefault "" . deadSimple) commands)
in do
mapM_ f (map (\n -> take (length l) $ drop n $ commands) indices)
return . not . null $ indices
for' l f = for l (first f)
first func (x:_) = func (getId x)
first _ _ = return ()
hasShortParameter list char = any (\x -> "-" `isPrefixOf` x && char `elem` x) list
checkPipePitfalls _ = return ()
indexOfSublists sub all = f 0 all
where
f _ [] = []
f n a@(r:rest) =
let others = f (n+1) rest in
if match sub a
then n:others
else others
match ("?":r1) (_:r2) = match r1 r2
match (x1:r1) (x2:r2) | x1 == x2 = match r1 r2
match [] _ = True
match _ _ = False
bracedString l = concat $ deadSimple l
isMagicInQuotes (T_DollarBraced _ l) | '@' `elem` (bracedString l) = True
isMagicInQuotes _ = False
prop_checkShebang1 = verifyFull checkShebang "#!/usr/bin/env bash -x\necho cow"
prop_checkShebang2 = verifyNotFull checkShebang "#! /bin/sh -l "
checkShebang (T_Script id sb _) =
if (length $ words sb) > 2 then
let note = Note ErrorC 2096 $ "On most OS, shebangs can only specify a single parameter."
in [(id, note)]
else []
prop_checkBashisms = verify checkBashisms "while read a; do :; done < <(a)"
prop_checkBashisms2 = verify checkBashisms "[ foo -nt bar ]"
prop_checkBashisms3 = verify checkBashisms "echo $((i++))"
prop_checkBashisms4 = verify checkBashisms "rm !(*.hs)"
prop_checkBashisms5 = verify checkBashisms "source file"
prop_checkBashisms6 = verify checkBashisms "[ \"$a\" == 42 ]"
prop_checkBashisms7 = verify checkBashisms "echo ${var[1]}"
prop_checkBashisms8 = verify checkBashisms "echo ${!var[@]}"
prop_checkBashisms9 = verify checkBashisms "echo ${!var*}"
prop_checkBashisms10= verify checkBashisms "echo ${var:4:12}"
prop_checkBashisms11= verifyNot checkBashisms "echo ${var:-4}"
prop_checkBashisms12= verify checkBashisms "echo ${var//foo/bar}"
prop_checkBashisms13= verify checkBashisms "exec -c env"
prop_checkBashisms14= verify checkBashisms "echo -n \"Foo: \""
prop_checkBashisms15= verify checkBashisms "let n++"
prop_checkBashisms16= verify checkBashisms "echo $RANDOM"
prop_checkBashisms17= verify checkBashisms "echo $((RANDOM%6+1))"
prop_checkBashisms18= verify checkBashisms "foo &> /dev/null"
checkBashisms = bashism
where
errMsg id s = err id 2040 $ "#!/bin/sh was specified, so " ++ s ++ " is not supported, even when sh is actually bash."
warnMsg id s = warn id 2039 $ "#!/bin/sh was specified, but " ++ s ++ " is not standard."
bashism (T_ProcSub id _ _) = errMsg id "process substitution"
bashism (T_Extglob id _ _) = warnMsg id "extglob"
bashism (T_DollarSingleQuoted id _) = warnMsg id "$'..'"
bashism (T_DollarDoubleQuoted id _) = warnMsg id "$\"..\""
bashism (T_ForArithmetic id _ _ _ _) = warnMsg id "arithmetic for loop"
bashism (T_Arithmetic id _) = warnMsg id "standalone ((..))"
bashism (T_DollarBracket id _) = warnMsg id "$[..] in place of $((..))"
bashism (T_SelectIn id _ _ _) = warnMsg id "select loop"
bashism (T_BraceExpansion id _) = warnMsg id "brace expansion"
bashism (T_Condition id DoubleBracket _) = warnMsg id "[[ ]]"
bashism (T_HereString id _) = warnMsg id "here-string"
bashism (TC_Binary id SingleBracket op _ _)
| op `elem` [ "-nt", "-ef", "\\<", "\\>", "==" ] =
warnMsg id op
bashism (TA_Unary id op _)
| op `elem` [ "|++", "|--", "++|", "--|"] =
warnMsg id (filter (/= '|') op)
bashism t@(T_SimpleCommand id _ _)
| t `isCommand` "source" =
warnMsg id "'source' in place of '.'"
bashism (T_FdRedirect id "&" (T_IoFile _ (T_Greater _) _)) = warnMsg id "&>"
bashism (T_DollarBraced id token) =
mapM_ check expansion
where
str = concat $ deadSimple token
check (regex, feature) =
when (isJust $ matchRegex regex str) $ warnMsg id feature
bashism t@(T_SimpleCommand _ _ (cmd:arg:_))
| t `isCommand` "echo" && "-" `isPrefixOf` argString =
when (not $ "--" `isPrefixOf` argString) $
warnMsg (getId arg) "echo flag"
where argString = (concat $ deadSimple arg)
bashism t@(T_SimpleCommand _ _ (cmd:arg:_))
| t `isCommand` "exec" && "-" `isPrefixOf` (concat $ deadSimple arg) =
warnMsg (getId arg) "exec flag"
bashism t@(T_SimpleCommand id _ _)
| t `isCommand` "let" = warnMsg id "'let'"
bashism t@(TA_Variable id "RANDOM") =
warnMsg id "RANDOM"
bashism _ = return()
varChars="_0-9a-zA-Z"
expansion = let re = mkRegex in [
(re $ "^[" ++ varChars ++ "]+\\[.*\\]$", "array references"),
(re $ "^![" ++ varChars ++ "]+\\[[*@]]$", "array key expansion"),
(re $ "^![" ++ varChars ++ "]+[*@]$", "name matching prefix"),
(re $ "^[" ++ varChars ++ "]+:[^-=?+]", "string indexing"),
(re $ "^[" ++ varChars ++ "]+(\\[.*\\])?/", "string replacement"),
(re $ "^RANDOM$", "$RANDOM")
]
prop_checkForInQuoted = verify checkForInQuoted "for f in \"$(ls)\"; do echo foo; done"
prop_checkForInQuoted2 = verifyNot checkForInQuoted "for f in \"$@\"; do echo foo; done"
prop_checkForInQuoted2a = verifyNot checkForInQuoted "for f in *.mp3; do echo foo; done"
prop_checkForInQuoted2b = verify checkForInQuoted "for f in \"*.mp3\"; do echo foo; done"
prop_checkForInQuoted3 = verify checkForInQuoted "for f in 'find /'; do true; done"
prop_checkForInQuoted4 = verify checkForInQuoted "for f in 1,2,3; do true; done"
prop_checkForInQuoted5 = verify checkForInQuoted "for f in ls; do true; done"
checkForInQuoted (T_ForIn _ f [T_NormalWord _ [word@(T_DoubleQuoted id list)]] _) =
when (any (\x -> willSplit x && not (isMagicInQuotes x)) list
|| (getLiteralString word >>= (return . wouldHaveBeenGlob)) == Just True) $
err id 2066 $ "Since you double quoted this, it will not word split, and the loop will only run once."
checkForInQuoted (T_ForIn _ f [T_NormalWord _ [T_SingleQuoted id s]] _) =
warn id 2041 $ "This is a literal string. To run as a command, use $(" ++ s ++ ")."
checkForInQuoted (T_ForIn _ f [T_NormalWord _ [T_Literal id s]] _) =
if ',' `elem` s
then warn id 2042 $ "Use spaces, not commas, to separate loop elements."
else warn id 2043 $ "This loop will only run once, with " ++ f ++ "='" ++ s ++ "'."
checkForInQuoted _ = return ()
prop_checkForInCat1 = verify checkForInCat "for f in $(cat foo); do stuff; done"
prop_checkForInCat1a= verify checkForInCat "for f in `cat foo`; do stuff; done"
prop_checkForInCat2 = verify checkForInCat "for f in $(cat foo | grep lol); do stuff; done"
prop_checkForInCat2a= verify checkForInCat "for f in `cat foo | grep lol`; do stuff; done"
prop_checkForInCat3 = verifyNot checkForInCat "for f in $(cat foo | grep bar | wc -l); do stuff; done"
checkForInCat (T_ForIn _ f [T_NormalWord _ w] _) = mapM_ checkF w
where
checkF (T_DollarExpansion id [T_Pipeline _ r])
| all isLineBased r =
info id 2013 "To read lines rather than words, pipe/redirect to a 'while read' loop."
checkF (T_Backticked id cmds) = checkF (T_DollarExpansion id cmds)
checkF _ = return ()
isLineBased cmd = any (cmd `isCommand`)
["grep", "fgrep", "egrep", "sed", "cat", "awk", "cut", "sort"]
checkForInCat _ = return ()
prop_checkForInLs = verify checkForInLs "for f in $(ls *.mp3); do mplayer \"$f\"; done"
prop_checkForInLs2 = verify checkForInLs "for f in `ls *.mp3`; do mplayer \"$f\"; done"
prop_checkForInLs3 = verify checkForInLs "for f in `find / -name '*.mp3'`; do mplayer \"$f\"; done"
checkForInLs t = try t
where
try (T_ForIn _ f [T_NormalWord _ [T_DollarExpansion id [x]]] _) =
check id f x
try (T_ForIn _ f [T_NormalWord _ [T_Backticked id [x]]] _) =
check id f x
try _ = return ()
check id f x =
case deadSimple x of
("ls":n) ->
let warntype = if any ("-" `isPrefixOf`) n then warn else err in
warntype id 2045 $ "Iterate over globs whenever possible (e.g. 'for f in */*.wav'), as for loops over ls will fail for filenames like 'my file*.txt'."
("find":_) -> warn id 2044 $ "Use find -exec or a while read loop instead, as for loops over find will fail for filenames like 'my file*.txt'."
_ -> return ()
prop_checkFindExec1 = verify checkFindExec "find / -name '*.php' -exec rm {};"
prop_checkFindExec2 = verify checkFindExec "find / -exec touch {} && ls {} \\;"
prop_checkFindExec3 = verify checkFindExec "find / -execdir cat {} | grep lol +"
prop_checkFindExec4 = verifyNot checkFindExec "find / -name '*.php' -exec foo {} +"
prop_checkFindExec5 = verifyNot checkFindExec "find / -execdir bash -c 'a && b' \\;"
prop_checkFindExec6 = verify checkFindExec "find / -type d -execdir rm *.jpg \\;"
checkFindExec cmd@(T_SimpleCommand _ _ t@(h:r)) | cmd `isCommand` "find" = do
c <- broken r False
when c $ do
let wordId = getId $ last t in
err wordId 2067 "Missing ';' or + terminating -exec. You can't use |/||/&&, and ';' has to be a separate, quoted argument."
where
broken [] v = return v
broken (w:r) v = do
when v $ (mapM_ warnFor $ fromWord w)
case getLiteralString w of
Just "-exec" -> broken r True
Just "-execdir" -> broken r True
Just "+" -> broken r False
Just ";" -> broken r False
_ -> broken r v
shouldWarn x =
case x of
T_DollarExpansion _ _ -> True
T_Backticked _ _ -> True
T_Glob _ _ -> True
T_Extglob _ _ _ -> True
_ -> False
warnFor x =
if shouldWarn x
then info (getId x) 2014 "This will expand once before find runs, not per file found."
else return ()
fromWord (T_NormalWord _ l) = l
fromWord _ = []
checkFindExec _ = return ()
prop_checkUnquotedExpansions1 = verifyTree checkUnquotedExpansions "rm $(ls)"
prop_checkUnquotedExpansions1a= verifyTree checkUnquotedExpansions "rm `ls`"
prop_checkUnquotedExpansions2 = verifyTree checkUnquotedExpansions "rm foo$(date)"
prop_checkUnquotedExpansions3 = verifyTree checkUnquotedExpansions "[ $(foo) == cow ]"
prop_checkUnquotedExpansions3a= verifyTree checkUnquotedExpansions "[ ! $(foo) ]"
prop_checkUnquotedExpansions4 = verifyNotTree checkUnquotedExpansions "[[ $(foo) == cow ]]"
prop_checkUnquotedExpansions5 = verifyNotTree checkUnquotedExpansions "for f in $(cmd); do echo $f; done"
prop_checkUnquotedExpansions6 = verifyNotTree checkUnquotedExpansions "$(cmd)"
prop_checkUnquotedExpansions7 = verifyNotTree checkUnquotedExpansions "cat << foo\n$(ls)\nfoo"
checkUnquotedExpansions t tree =
check t
where
check t@(T_DollarExpansion _ _) = examine t
check t@(T_Backticked _ _) = examine t
check _ = return ()
examine t =
unless (inUnquotableContext tree t || usedAsCommandName tree t) $
warn (getId t) 2046 "Quote this to prevent word splitting."
prop_checkRedirectToSame = verifyTree checkRedirectToSame "cat foo > foo"
prop_checkRedirectToSame2 = verifyTree checkRedirectToSame "cat lol | sed -e 's/a/b/g' > lol"
prop_checkRedirectToSame3 = verifyNotTree checkRedirectToSame "cat lol | sed -e 's/a/b/g' > foo.bar && mv foo.bar lol"
prop_checkRedirectToSame4 = verifyNotTree checkRedirectToSame "foo /dev/null > /dev/null"
prop_checkRedirectToSame5 = verifyNotTree checkRedirectToSame "foo > bar 2> bar"
checkRedirectToSame s@(T_Pipeline _ list) parents =
mapM_ (\l -> (mapM_ (\x -> doAnalysis (checkOccurences x) l) (getAllRedirs list))) list
where checkOccurences t@(T_NormalWord exceptId x) u@(T_NormalWord newId y) =
when (exceptId /= newId
&& x == y
&& not (isOutput t && isOutput u)
&& not (special t)) $ do
let note = Note InfoC 2094 $ "Make sure not to read and write the same file in the same pipeline."
addNoteFor newId $ note
addNoteFor exceptId $ note
checkOccurences _ _ = return ()
getAllRedirs l = concatMap (\(T_Redirecting _ ls _) -> concatMap getRedirs ls) l
getRedirs (T_FdRedirect _ _ (T_IoFile _ op file)) =
case op of T_Greater _ -> [file]
T_Less _ -> [file]
T_DGREAT _ -> [file]
_ -> []
getRedirs _ = []
special x = "/dev/" `isPrefixOf` (concat $ deadSimple x)
isOutput t =
case drop 1 $ getPath parents t of
(T_IoFile _ op _):_ ->
case op of
T_Greater _ -> True
T_DGREAT _ -> True
_ -> False
_ -> False
checkRedirectToSame _ _ = return ()
prop_checkShorthandIf = verify checkShorthandIf "[[ ! -z file ]] && scp file host || rm file"
prop_checkShorthandIf2 = verifyNot checkShorthandIf "[[ ! -z file ]] && { scp file host || echo 'Eek'; }"
prop_checkShorthandIf3 = verifyNot checkShorthandIf "foo && bar || echo baz"
prop_checkShorthandIf4 = verifyNot checkShorthandIf "foo && a=b || a=c"
checkShorthandIf (T_AndIf id _ (T_OrIf _ _ (T_Pipeline _ t)))
| not $ isOk t =
info id 2015 "Note that A && B || C is not if-then-else. C may run when A is true."
where
isOk [t] = isAssignment t || (fromMaybe False $ do
name <- getCommandBasename t
return $ name `elem` ["echo", "exit"])
isOk _ = False
checkShorthandIf _ = return ()
prop_checkDollarStar = verify checkDollarStar "for f in $*; do ..; done"
checkDollarStar (T_NormalWord _ [(T_DollarBraced id l)]) | (bracedString l) == "*" =
warn id 2048 $ "Use \"$@\" (with quotes) to prevent whitespace problems."
checkDollarStar _ = return ()
prop_checkUnquotedDollarAt = verify checkUnquotedDollarAt "ls $@"
prop_checkUnquotedDollarAt1= verifyNot checkUnquotedDollarAt "ls ${#@}"
prop_checkUnquotedDollarAt2 = verify checkUnquotedDollarAt "ls ${foo[@]}"
prop_checkUnquotedDollarAt3 = verifyNot checkUnquotedDollarAt "ls ${#foo[@]}"
prop_checkUnquotedDollarAt4 = verifyNot checkUnquotedDollarAt "ls \"$@\""
prop_checkUnquotedDollarAt5 = verifyNot checkUnquotedDollarAt "ls ${foo/@/ at }"
checkUnquotedDollarAt (T_NormalWord _ [T_DollarBraced id l]) =
let string = bracedString l
failing = err id 2068 $ "Add double quotes around ${" ++ string ++ "}, otherwise it's just like $* and breaks on spaces."
in do
when ("@" `isPrefixOf` string) failing
when (not ("#" `isPrefixOf` string) && "[@]" `isInfixOf` string) failing
checkUnquotedDollarAt _ = return ()
prop_checkStderrRedirect = verify checkStderrRedirect "test 2>&1 > cow"
prop_checkStderrRedirect2 = verifyNot checkStderrRedirect "test > cow 2>&1"
checkStderrRedirect (T_Redirecting _ [
T_FdRedirect id "2" (T_IoFile _ (T_GREATAND _) (T_NormalWord _ [T_Literal _ "1"])),
T_FdRedirect _ _ (T_IoFile _ op _)
] _) = case op of
T_Greater _ -> error
T_DGREAT _ -> error
_ -> return ()
where error = err id 2069 $ "The order of the 2>&1 and the redirect matters. The 2>&1 has to be last."
checkStderrRedirect _ = return ()
lt x = trace ("FAILURE " ++ (show x)) x
ltt t x = trace ("FAILURE " ++ (show t)) x
prop_checkSingleQuotedVariables = verifyTree checkSingleQuotedVariables "echo '$foo'"
prop_checkSingleQuotedVariables2 = verifyTree checkSingleQuotedVariables "echo 'lol$1.jpg'"
prop_checkSingleQuotedVariables3 = verifyNotTree checkSingleQuotedVariables "sed 's/foo$/bar/'"
prop_checkSingleQuotedVariables3a= verifyTree checkSingleQuotedVariables "sed 's/${foo}/bar/'"
prop_checkSingleQuotedVariables3b= verifyTree checkSingleQuotedVariables "sed 's/$(echo cow)/bar/'"
prop_checkSingleQuotedVariables3c= verifyTree checkSingleQuotedVariables "sed 's/$((1+foo))/bar/'"
prop_checkSingleQuotedVariables4 = verifyNotTree checkSingleQuotedVariables "awk '{print $1}'"
prop_checkSingleQuotedVariables5 = verifyNotTree checkSingleQuotedVariables "trap 'echo $SECONDS' EXIT"
checkSingleQuotedVariables t@(T_SingleQuoted id s) parents =
case matchRegex re s of
Just [] -> unless (probablyOk t) $ info id 2016 $ "Expressions don't expand in single quotes, use double quotes for that."
_ -> return ()
where
probablyOk t = fromMaybe False $ do
cmd <- getClosestCommand parents t
name <- getCommandBasename cmd
return $ name `elem` [
"trap"
,"sh"
,"bash"
,"ksh"
,"zsh"
,"ssh"
]
|| "awk" `isSuffixOf` name
|| "perl" `isPrefixOf` name
re = mkRegex "\\$[{(0-9a-zA-Z_]"
checkSingleQuotedVariables _ _ = return ()
prop_checkUnquotedN = verify checkUnquotedN "if [ -n $foo ]; then echo cow; fi"
prop_checkUnquotedN2 = verify checkUnquotedN "[ -n $cow ]"
prop_checkUnquotedN3 = verifyNot checkUnquotedN "[[ -n $foo ]] && echo cow"
checkUnquotedN (T_Condition _ SingleBracket (TC_Unary _ SingleBracket "-n" (T_NormalWord id [t]))) | willSplit t =
err id 2070 "Always true because you failed to quote. Use [[ ]] instead."
checkUnquotedN _ = return ()
prop_checkNumberComparisons1 = verify checkNumberComparisons "[[ $foo < 3 ]]"
prop_checkNumberComparisons2 = verify checkNumberComparisons "[[ 0 >= $(cmd) ]]"
prop_checkNumberComparisons3 = verifyNot checkNumberComparisons "[[ $foo ]] > 3"
prop_checkNumberComparisons4 = verify checkNumberComparisons "[[ $foo > 2.72 ]]"
prop_checkNumberComparisons5 = verify checkNumberComparisons "[[ $foo -le 2.72 ]]"
prop_checkNumberComparisons6 = verify checkNumberComparisons "[[ 3.14 = $foo ]]"
checkNumberComparisons (TC_Binary id typ op lhs rhs) = do
when (op `elem` ["<", ">", "<=", ">=", "\\<", "\\>", "\\<=", "\\>="]) $ do
when (isNum lhs || isNum rhs) $ err id 2071 $ "\"" ++ op ++ "\" is for string comparisons. Use " ++ (eqv op) ++" ."
mapM_ checkDecimals [lhs, rhs]
when (op `elem` ["-lt", "-gt", "-le", "-ge", "-eq", "=", "=="]) $ do
mapM_ checkDecimals [lhs, rhs]
where
checkDecimals hs = when (isFraction hs) $ err (getId hs) 2072 $ decimalError
decimalError = "Decimals are not supported. Either use integers only, or use bc or awk to compare."
isNum t = case deadSimple t of [v] -> all isDigit v
_ -> False
isFraction t = case deadSimple t of [v] -> isJust $ matchRegex floatRegex v
_ -> False
eqv ('\\':s) = eqv s
eqv "<" = "-lt"
eqv ">" = "-gt"
eqv "<=" = "-le"
eqv ">=" = "-ge"
eqv _ = "the numerical equivalent"
floatRegex = mkRegex "^[0-9]+\\.[0-9]+$"
checkNumberComparisons _ = return ()
prop_checkSingleBracketOperators1 = verify checkSingleBracketOperators "[ test =~ foo ]"
prop_checkSingleBracketOperators2 = verify checkSingleBracketOperators "[ $foo > $bar ]"
prop_checkSingleBracketOperators3 = verifyNot checkSingleBracketOperators "[[ foo < bar ]]"
prop_checkSingleBracketOperators5 = verify checkSingleBracketOperators "until [ $n <= $z ]; do echo foo; done"
checkSingleBracketOperators (TC_Binary id typ op lhs rhs)
| typ == SingleBracket && op `elem` ["<", ">", "<=", ">="] =
err id 2073 $ "Can't use " ++ op ++" in [ ]. Escape it or use [[..]]."
checkSingleBracketOperators (TC_Binary id typ op lhs rhs)
| typ == SingleBracket && op == "=~" =
err id 2074 $ "Can't use " ++ op ++" in [ ]. Use [[..]] instead."
checkSingleBracketOperators _ = return ()
prop_checkDoubleBracketOperators1 = verify checkDoubleBracketOperators "[[ 3 \\< 4 ]]"
prop_checkDoubleBracketOperators3 = verifyNot checkDoubleBracketOperators "[[ foo < bar ]]"
checkDoubleBracketOperators x@(TC_Binary id typ op lhs rhs)
| typ == DoubleBracket && op `elem` ["\\<", "\\>", "\\<=", "\\>="] =
err id 2075 $ "Escaping " ++ op ++" is required in [..], but invalid in [[..]]"
checkDoubleBracketOperators _ = return ()
prop_checkQuotedCondRegex1 = verify checkQuotedCondRegex "[[ $foo =~ \"bar\" ]]"
prop_checkQuotedCondRegex2 = verify checkQuotedCondRegex "[[ $foo =~ 'cow' ]]"
prop_checkQuotedCondRegex3 = verifyNot checkQuotedCondRegex "[[ $foo =~ $foo ]]"
checkQuotedCondRegex (TC_Binary _ _ "=~" _ rhs) =
case rhs of
T_NormalWord id [T_DoubleQuoted _ _] -> error id
T_NormalWord id [T_SingleQuoted _ _] -> error id
_ -> return ()
where
error id = err id 2076 $ "Don't quote rhs of =~, it'll match literally rather than as a regex."
checkQuotedCondRegex _ = return ()
prop_checkGlobbedRegex1 = verify checkGlobbedRegex "[[ $foo =~ *foo* ]]"
prop_checkGlobbedRegex2 = verify checkGlobbedRegex "[[ $foo =~ f* ]]"
prop_checkGlobbedRegex2a = verify checkGlobbedRegex "[[ $foo =~ \\#* ]]"
prop_checkGlobbedRegex3 = verifyNot checkGlobbedRegex "[[ $foo =~ $foo ]]"
prop_checkGlobbedRegex4 = verifyNot checkGlobbedRegex "[[ $foo =~ ^c.* ]]"
checkGlobbedRegex (TC_Binary _ DoubleBracket "=~" _ rhs) =
let s = concat $ deadSimple rhs in
if isConfusedGlobRegex s
then warn (getId rhs) 2049 $ "=~ is for regex. Use == for globs."
else return ()
checkGlobbedRegex _ = return ()
prop_checkConstantIfs1 = verify checkConstantIfs "[[ foo != bar ]]"
prop_checkConstantIfs2 = verify checkConstantIfs "[[ n -le 4 ]]"
prop_checkConstantIfs3 = verify checkConstantIfs "[[ $n -le 4 && n -ge 2 ]]"
prop_checkConstantIfs4 = verifyNot checkConstantIfs "[[ $n -le 3 ]]"
prop_checkConstantIfs5 = verifyNot checkConstantIfs "[[ $n -le $n ]]"
checkConstantIfs (TC_Binary id typ op lhs rhs)
| op `elem` [ "==", "!=", "<=", ">=", "-eq", "-ne", "-lt", "-le", "-gt", "-ge", "=~", ">", "<", "="] = do
when (isJust lLit && isJust rLit) $ warn id 2050 $ "This expression is constant. Did you forget the $ on a variable?"
where
lLit = getLiteralString lhs
rLit = getLiteralString rhs
checkConstantIfs _ = return ()
prop_checkNoaryWasBinary = verify checkNoaryWasBinary "[[ a==$foo ]]"
prop_checkNoaryWasBinary2 = verify checkNoaryWasBinary "[ $foo=3 ]"
prop_checkNoaryWasBinary3 = verify checkNoaryWasBinary "[ $foo!=3 ]"
checkNoaryWasBinary (TC_Noary _ _ t@(T_NormalWord id l)) | not $ isConstant t = do
let str = concat $ deadSimple t
when ('=' `elem` str) $ err id 2077 $ "You need spaces around the comparison operator."
checkNoaryWasBinary _ = return ()
prop_checkConstantNoary = verify checkConstantNoary "[[ '$(foo)' ]]"
prop_checkConstantNoary2 = verify checkConstantNoary "[ \"-f lol\" ]"
prop_checkConstantNoary3 = verify checkConstantNoary "[[ cmd ]]"
prop_checkConstantNoary4 = verify checkConstantNoary "[[ ! cmd ]]"
checkConstantNoary (TC_Noary _ _ t@(T_NormalWord id _)) | isConstant t = do
err id 2078 $ "This expression is constant. Did you forget a $ somewhere?"
checkConstantNoary _ = return ()
prop_checkBraceExpansionVars = verify checkBraceExpansionVars "echo {1..$n}"
checkBraceExpansionVars (T_BraceExpansion id s) | '$' `elem` s =
warn id 2051 $ "Bash doesn't support variables in brace expansions."
checkBraceExpansionVars _ = return ()
prop_checkForDecimals = verify checkForDecimals "((3.14*c))"
checkForDecimals (TA_Literal id s) | any (== '.') s = do
err id 2079 $ "(( )) doesn't support decimals. Use bc or awk."
checkForDecimals _ = return ()
prop_checkDivBeforeMult = verify checkDivBeforeMult "echo $((c/n*100))"
prop_checkDivBeforeMult2 = verifyNot checkDivBeforeMult "echo $((c*100/n))"
checkDivBeforeMult (TA_Binary _ "*" (TA_Binary id "/" _ _) _) = do
info id 2017 $ "Increase precision by replacing a/b*c with a*c/b."
checkDivBeforeMult _ = return ()
prop_checkArithmeticDeref = verify checkArithmeticDeref "echo $((3+$foo))"
prop_checkArithmeticDeref2 = verify checkArithmeticDeref "cow=14; (( s+= $cow ))"
prop_checkArithmeticDeref3 = verifyNot checkArithmeticDeref "cow=1/40; (( s+= ${cow%%/*} ))"
prop_checkArithmeticDeref4 = verifyNot checkArithmeticDeref "(( ! $? ))"
prop_checkArithmeticDeref5 = verifyNot checkArithmeticDeref "(($1))"
prop_checkArithmeticDeref6 = verifyNot checkArithmeticDeref "(( ${a[$i]} ))"
checkArithmeticDeref (TA_Expansion _ (T_DollarBraced id l)) | not . excepting $ bracedString l =
style id 2004 $ "Don't use $ on variables in (( ))."
where
excepting [] = True
excepting s = (any (`elem` "/.:#%?*@[]") s) || (isDigit $ head s)
checkArithmeticDeref _ = return ()
prop_checkArithmeticBadOctal1 = verify checkArithmeticBadOctal "(( 0192 ))"
prop_checkArithmeticBadOctal2 = verifyNot checkArithmeticBadOctal "(( 0x192 ))"
prop_checkArithmeticBadOctal3 = verifyNot checkArithmeticBadOctal "(( 1 ^ 0777 ))"
checkArithmeticBadOctal (TA_Base id "0" (TA_Literal _ str)) | '9' `elem` str || '8' `elem` str =
err id 2080 $ "Numbers with leading 0 are considered octal."
checkArithmeticBadOctal _ = return ()
prop_checkComparisonAgainstGlob = verify checkComparisonAgainstGlob "[[ $cow == $bar ]]"
prop_checkComparisonAgainstGlob2 = verifyNot checkComparisonAgainstGlob "[[ $cow == \"$bar\" ]]"
prop_checkComparisonAgainstGlob3 = verify checkComparisonAgainstGlob "[ $cow = *foo* ]"
prop_checkComparisonAgainstGlob4 = verifyNot checkComparisonAgainstGlob "[ $cow = foo ]"
checkComparisonAgainstGlob (TC_Binary _ DoubleBracket op _ (T_NormalWord id [T_DollarBraced _ _])) | op == "=" || op == "==" =
warn id 2053 $ "Quote the rhs of = in [[ ]] to prevent glob interpretation."
checkComparisonAgainstGlob (TC_Binary _ SingleBracket op _ word)
| (op == "=" || op == "==") && isGlob word =
err (getId word) 2081 $ "[ .. ] can't match globs. Use [[ .. ]] or grep."
checkComparisonAgainstGlob _ = return ()
prop_checkCommarrays1 = verify checkCommarrays "a=(1, 2)"
prop_checkCommarrays2 = verify checkCommarrays "a+=(1,2,3)"
prop_checkCommarrays3 = verifyNot checkCommarrays "cow=(1 \"foo,bar\" 3)"
checkCommarrays (T_Array id l) =
if any ("," `isSuffixOf`) (concatMap deadSimple l) || (length $ filter (==',') (concat $ concatMap deadSimple l)) > 1
then warn id 2054 "Use spaces, not commas, to separate array elements."
else return ()
checkCommarrays _ = return ()
prop_checkOrNeq1 = verify checkOrNeq "if [[ $lol -ne cow || $lol -ne foo ]]; then echo foo; fi"
prop_checkOrNeq2 = verify checkOrNeq "(( a!=lol || a!=foo ))"
prop_checkOrNeq3 = verify checkOrNeq "[ \"$a\" != lol || \"$a\" != foo ]"
prop_checkOrNeq4 = verifyNot checkOrNeq "[ a != $cow || b != $foo ]"
checkOrNeq (TC_Or id typ op (TC_Binary _ _ op1 word1 _) (TC_Binary _ _ op2 word2 _))
| word1 == word2 && (op1 == op2 && (op1 == "-ne" || op1 == "!=")) =
warn id 2055 $ "You probably wanted " ++ (if typ == SingleBracket then "-a" else "&&") ++ " here."
checkOrNeq (TA_Binary id "||" (TA_Binary _ "!=" word1 _) (TA_Binary _ "!=" word2 _))
| word1 == word2 =
warn id 2056 "You probably wanted && here."
checkOrNeq _ = return ()
allModifiedVariables t = snd $ runState (doAnalysis (\x -> modify $ (++) (getModifiedVariables x)) t) []
prop_checkValidCondOps1 = verify checkValidCondOps "[[ a -xz b ]]"
prop_checkValidCondOps2 = verify checkValidCondOps "[ -M a ]"
prop_checkValidCondOps2a= verifyNot checkValidCondOps "[ 3 \\> 2 ]"
prop_checkValidCondOps3 = verifyNot checkValidCondOps "[ 1 = 2 -a 3 -ge 4 ]"
prop_checkValidCondOps4 = verifyNot checkValidCondOps "[[ ! -v foo ]]"
checkValidCondOps (TC_Binary id _ s _ _)
| not (s `elem` ["-nt", "-ot", "-ef", "==", "!=", "<=", ">=", "-eq", "-ne", "-lt", "-le", "-gt", "-ge", "=~", ">", "<", "=", "\\<", "\\>", "\\<=", "\\>="]) =
warn id 2057 "Unknown binary operator."
checkValidCondOps (TC_Unary id _ s _)
| not (s `elem` [ "!", "-a", "-b", "-c", "-d", "-e", "-f", "-g", "-h", "-L", "-k", "-p", "-r", "-s", "-S", "-t", "-u", "-w", "-x", "-O", "-G", "-N", "-z", "-n", "-o", "-v", "-R"]) =
warn id 2058 "Unknown unary operator."
checkValidCondOps _ = return ()
getParentTree t =
snd . snd $ runState (doStackAnalysis pre post t) ([], Map.empty)
where
pre t = modify (\(l, m) -> (t:l, m))
post t = do
((_:rest), map) <- get
case rest of [] -> put (rest, map)
(x:_) -> put (rest, Map.insert (getId t) x map)
getTokenMap t =
snd $ runState (doAnalysis f t) (Map.empty)
where
f t = modify (Map.insert (getId t) t)
inUnquotableContext tree t =
case t of
TC_Noary _ DoubleBracket _ -> True
TC_Unary _ DoubleBracket _ _ -> True
TC_Binary _ DoubleBracket _ _ _ -> True
TA_Unary _ _ _ -> True
TA_Binary _ _ _ _ -> True
TA_Trinary _ _ _ _ -> True
TA_Expansion _ _ -> True
T_Assignment _ _ _ _ _ -> True
T_Redirecting _ _ _ ->
any (isCommand t) ["local", "declare", "typeset", "export"]
T_DoubleQuoted _ _ -> True
T_CaseExpression _ _ _ -> True
T_HereDoc _ _ _ _ _ -> True
T_ForIn _ _ _ _ -> True
x -> case Map.lookup (getId x) tree of
Nothing -> False
Just parent -> inUnquotableContext tree parent
isParamTo tree cmd t =
go t
where
go x = case Map.lookup (getId x) tree of
Nothing -> False
Just parent -> check parent
check t =
case t of
T_SingleQuoted _ _ -> go t
T_DoubleQuoted _ _ -> go t
T_NormalWord _ _ -> go t
T_SimpleCommand _ _ _ -> isCommand t cmd
T_Redirecting _ _ _ -> isCommand t cmd
_ -> False
getClosestCommand tree t =
msum . map getCommand $ getPath tree t
where
getCommand t@(T_Redirecting _ _ _) = return t
getCommand _ = Nothing
usedAsCommandName tree token = go (getId token) (tail $ getPath tree token)
where
go currentId ((T_NormalWord id [word]):rest)
| currentId == (getId word) = go id rest
go currentId ((T_DoubleQuoted id [word]):rest)
| currentId == (getId word) = go id rest
go currentId ((T_SimpleCommand _ _ (word:_)):_)
| currentId == (getId word) = True
go _ _ = False
getPath tree t = t :
case Map.lookup (getId t) tree of
Nothing -> []
Just parent -> getPath tree parent
checkCommand str f t@(T_SimpleCommand id _ (cmd:rest)) =
if t `isCommand` str then f rest else return ()
checkCommand _ _ _ = return ()
checkUnqualifiedCommand str f t@(T_SimpleCommand id _ (cmd:rest)) =
if t `isUnqualifiedCommand` str then f rest else return ()
checkUnqualifiedCommand _ _ _ = return ()
getLiteralString = getLiteralStringExt (const Nothing)
getGlobOrLiteralString = getLiteralStringExt f
where
f (T_Glob _ str) = return str
f _ = Nothing
getLiteralStringExt more t = g t
where
allInList l = let foo = map g l in if all isJust foo then return $ concat (catMaybes foo) else Nothing
g s@(T_DoubleQuoted _ l) = allInList l
g s@(T_DollarDoubleQuoted _ l) = allInList l
g s@(T_NormalWord _ l) = allInList l
g (T_SingleQuoted _ s) = return s
g (T_Literal _ s) = return s
g x = more x
isLiteral t = isJust $ getLiteralString t
isCommand token str = isCommandMatch token (\cmd -> cmd == str || ("/" ++ str) `isSuffixOf` cmd)
isUnqualifiedCommand token str = isCommandMatch token (\cmd -> cmd == str)
isCommandMatch token matcher = fromMaybe False $ do
cmd <- getCommandName token
return $ matcher cmd
getCommandName (T_Redirecting _ _ w) =
getCommandName w
getCommandName (T_SimpleCommand _ _ (w:_)) =
getLiteralString w
getCommandName (T_Annotation _ _ t) = getCommandName t
getCommandName _ = Nothing
getCommandBasename = liftM basename . getCommandName
basename = reverse . (takeWhile (/= '/')) . reverse
isAssignment (T_Annotation _ _ w) = isAssignment w
isAssignment (T_Redirecting _ _ w) = isAssignment w
isAssignment (T_SimpleCommand _ (w:_) []) = True
isAssignment _ = False
prop_checkPrintfVar1 = verify checkPrintfVar "printf \"Lol: $s\""
prop_checkPrintfVar2 = verifyNot checkPrintfVar "printf 'Lol: $s'"
prop_checkPrintfVar3 = verify checkPrintfVar "printf -v cow $(cmd)"
prop_checkPrintfVar4 = verifyNot checkPrintfVar "printf \"%${count}s\" var"
checkPrintfVar = checkUnqualifiedCommand "printf" f where
f (dashv:var:rest) | getLiteralString dashv == (Just "-v") = f rest
f (format:params) = check format
f _ = return ()
check format =
if '%' `elem` (concat $ deadSimple format) || isLiteral format
then return ()
else warn (getId format) 2059 $
"Don't use variables in the printf format string. Use printf \"..%s..\" \"$foo\"."
prop_checkUuoe1 = verify checkUuoe "echo $(date)"
prop_checkUuoe1a= verify checkUuoe "echo `date`"
prop_checkUuoe2 = verify checkUuoe "echo \"$(date)\""
prop_checkUuoe2a= verify checkUuoe "echo \"`date`\""
prop_checkUuoe3 = verifyNot checkUuoe "echo \"The time is $(date)\""
checkUuoe = checkUnqualifiedCommand "echo" f where
msg id = style id 2005 "Useless echo? Instead of 'echo $(cmd)', just use 'cmd'."
f [T_NormalWord id [(T_DollarExpansion _ _)]] = msg id
f [T_NormalWord id [T_DoubleQuoted _ [(T_DollarExpansion _ _)]]] = msg id
f [T_NormalWord id [(T_Backticked _ _)]] = msg id
f [T_NormalWord id [T_DoubleQuoted _ [(T_Backticked _ _)]]] = msg id
f _ = return ()
prop_checkTr1 = verify checkTr "tr [a-f] [A-F]"
prop_checkTr2 = verify checkTr "tr 'a-z' 'A-Z'"
prop_checkTr2a= verify checkTr "tr '[a-z]' '[A-Z]'"
prop_checkTr3 = verifyNot checkTr "tr -d '[:lower:]'"
prop_checkTr3a= verifyNot checkTr "tr -d '[:upper:]'"
prop_checkTr3b= verifyNot checkTr "tr -d '|/_[:upper:]'"
prop_checkTr4 = verifyNot checkTr "ls [a-z]"
prop_checkTr5 = verify checkTr "tr foo bar"
prop_checkTr6 = verify checkTr "tr 'hello' 'world'"
prop_checkTr8 = verifyNot checkTr "tr aeiou _____"
prop_checkTr9 = verifyNot checkTr "a-z n-za-m"
prop_checkTr10= verifyNot checkTr "tr --squeeze-repeats rl lr"
prop_checkTr11= verifyNot checkTr "tr abc '[d*]'"
checkTr = checkCommand "tr" (mapM_ f)
where
f w | isGlob w = do
warn (getId w) 2060 $ "Quote parameters to tr to prevent glob expansion."
f word = case getLiteralString word of
Just "a-z" -> info (getId word) 2018 "Use '[:lower:]' to support accents and foreign alphabets."
Just "A-Z" -> info (getId word) 2019 "Use '[:upper:]' to support accents and foreign alphabets."
Just s -> do
when ((not $ "-" `isPrefixOf` s || "[:" `isInfixOf` s) && duplicated s) $
info (getId word) 2020 "tr replaces sets of chars, not words (mentioned due to duplicates)."
unless ("[:" `isPrefixOf` s) $
when ("[" `isPrefixOf` s && "]" `isSuffixOf` s && (length s > 2) && (not $ '*' `elem` s)) $
info (getId word) 2021 "Don't use [] around ranges in tr, it replaces literal square brackets."
Nothing -> return ()
duplicated s =
let relevant = filter isAlpha s
in not $ relevant == nub relevant
prop_checkFindNameGlob1 = verify checkFindNameGlob "find / -name *.php"
prop_checkFindNameGlob2 = verify checkFindNameGlob "find / -type f -ipath *(foo)"
prop_checkFindNameGlob3 = verifyNot checkFindNameGlob "find * -name '*.php'"
checkFindNameGlob = checkCommand "find" f where
acceptsGlob (Just s) = s `elem` [ "-ilname", "-iname", "-ipath", "-iregex", "-iwholename", "-lname", "-name", "-path", "-regex", "-wholename" ]
acceptsGlob _ = False
f [] = return ()
f [x] = return ()
f (a:b:r) = do
when (acceptsGlob (getLiteralString a) && isGlob b) $ do
let (Just s) = getLiteralString a
warn (getId b) 2061 $ "Quote the parameter to " ++ s ++ " so the shell won't interpret it."
f (b:r)
prop_checkGrepRe1 = verify checkGrepRe "cat foo | grep *.mp3"
prop_checkGrepRe2 = verify checkGrepRe "grep -Ev cow*test *.mp3"
prop_checkGrepRe3 = verify checkGrepRe "grep --regex=*.mp3 file"
prop_checkGrepRe4 = verifyNot checkGrepRe "grep foo *.mp3"
prop_checkGrepRe5 = verifyNot checkGrepRe "grep-v --regex=moo *"
prop_checkGrepRe6 = verifyNot checkGrepRe "grep foo \\*.mp3"
prop_checkGrepRe7 = verify checkGrepRe "grep *foo* file"
prop_checkGrepRe8 = verify checkGrepRe "ls | grep foo*.jpg"
prop_checkGrepRe9 = verifyNot checkGrepRe "grep '[0-9]*' file"
checkGrepRe = checkCommand "grep" f where
skippable (Just s) = not ("--regex=" `isPrefixOf` s) && "-" `isPrefixOf` s
skippable _ = False
f [] = return ()
f (x:r) | skippable (getLiteralString x) = f r
f (re:_) = do
when (isGlob re) $ do
warn (getId re) 2062 $ "Quote the grep pattern so the shell won't interpret it."
let string = concat $ deadSimple re
if isConfusedGlobRegex string then
warn (getId re) 2063 $ "Grep uses regex, but this looks like a glob."
else
if (isPotentiallyConfusedGlobRegex string)
then info (getId re) 2022 "Note that c* does not mean \"c followed by anything\" in regex."
else return ()
prop_checkTrapQuotes1 = verify checkTrapQuotes "trap \"echo $num\" INT"
prop_checkTrapQuotes1a= verify checkTrapQuotes "trap \"echo `ls`\" INT"
prop_checkTrapQuotes2 = verifyNot checkTrapQuotes "trap 'echo $num' INT"
prop_checkTrapQuotes3 = verify checkTrapQuotes "trap \"echo $((1+num))\" EXIT DEBUG"
checkTrapQuotes = checkCommand "trap" f where
f (x:_) = checkTrap x
f _ = return ()
checkTrap (T_NormalWord _ [T_DoubleQuoted _ rs]) = mapM_ checkExpansions rs
checkTrap _ = return ()
warning id = warn id 2064 $ "Use single quotes, otherwise this expands now rather than when signalled."
checkExpansions (T_DollarExpansion id _) = warning id
checkExpansions (T_Backticked id _) = warning id
checkExpansions (T_DollarBraced id _) = warning id
checkExpansions (T_DollarArithmetic id _) = warning id
checkExpansions _ = return ()
prop_checkTimeParameters1 = verify checkTimeParameters "time -f lol sleep 10"
prop_checkTimeParameters2 = verifyNot checkTimeParameters "time sleep 10"
prop_checkTimeParameters3 = verifyNot checkTimeParameters "time -p foo"
checkTimeParameters = checkUnqualifiedCommand "time" f where
f (x:_) = let s = concat $ deadSimple x in
if "-" `isPrefixOf` s && s /= "-p" then
info (getId x) 2023 "The shell may override 'time' as seen in man time(1). Use 'command time ..' for that one."
else return ()
f _ = return ()
prop_checkTestRedirects1 = verify checkTestRedirects "test 3 > 1"
prop_checkTestRedirects2 = verifyNot checkTestRedirects "test 3 \\> 1"
prop_checkTestRedirects3 = verify checkTestRedirects "/usr/bin/test $var > $foo"
checkTestRedirects (T_Redirecting id redirs@(redir:_) cmd) | cmd `isCommand` "test" =
warn (getId redir) 2065 $ "This is interpretted as a shell file redirection, not a comparison."
checkTestRedirects _ = return ()
prop_checkSudoRedirect1 = verify checkSudoRedirect "sudo echo 3 > /proc/file"
prop_checkSudoRedirect2 = verify checkSudoRedirect "sudo cmd < input"
prop_checkSudoRedirect3 = verify checkSudoRedirect "sudo cmd >> file"
prop_checkSudoRedirect4 = verify checkSudoRedirect "sudo cmd &> file"
prop_checkSudoRedirect5 = verifyNot checkSudoRedirect "sudo cmd 2>&1"
prop_checkSudoRedirect6 = verifyNot checkSudoRedirect "sudo cmd 2> log"
prop_checkSudoRedirect7 = verifyNot checkSudoRedirect "sudo cmd > /dev/null 2>&1"
checkSudoRedirect (T_Redirecting _ redirs cmd) | cmd `isCommand` "sudo" =
mapM_ warnAbout redirs
where
warnAbout (T_FdRedirect _ s (T_IoFile id op file))
| (s == "" || s == "&") && (not $ special file) =
case op of
T_Less _ ->
info (getId op) 2024 $
"sudo doesn't affect redirects. Use sudo cat file | .."
T_Greater _ ->
warn (getId op) 2024 $
"sudo doesn't affect redirects. Use ..| sudo tee file"
T_DGREAT _ ->
warn (getId op) 2024 $
"sudo doesn't affect redirects. Use .. | sudo tee -a file"
_ -> return ()
warnAbout _ = return ()
special file = (concat $ deadSimple file) == "/dev/null"
checkSudoRedirect _ = return ()
prop_checkPS11 = verify checkPS1Assignments "PS1='\\033[1;35m\\$ '"
prop_checkPS11a= verify checkPS1Assignments "export PS1='\\033[1;35m\\$ '"
prop_checkPSf2 = verify checkPS1Assignments "PS1='\\h \\e[0m\\$ '"
prop_checkPS13 = verify checkPS1Assignments "PS1=$'\\x1b[c '"
prop_checkPS14 = verify checkPS1Assignments "PS1=$'\\e[3m; '"
prop_checkPS14a= verify checkPS1Assignments "export PS1=$'\\e[3m; '"
prop_checkPS15 = verifyNot checkPS1Assignments "PS1='\\[\\033[1;35m\\]\\$ '"
prop_checkPS16 = verifyNot checkPS1Assignments "PS1='\\[\\e1m\\e[1m\\]\\$ '"
prop_checkPS17 = verifyNot checkPS1Assignments "PS1='e033x1B'"
prop_checkPS18 = verifyNot checkPS1Assignments "PS1='\\[\\e\\]'"
checkPS1Assignments (T_Assignment _ _ "PS1" _ word) = warnFor word
where
warnFor word =
let contents = concat $ deadSimple word in
when (containsUnescaped contents) $
info (getId word) 2025 "Make sure all escape sequences are enclosed in \\[..\\] to prevent line wrapping issues"
containsUnescaped s =
let unenclosed = subRegex enclosedRegex s "" in
isJust $ matchRegex escapeRegex unenclosed
enclosedRegex = mkRegex "\\\\\\[.*\\\\\\]"
escapeRegex = mkRegex "\\\\x1[Bb]|\\\\e|\x1B|\\\\033"
checkPS1Assignments _ = return ()
prop_checkBackticks1 = verify checkBackticks "echo `foo`"
prop_checkBackticks2 = verifyNot checkBackticks "echo $(foo)"
checkBackticks (T_Backticked id _) =
style id 2006 "Use $(..) instead of deprecated `..`"
checkBackticks _ = return ()
prop_checkIndirectExpansion1 = verify checkIndirectExpansion "${foo$n}"
prop_checkIndirectExpansion2 = verifyNot checkIndirectExpansion "${foo//$n/lol}"
prop_checkIndirectExpansion3 = verify checkIndirectExpansion "${$#}"
prop_checkIndirectExpansion4 = verify checkIndirectExpansion "${var${n}_$((i%2))}"
prop_checkIndirectExpansion5 = verifyNot checkIndirectExpansion "${bar}"
checkIndirectExpansion (T_DollarBraced i (T_NormalWord _ contents)) =
when (isIndirection contents) $
err i 2082 "To expand via indirection, use name=\"foo$n\"; echo \"${!name}\"."
where
isIndirection vars =
let list = catMaybes (map isIndirectionPart vars) in
not (null list) && all id list
isIndirectionPart t =
case t of T_DollarExpansion _ _ -> Just True
T_Backticked _ _ -> Just True
T_DollarBraced _ _ -> Just True
T_DollarArithmetic _ _ -> Just True
T_Literal _ s -> if all isVariableChar s
then Nothing
else Just False
_ -> Just False
checkIndirectExpansion _ = return ()
prop_checkInexplicablyUnquoted1 = verify checkInexplicablyUnquoted "echo 'var='value';'"
prop_checkInexplicablyUnquoted2 = verifyNot checkInexplicablyUnquoted "'foo'*"
prop_checkInexplicablyUnquoted3 = verifyNot checkInexplicablyUnquoted "wget --user-agent='something'"
checkInexplicablyUnquoted (T_NormalWord id tokens) = mapM_ check (tails tokens)
where
check ((T_SingleQuoted _ _):(T_Literal id str):_)
| all isAlphaNum str =
info id 2026 $ "This word is outside of quotes. Did you intend to 'nest '\"'single quotes'\"' instead'? "
check ((T_DoubleQuoted _ _):trapped:(T_DoubleQuoted _ _):_) =
case trapped of
T_DollarExpansion id _ -> warnAbout id
T_DollarBraced id _ -> warnAbout id
_ -> return ()
check _ = return ()
warnAbout id =
info id 2027 $ "Surrounding quotes actually unquotes this (\"inside\"$outside\"inside\"). Did you forget your quote level?"
checkInexplicablyUnquoted _ = return ()
prop_checkTildeInQuotes1 = verify checkTildeInQuotes "var=\"~/out.txt\""
prop_checkTildeInQuotes2 = verify checkTildeInQuotes "foo > '~/dir'"
prop_checkTildeInQuotes4 = verifyNot checkTildeInQuotes "~/file"
prop_checkTildeInQuotes5 = verifyNot checkTildeInQuotes "echo '/~foo/cow'"
prop_checkTildeInQuotes6 = verifyNot checkTildeInQuotes "awk '$0 ~ /foo/'"
checkTildeInQuotes = check
where
verify id ('~':_) = warn id 2088 "Note that ~ does not expand in quotes."
verify _ _ = return ()
check (T_NormalWord _ ((T_SingleQuoted id str):_)) =
verify id str
check (T_NormalWord _ ((T_DoubleQuoted _ ((T_Literal id str):_)):_)) =
verify id str
check _ = return ()
prop_checkLonelyDotDash1 = verify checkLonelyDotDash "./ file"
prop_checkLonelyDotDash2 = verifyNot checkLonelyDotDash "./file"
checkLonelyDotDash t@(T_Redirecting id _ _)
| isUnqualifiedCommand t "./" =
err id 2083 "Don't add spaces after the slash in './file'."
checkLonelyDotDash _ = return ()
prop_checkSpuriousExec1 = verify checkSpuriousExec "exec foo; true"
prop_checkSpuriousExec2 = verify checkSpuriousExec "if a; then exec b; exec c; fi"
prop_checkSpuriousExec3 = verifyNot checkSpuriousExec "echo cow; exec foo"
prop_checkSpuriousExec4 = verifyNot checkSpuriousExec "if a; then exec b; fi"
prop_checkSpuriousExec5 = verifyNot checkSpuriousExec "exec > file; cmd"
prop_checkSpuriousExec6 = verify checkSpuriousExec "exec foo > file; cmd"
prop_checkSpuriousExec7 = verifyNot checkSpuriousExec "exec file; echo failed; exit 3"
checkSpuriousExec = doLists
where
doLists (T_Script _ _ cmds) = doList cmds
doLists (T_BraceGroup _ cmds) = doList cmds
doLists (T_WhileExpression _ _ cmds) = doList cmds
doLists (T_UntilExpression _ _ cmds) = doList cmds
doLists (T_ForIn _ _ _ cmds) = doList cmds
doLists (T_IfExpression _ thens elses) = do
mapM_ (\(_, l) -> doList l) thens
doList elses
doLists _ = return ()
stripCleanup = reverse . dropWhile cleanup . reverse
cleanup (T_Pipeline _ [cmd]) =
isCommandMatch cmd (`elem` ["echo", "exit"])
cleanup _ = False
doList = doList' . stripCleanup
doList' t@(current:following:_) = do
commentIfExec current
doList (tail t)
doList' _ = return ()
commentIfExec (T_Pipeline id list) =
mapM_ commentIfExec $ take 1 list
commentIfExec (T_Redirecting _ _ f@(
T_SimpleCommand id _ (cmd:arg:_))) =
when (f `isUnqualifiedCommand` "exec") $
warn (id) 2093 $
"Remove \"exec \" if script should continue after this command."
commentIfExec _ = return ()
prop_checkSpuriousExpansion1 = verify checkSpuriousExpansion "if $(true); then true; fi"
prop_checkSpuriousExpansion2 = verify checkSpuriousExpansion "while \"$(cmd)\"; do :; done"
prop_checkSpuriousExpansion3 = verifyNot checkSpuriousExpansion "$(cmd) --flag1 --flag2"
prop_checkSpuriousExpansion4 = verify checkSpuriousExpansion "$((i++))"
checkSpuriousExpansion (T_SimpleCommand _ _ [T_NormalWord _ [word]]) = check word
where
check word = case word of
T_DollarExpansion id _ ->
warn id 2091 "Remove surrounding $() to avoid executing output."
T_Backticked id _ ->
warn id 2092 "Remove backticks to avoid executing output."
T_DollarArithmetic id _ ->
err id 2084 "Remove '$' or use '_=$((expr))' to avoid executing output."
T_DoubleQuoted id [subword] -> check subword
_ -> return ()
checkSpuriousExpansion _ = return ()
prop_checkUnusedEchoEscapes1 = verify checkUnusedEchoEscapes "echo 'foo\\nbar\\n'"
prop_checkUnusedEchoEscapes2 = verifyNot checkUnusedEchoEscapes "echo -e 'foi\\nbar'"
prop_checkUnusedEchoEscapes3 = verify checkUnusedEchoEscapes "echo \"n:\\t42\""
prop_checkUnusedEchoEscapes4 = verifyNot checkUnusedEchoEscapes "echo lol"
checkUnusedEchoEscapes = checkCommand "echo" f
where
isDashE = mkRegex "^-.*e"
hasEscapes = mkRegex "\\\\[rnt]"
f (arg:_) | (concat $ deadSimple arg) `matches` isDashE = return ()
f args = mapM_ checkEscapes args
checkEscapes (T_NormalWord _ args) =
mapM_ checkEscapes args
checkEscapes (T_DoubleQuoted id args) =
mapM_ checkEscapes args
checkEscapes (T_Literal id str) = examine id str
checkEscapes (T_SingleQuoted id str) = examine id str
checkEscapes _ = return ()
examine id str =
when (str `matches` hasEscapes) $
info id 2028 "echo won't expand escape sequences. Consider printf."
prop_checkDollarBrackets1 = verify checkDollarBrackets "echo $[1+2]"
prop_checkDollarBrackets2 = verifyNot checkDollarBrackets "echo $((1+2))"
checkDollarBrackets (T_DollarBracket id _) =
style id 2007 "Use $((..)) instead of deprecated $[..]"
checkDollarBrackets _ = return ()
prop_checkSshHereDoc1 = verify checkSshHereDoc "ssh host << foo\necho $PATH\nfoo"
prop_checkSshHereDoc2 = verifyNot checkSshHereDoc "ssh host << 'foo'\necho $PATH\nfoo"
checkSshHereDoc (T_Redirecting _ redirs cmd)
| cmd `isCommand` "ssh" =
mapM_ checkHereDoc redirs
where
hasVariables = mkRegex "[`$]"
checkHereDoc (T_FdRedirect _ _ (T_HereDoc id _ Unquoted token tokens))
| not (all isConstant tokens) =
warn id 2087 $ "Quote '" ++ token ++ "' to make here document expansions happen on the server side rather than on the client."
checkHereDoc _ = return ()
checkSshHereDoc _ = return ()
prop_checkSshCmdStr1 = verify checkSshCommandString "ssh host \"echo $PS1\""
prop_checkSshCmdStr2 = verifyNot checkSshCommandString "ssh host \"ls foo\""
prop_checkSshCmdStr3 = verifyNot checkSshCommandString "ssh \"$host\""
checkSshCommandString = checkCommand "ssh" f
where
nonOptions args =
filter (\x -> not $ "-" `isPrefixOf` (concat $ deadSimple x)) args
f args =
case nonOptions args of
(hostport:r@(_:_)) -> checkArg $ last r
_ -> return ()
checkArg (T_NormalWord _ [T_DoubleQuoted id parts]) =
case filter (not . isConstant) parts of
[] -> return ()
(x:_) -> info (getId x) 2029 $
"Note that, unescaped, this expands on the client side."
checkArg _ = return ()
prop_subshellAssignmentCheck = verifyFull subshellAssignmentCheck "cat foo | while read bar; do a=$bar; done; echo \"$a\""
prop_subshellAssignmentCheck2 = verifyNotFull subshellAssignmentCheck "while read bar; do a=$bar; done < file; echo \"$a\""
prop_subshellAssignmentCheck3 = verifyFull subshellAssignmentCheck "( A=foo; ); rm $A"
prop_subshellAssignmentCheck4 = verifyNotFull subshellAssignmentCheck "( A=foo; rm $A; )"
prop_subshellAssignmentCheck5 = verifyFull subshellAssignmentCheck "cat foo | while read cow; do true; done; echo $cow;"
prop_subshellAssignmentCheck6 = verifyFull subshellAssignmentCheck "( export lol=$(ls); ); echo $lol;"
prop_subshellAssignmentCheck6a= verifyFull subshellAssignmentCheck "( typeset -a lol=a; ); echo $lol;"
prop_subshellAssignmentCheck7 = verifyFull subshellAssignmentCheck "cmd | while read foo; do (( n++ )); done; echo \"$n lines\""
prop_subshellAssignmentCheck8 = verifyFull subshellAssignmentCheck "n=3 & echo $((n++))"
prop_subshellAssignmentCheck9 = verifyFull subshellAssignmentCheck "read n & n=foo$n"
prop_subshellAssignmentCheck10 = verifyFull subshellAssignmentCheck "(( n <<= 3 )) & (( n |= 4 )) &"
prop_subshellAssignmentCheck11 = verifyFull subshellAssignmentCheck "cat /etc/passwd | while read line; do let n=n+1; done\necho $n"
prop_subshellAssignmentCheck12 = verifyFull subshellAssignmentCheck "cat /etc/passwd | while read line; do let ++n; done\necho $n"
subshellAssignmentCheck t =
let flow = getVariableFlow t
check = findSubshelled flow [("oops",[])] Map.empty
in snd $ runState check []
data Scope = SubshellScope String | NoneScope deriving (Show, Eq)
data StackData =
StackScope Scope
| StackScopeEnd
| Assignment (Token, Token, String, DataSource)
| Reference (Token, Token, String)
deriving (Show, Eq)
data DataSource = DataFrom [Token] | DataExternal
deriving (Show, Eq)
data VariableState = Dead Token String | Alive deriving (Show, Eq)
leadType t =
case t of
T_DollarExpansion _ _ -> SubshellScope "$(..) expansion"
T_Backticked _ _ -> SubshellScope "`..` expansion"
T_Backgrounded _ _ -> SubshellScope "backgrounding &"
T_Subshell _ _ -> SubshellScope "(..) group"
T_Pipeline _ (_:_:[]) -> SubshellScope "pipeline"
_ -> NoneScope
getModifiedVariables t =
case t of
T_SimpleCommand _ vars [] ->
concatMap (\x -> case x of
T_Assignment id _ name _ w ->
[(x, x, name, DataFrom [w])]
_ -> []
) vars
c@(T_SimpleCommand _ _ _) ->
getModifiedVariableCommand c
TA_Unary _ "++|" (TA_Variable id name) -> [(t, t, name, DataFrom [t])]
TA_Unary _ "|++" (TA_Variable id name) -> [(t, t, name, DataFrom [t])]
TA_Binary _ op (TA_Variable id name) rhs ->
if any (==op) ["=", "*=", "/=", "%=", "+=", "-=", "<<=", ">>=", "&=", "^=", "|="]
then [(t, t, name, DataFrom [rhs])]
else []
T_ForIn id str words _ -> [(t, t, str, DataFrom words)]
T_SelectIn id str words _ -> [(t, t, str, DataFrom words)]
_ -> []
getReferencedVariableCommand base@(T_SimpleCommand _ _ ((T_NormalWord _ ((T_Literal _ x):_)):rest)) =
case x of
"export" -> concatMap getReference rest
_ -> []
where
getReference t@(T_Assignment _ _ name _ value) = [(t, t, name)]
getReference t@(T_NormalWord _ [T_Literal _ name]) | not ("-" `isPrefixOf` name) = [(t, t, name)]
getReference _ = []
getReferencedVariableCommand _ = []
getModifiedVariableCommand base@(T_SimpleCommand _ _ ((T_NormalWord _ ((T_Literal _ x):_)):rest)) =
filter (\(_,_,s,_) -> not ("-" `isPrefixOf` s)) $
case x of
"read" -> concatMap getLiteral rest
"let" -> concatMap letParamToLiteral rest
"export" -> concatMap getModifierParam rest
"declare" -> concatMap getModifierParam rest
"typeset" -> concatMap getModifierParam rest
"local" -> concatMap getModifierParam rest
_ -> []
where
stripEquals s = let rest = dropWhile (/= '=') s in
if rest == "" then "" else tail rest
stripEqualsFrom (T_NormalWord id1 ((T_Literal id2 s):rs)) =
(T_NormalWord id1 ((T_Literal id2 (stripEquals s)):rs))
stripEqualsFrom (T_NormalWord id1 [T_DoubleQuoted id2 [T_Literal id3 s]]) =
(T_NormalWord id1 [T_DoubleQuoted id2 [T_Literal id3 (stripEquals s)]])
stripEqualsFrom t = t
getLiteral t@(T_NormalWord _ [T_Literal _ s]) =
[(base, t, s, DataExternal)]
getLiteral t@(T_NormalWord _ [T_SingleQuoted _ s]) =
[(base, t, s, DataExternal)]
getLiteral t@(T_NormalWord _ [T_DoubleQuoted _ [T_Literal id s]]) =
[(base, t, s, DataExternal)]
getLiteral x = []
getModifierParam t@(T_Assignment _ _ name _ value) =
[(base, t, name, DataFrom [value])]
getModifierParam _ = []
letParamToLiteral token =
if var == ""
then []
else [(base, token, var, DataFrom [stripEqualsFrom token])]
where var = takeWhile (isVariableChar) $ dropWhile (\x -> x `elem` "+-") $ concat $ deadSimple token
getModifiedVariableCommand _ = []
getBracedReference s = takeWhile (\x -> not $ x `elem` ":[#%/^,") $ dropWhile (`elem` "#!") s
getReferencedVariables t =
case t of
T_DollarBraced id l -> map (\x -> (t, t, x)) $ [getBracedReference $ bracedString l]
TA_Variable id str -> [(t, t, str)]
T_Assignment id Append str _ _ -> [(t, t, str)]
x -> getReferencedVariableCommand x
getVariableFlow t =
let (_, stack) = runState (doStackAnalysis startScope endScope t) []
in reverse stack
where
startScope t =
let scopeType = leadType t
in do
when (scopeType /= NoneScope) $ modify ((StackScope scopeType):)
if assignFirst t then setWritten t else return ()
endScope t =
let scopeType = leadType t
in do
setRead t
if assignFirst t then return () else setWritten t
when (scopeType /= NoneScope) $ modify ((StackScopeEnd):)
assignFirst (T_ForIn _ _ _ _) = True
assignFirst (T_SelectIn _ _ _ _) = True
assignFirst _ = False
setRead t =
let read = getReferencedVariables t
in mapM_ (\v -> modify ((Reference v):)) read
setWritten t =
let written = getModifiedVariables t
in mapM_ (\v -> modify ((Assignment v):)) written
findSubshelled [] _ _ = return ()
findSubshelled ((Assignment x@(_, _, str, _)):rest) ((reason,scope):lol) deadVars =
findSubshelled rest ((reason, x:scope):lol) $ Map.insert str Alive deadVars
findSubshelled ((Reference (_, readToken, str)):rest) scopes deadVars = do
case Map.findWithDefault Alive str deadVars of
Alive -> return ()
Dead writeToken reason -> do
info (getId writeToken) 2030 $ "Modification of " ++ str ++ " is local (to subshell caused by "++ reason ++")."
info (getId readToken) 2031 $ str ++ " was modified in a subshell. That change might be lost."
findSubshelled rest scopes deadVars
findSubshelled ((StackScope (SubshellScope reason)):rest) scopes deadVars =
findSubshelled rest ((reason,[]):scopes) deadVars
findSubshelled ((StackScopeEnd):rest) ((reason, scope):oldScopes) deadVars =
findSubshelled rest oldScopes $
foldl (\m (_, token, var, _) ->
Map.insert var (Dead token reason) m) deadVars scope
doVariableFlowAnalysis readFunc writeFunc empty t = fst $ runState (
foldM (\list x -> do { l <- doFlow x; return $ l ++ list; }) [] flow
) empty
where
flow = getVariableFlow t
doFlow (Reference (base, token, name)) =
readFunc base token name
doFlow (Assignment (base, token, name, values)) =
writeFunc base token name values
doFlow _ = return []
prop_checkSpacefulness0 = verifyFull checkSpacefulness "for f in *.mp3; do echo $f; done"
prop_checkSpacefulness1 = verifyFull checkSpacefulness "a='cow moo'; echo $a"
prop_checkSpacefulness2 = verifyNotFull checkSpacefulness "a='cow moo'; [[ $a ]]"
prop_checkSpacefulness3 = verifyNotFull checkSpacefulness "a='cow*.mp3'; echo \"$a\""
prop_checkSpacefulness4 = verifyFull checkSpacefulness "for f in *.mp3; do echo $f; done"
prop_checkSpacefulness4a= verifyNotFull checkSpacefulness "foo=3; foo=$(echo $foo)"
prop_checkSpacefulness5 = verifyFull checkSpacefulness "a='*'; b=$a; c=lol${b//foo/bar}; echo $c"
prop_checkSpacefulness6 = verifyFull checkSpacefulness "a=foo$(lol); echo $a"
prop_checkSpacefulness7 = verifyFull checkSpacefulness "a=foo\\ bar; rm $a"
prop_checkSpacefulness8 = verifyNotFull checkSpacefulness "a=foo\\ bar; a=foo; rm $a"
prop_checkSpacefulnessA = verifyFull checkSpacefulness "rm $1"
prop_checkSpacefulnessB = verifyFull checkSpacefulness "rm ${10//foo/bar}"
prop_checkSpacefulnessC = verifyNotFull checkSpacefulness "(( $1 + 3 ))"
prop_checkSpacefulnessD = verifyNotFull checkSpacefulness "if [[ $2 -gt 14 ]]; then true; fi"
prop_checkSpacefulnessE = verifyNotFull checkSpacefulness "foo=$3 env"
prop_checkSpacefulnessF = verifyNotFull checkSpacefulness "local foo=$1"
prop_checkSpacefulnessG = verifyNotFull checkSpacefulness "declare foo=$1"
prop_checkSpacefulnessH = verifyFull checkSpacefulness "echo foo=$1"
prop_checkSpacefulnessI = verifyNotFull checkSpacefulness "$1 --flags"
prop_checkSpacefulnessJ = verifyFull checkSpacefulness "echo $PWD"
checkSpacefulness t =
doVariableFlowAnalysis readF writeF (Map.fromList defaults) t
where
defaults = zip variablesWithoutSpaces (repeat False)
hasSpaces name = do
map <- get
return $ Map.findWithDefault True name map
setSpaces name bool = do
modify $ Map.insert name bool
readF _ token name = do
spaced <- hasSpaces name
if spaced
&& (not $ "@" `isPrefixOf` name)
&& (not $ isCounting token)
&& (not $ inUnquotableContext parents token)
&& (not $ usedAsCommandName parents token)
then return [(getId token, Note InfoC 2086 warning)]
else return []
where
warning = "Double quote to prevent globbing and word splitting."
writeF _ _ name DataExternal = do
setSpaces name True
return []
writeF _ _ name (DataFrom vals) = do
map <- get
setSpaces name
(isSpacefulWord (\x -> Map.findWithDefault True x map) vals)
return []
parents = getParentTree t
isCounting (T_DollarBraced id token) =
case concat $ deadSimple token of
'#':_ -> True
_ -> False
isCounting _ = False
isSpacefulWord :: (String -> Bool) -> [Token] -> Bool
isSpacefulWord f words = any (isSpaceful f) words
isSpaceful :: (String -> Bool) -> Token -> Bool
isSpaceful spacefulF x =
case x of
T_DollarExpansion _ _ -> True
T_Backticked _ _ -> True
T_Glob _ _ -> True
T_Extglob _ _ _ -> True
T_Literal _ s -> s `containsAny` globspace
T_SingleQuoted _ s -> s `containsAny` globspace
T_DollarBraced _ l -> spacefulF $ getBracedReference $ bracedString l
T_NormalWord _ w -> isSpacefulWord spacefulF w
T_DoubleQuoted _ w -> isSpacefulWord spacefulF w
_ -> False
where
globspace = "*? \t\n"
containsAny s chars = any (\c -> c `elem` s) chars
prop_checkQuotesInLiterals1 = verifyFull checkQuotesInLiterals "param='--foo=\"bar\"'; app $param"
prop_checkQuotesInLiterals1a= verifyFull checkQuotesInLiterals "param=\"--foo='lolbar'\"; app $param"
prop_checkQuotesInLiterals2 = verifyNotFull checkQuotesInLiterals "param='--foo=\"bar\"'; app \"$param\""
prop_checkQuotesInLiterals3 =verifyNotFull checkQuotesInLiterals "param=('--foo='); app \"${param[@]}\""
prop_checkQuotesInLiterals4 = verifyNotFull checkQuotesInLiterals "param=\"don't bother with this one\"; app $param"
prop_checkQuotesInLiterals5 = verifyNotFull checkQuotesInLiterals "param=\"--foo='lolbar'\"; eval app $param"
checkQuotesInLiterals t =
doVariableFlowAnalysis readF writeF Map.empty t
where
getQuotes name = get >>= (return . Map.lookup name)
setQuotes name ref = modify $ Map.insert name ref
deleteQuotes = modify . Map.delete
parents = getParentTree t
quoteRegex = mkRegex "\"|([= ]|^)'|'( |$)"
containsQuotes s = isJust $ matchRegex quoteRegex s
writeF _ _ name (DataFrom values) = do
let quotedVars = filter (\v -> containsQuotes (concat $ deadSimple v)) values
case quotedVars of
[] -> deleteQuotes name
x:_ -> setQuotes name (getId x)
return []
writeF _ _ _ _ = return []
readF _ expr name = do
assignment <- getQuotes name
if isJust assignment
&& not (isParamTo parents "eval" expr)
&& not (inUnquotableContext parents expr)
then return [
(fromJust assignment,
Note WarningC 2089 "Word splitting will treat quotes as literals. Use an array."),
(getId expr,
Note WarningC 2090 "Embedded quotes in this variable will not be respected.")
]
else return []
prop_checkFunctionsUsedExternally1 =
verifyFull checkFunctionsUsedExternally "foo() { :; }; sudo foo"
prop_checkFunctionsUsedExternally2 =
verifyFull checkFunctionsUsedExternally "alias f='a'; xargs -n 1 f"
prop_checkFunctionsUsedExternally3 =
verifyNotFull checkFunctionsUsedExternally "f() { :; }; echo f"
checkFunctionsUsedExternally t =
runBasicAnalysis checkCommand t
where
invokingCmds = [
"chroot",
"find",
"screen",
"ssh",
"su",
"sudo",
"xargs"
]
checkCommand t@(T_SimpleCommand _ _ (cmd:args)) =
let name = fromMaybe "" $ getCommandBasename t in
when (name `elem` invokingCmds) $
mapM_ (checkArg name) args
checkCommand _ = return ()
functions = Map.fromList $ runBasicAnalysis findFunctions t
findFunctions (T_Function id name _) = modify ((name, id):)
findFunctions t@(T_SimpleCommand id _ (_:args))
| t `isUnqualifiedCommand` "alias" = mapM_ getAlias args
findFunctions _ = return ()
getAlias arg =
let string = concat $ deadSimple arg
in when ('=' `elem` string) $
modify ((takeWhile (/= '=') string, getId arg):)
checkArg cmd arg =
case Map.lookup (concat $ deadSimple arg) functions of
Nothing -> return ()
Just id -> do
warn (getId arg) 2033 $
"Shell functions can't be passed to external commands."
info id 2032 $
"Use own script or sh -c '..' to run this from " ++ cmd ++ "."
prop_checkUnused0 = verifyNotFull checkUnusedAssignments "var=foo; echo $var"
prop_checkUnused1 = verifyFull checkUnusedAssignments "var=foo; echo $bar"
prop_checkUnused2 = verifyNotFull checkUnusedAssignments "var=foo; export var;"
prop_checkUnused3 = verifyFull checkUnusedAssignments "for f in *; do echo '$f'; done"
prop_checkUnused4 = verifyFull checkUnusedAssignments "local i=0"
prop_checkUnused5 = verifyNotFull checkUnusedAssignments "read lol; echo $lol"
prop_checkUnused6 = verifyNotFull checkUnusedAssignments "var=4; (( var++ ))"
prop_checkUnused7 = verifyNotFull checkUnusedAssignments "var=2; $((var))"
prop_checkUnused8 = verifyFull checkUnusedAssignments "var=2; var=3;"
prop_checkUnused9 = verifyNotFull checkUnusedAssignments "read ''"
prop_checkUnused10= verifyNotFull checkUnusedAssignments "read -p 'test: '"
prop_checkUnused11= verifyNotFull checkUnusedAssignments "bar=5; export foo[$bar]=3"
prop_checkUnused12= verifyNotFull checkUnusedAssignments "read foo; echo ${!foo}"
checkUnusedAssignments t = snd $ runState (mapM_ checkAssignment flow) []
where
flow = getVariableFlow t
references = foldl (flip ($)) defaultMap (map insertRef flow)
insertRef (Reference (base, token, name)) =
Map.insert name ()
insertRef _ = id
checkAssignment (Assignment (_, token, name, _)) | isVariableName name =
case Map.lookup name references of
Just _ -> return ()
Nothing -> do
info (getId token) 2034 $
name ++ " appears unused. Verify it or export it."
checkAssignment _ = return ()
defaultMap = Map.fromList $ zip internalVariables $ repeat ()
prop_checkGlobsAsOptions1 = verify checkGlobsAsOptions "rm *.txt"
prop_checkGlobsAsOptions2 = verify checkGlobsAsOptions "ls ??.*"
prop_checkGlobsAsOptions3 = verifyNot checkGlobsAsOptions "rm -- *.txt"
checkGlobsAsOptions (T_SimpleCommand _ _ args) =
mapM_ check $ takeWhile (not . isEndOfArgs) args
where
check v@(T_NormalWord _ ((T_Glob id s):_)) | s == "*" || s == "?" =
info id 2035 $
"Use ./" ++ (concat $ deadSimple v)
++ " so names with dashes won't become options."
check _ = return ()
isEndOfArgs t =
case concat $ deadSimple t of
"--" -> True
":::" -> True
"::::" -> True
_ -> False
checkGlobsAsOptions _ = return ()
prop_checkWhileReadPitfalls1 = verify checkWhileReadPitfalls "while read foo; do ssh $foo uptime; done < file"
prop_checkWhileReadPitfalls2 = verifyNot checkWhileReadPitfalls "while read -u 3 foo; do ssh $foo uptime; done 3< file"
prop_checkWhileReadPitfalls3 = verifyNot checkWhileReadPitfalls "while true; do ssh host uptime; done"
prop_checkWhileReadPitfalls4 = verifyNot checkWhileReadPitfalls "while read foo; do ssh $foo hostname < /dev/null; done"
prop_checkWhileReadPitfalls5 = verifyNot checkWhileReadPitfalls "while read foo; do echo ls | ssh $foo; done"
prop_checkWhileReadPitfalls6 = verifyNot checkWhileReadPitfalls "while read foo <&3; do ssh $foo; done 3< foo"
checkWhileReadPitfalls (T_WhileExpression id [command] contents)
| isStdinReadCommand command = do
mapM_ checkMuncher contents
where
munchers = [ "ssh", "ffmpeg", "mplayer" ]
isStdinReadCommand (T_Pipeline _ [T_Redirecting id redirs cmd]) =
let plaintext = deadSimple cmd
in head (plaintext ++ [""]) == "read"
&& (not $ "-u" `elem` plaintext)
&& all (not . stdinRedirect) redirs
isStdinReadCommand _ = False
checkMuncher (T_Pipeline _ ((T_Redirecting _ redirs cmd):_)) = do
let name = fromMaybe "" $ getCommandBasename cmd
when ((not . any stdinRedirect $ redirs) && (name `elem` munchers)) $ do
info id 2095 $
name ++ " may swallow stdin, preventing this loop from working properly."
warn (getId cmd) 2095 $
"Add < /dev/null to prevent " ++ name ++ " from swallowing stdin."
checkMuncher _ = return ()
stdinRedirect (T_FdRedirect _ fd _)
| fd == "" || fd == "0" = True
stdinRedirect _ = False
checkWhileReadPitfalls _ = return ()
prop_checkPrefixAssign1 = verifyTree checkPrefixAssignmentReference "var=foo echo $var"
prop_checkPrefixAssign2 = verifyNotTree checkPrefixAssignmentReference "var=$(echo $var) cmd"
checkPrefixAssignmentReference t@(T_DollarBraced id value) tree =
check path
where
name = getBracedReference $ bracedString value
path = getPath tree t
idPath = map getId path
check [] = return ()
check (t:rest) =
case t of
T_SimpleCommand _ vars (_:_) -> mapM_ checkVar vars
otherwise -> check rest
checkVar (T_Assignment aId mode aName Nothing value) |
aName == name && (not $ aId `elem` idPath) = do
warn aId 2097 "This assignment is only seen by the forked process."
warn id 2098 "This expansion will not see the mentioned assignment."
checkVar _ = return ()
checkPrefixAssignmentReference _ _ = return ()
prop_checkCharRangeGlob1 = verify checkCharRangeGlob "ls *[:digit:].jpg"
prop_checkCharRangeGlob2 = verifyNot checkCharRangeGlob "ls *[[:digit:]].jpg"
prop_checkCharRangeGlob3 = verify checkCharRangeGlob "ls [10-15]"
prop_checkCharRangeGlob4 = verifyNot checkCharRangeGlob "ls [a-zA-Z]"
checkCharRangeGlob (T_Glob id str) | isCharClass str =
if ":" `isPrefixOf` contents
&& ":" `isSuffixOf` contents
&& contents /= ":"
then warn id 2101 "Named class needs outer [], e.g. [[:digit:]]."
else
if (not $ '[' `elem` contents) && hasDupes
then info id 2102 "Ranges can only match single chars (mentioned due to duplicates)."
else return ()
where
isCharClass str = "[" `isPrefixOf` str && "]" `isSuffixOf` str
contents = drop 1 . take ((length str) 1) $ str
hasDupes = any (>1) . map length . group . sort . filter (/= '-') $ contents
checkCharRangeGlob _ = return ()
prop_checkCdAndBack1 = verify (checkCdAndBack Sh) "for f in *; do cd $f; git pull; cd ..; done"
prop_checkCdAndBack2 = verifyNot (checkCdAndBack Sh) "for f in *; do cd $f || continue; git pull; cd ..; done"
prop_checkCdAndBack3 = verifyNot (checkCdAndBack Sh) "while [[ $PWD != / ]]; do cd ..; done"
checkCdAndBack shell = doLists
where
doLists (T_ForIn _ _ _ cmds) = doList cmds
doLists (T_WhileExpression _ _ cmds) = doList cmds
doLists (T_UntilExpression _ _ cmds) = doList cmds
doLists (T_IfExpression _ thens elses) = do
mapM_ (\(_, l) -> doList l) thens
doList elses
doLists _ = return ()
isCdRevert t =
case deadSimple t of
["cd", p] -> p `elem` ["..", "-"]
_ -> False
getCmd (T_Annotation id _ x) = getCmd x
getCmd (T_Pipeline id [x]) = getCommandName x
getCmd _ = Nothing
doList list =
let cds = filter ((== Just "cd") . getCmd) list in
when (length cds >= 2 && isCdRevert (last cds)) $
warn (getId $ head cds) 2103 message
message =
if shell == Bash || shell == Zsh
then "Consider using ( subshell ), 'cd foo||exit', or pushd/popd instead."
else "Consider using ( subshell ) or 'cd foo||exit' instead."