Warn when commands start with dashes (#938)

This commit is contained in:
Vidar Holen 2017-07-03 12:06:59 -07:00
parent a10b924570
commit a839a6657b
2 changed files with 26 additions and 4 deletions

View File

@ -125,6 +125,11 @@ isFlag token =
T_Literal _ ('-':_) : _ -> True T_Literal _ ('-':_) : _ -> True
_ -> False _ -> False
-- Is this token a flag where the - is unquoted?
isUnquotedFlag token = fromMaybe False $ do
str <- getLeadingUnquotedString token
return $ "-" `isPrefixOf` str
-- Given a T_DollarBraced, return a simplified version of the string contents. -- Given a T_DollarBraced, return a simplified version of the string contents.
bracedString (T_DollarBraced _ l) = concat $ oversimplify l bracedString (T_DollarBraced _ l) = concat $ oversimplify l
bracedString _ = error "Internal shellcheck error, please report! (bracedString on non-variable)" bracedString _ = error "Internal shellcheck error, please report! (bracedString on non-variable)"
@ -194,6 +199,13 @@ getTrailingUnquotedLiteral t =
T_Literal {} -> return t T_Literal {} -> return t
_ -> Nothing _ -> Nothing
-- Get the leading, unquoted, literal string of a token (if any).
getLeadingUnquotedString :: Token -> Maybe String
getLeadingUnquotedString t =
case t of
T_NormalWord _ ((T_Literal _ s) : _) -> return s
_ -> Nothing
-- Maybe get the literal string of this token and any globs in it. -- Maybe get the literal string of this token and any globs in it.
getGlobOrLiteralString = getLiteralStringExt f getGlobOrLiteralString = getLiteralStringExt f
where where

View File

@ -162,6 +162,7 @@ nodeChecks = [
,checkSplittingInArrays ,checkSplittingInArrays
,checkRedirectionToNumber ,checkRedirectionToNumber
,checkGlobAsCommand ,checkGlobAsCommand
,checkFlagAsCommand
,checkEmptyCondition ,checkEmptyCondition
] ]
@ -275,10 +276,7 @@ checkAssignAteCommand _ (T_SimpleCommand id (T_Assignment _ _ _ _ assignmentTerm
isCommonCommand _ = False isCommonCommand _ = False
firstWordIsArg list = fromMaybe False $ do firstWordIsArg list = fromMaybe False $ do
head <- list !!! 0 head <- list !!! 0
return . or $ mapMaybe ($ head) [return . isGlob, isFlag] return $ isGlob head || isUnquotedFlag head
isFlag word = do
first <- (concat $ oversimplify word) !!! 0
return $ first == '-'
checkAssignAteCommand _ _ = return () checkAssignAteCommand _ _ = return ()
@ -2770,6 +2768,18 @@ checkGlobAsCommand _ t = case t of
warn (getId first) 2211 "This is a glob used as a command name. Was it supposed to be in ${..}, array, or is it missing quoting?" warn (getId first) 2211 "This is a glob used as a command name. Was it supposed to be in ${..}, array, or is it missing quoting?"
_ -> return () _ -> return ()
prop_checkFlagAsCommand1 = verify checkFlagAsCommand "-e file"
prop_checkFlagAsCommand2 = verify checkFlagAsCommand "foo\n --bar=baz"
prop_checkFlagAsCommand3 = verifyNot checkFlagAsCommand "'--myexec--' args"
prop_checkFlagAsCommand4 = verifyNot checkFlagAsCommand "var=cmd --arg" -- Handled by SC2037
checkFlagAsCommand _ t = case t of
T_SimpleCommand _ [] (first:_) ->
when (isUnquotedFlag first) $
warn (getId first) 2215 "This flag is used as a command name. Bad line break or missing [ .. ]?"
_ -> return ()
prop_checkEmptyCondition1 = verify checkEmptyCondition "if [ ]; then ..; fi" prop_checkEmptyCondition1 = verify checkEmptyCondition "if [ ]; then ..; fi"
prop_checkEmptyCondition2 = verifyNot checkEmptyCondition "[ foo -o bar ]" prop_checkEmptyCondition2 = verifyNot checkEmptyCondition "[ foo -o bar ]"
checkEmptyCondition _ t = case t of checkEmptyCondition _ t = case t of