Improve spans for some warnings
This commit is contained in:
parent
7138abff4b
commit
868a7be33e
|
@ -293,17 +293,27 @@ getCommand t =
|
|||
T_Annotation _ _ t -> getCommand t
|
||||
_ -> Nothing
|
||||
|
||||
-- Maybe get the command name of a token representing a command
|
||||
getCommandName t = do
|
||||
-- Maybe get the command name string of a token representing a command
|
||||
getCommandName :: Token -> Maybe String
|
||||
getCommandName = fst . getCommandNameAndToken
|
||||
|
||||
-- Get the command name token from a command, i.e.
|
||||
-- the token representing 'ls' in 'ls -la 2> foo'.
|
||||
-- If it can't be determined, return the original token.
|
||||
getCommandTokenOrThis = snd . getCommandNameAndToken
|
||||
|
||||
getCommandNameAndToken :: Token -> (Maybe String, Token)
|
||||
getCommandNameAndToken t = fromMaybe (Nothing, t) $ do
|
||||
(T_SimpleCommand _ _ (w:rest)) <- getCommand t
|
||||
s <- getLiteralString w
|
||||
if "busybox" `isSuffixOf` s || "builtin" == s
|
||||
then
|
||||
case rest of
|
||||
(applet:_) -> getLiteralString applet
|
||||
_ -> return s
|
||||
(applet:_) -> return (getLiteralString applet, applet)
|
||||
_ -> return (Just s, w)
|
||||
else
|
||||
return s
|
||||
return (Just s, w)
|
||||
|
||||
|
||||
-- If a command substitution is a single command, get its name.
|
||||
-- $(date +%s) = Just "date"
|
||||
|
|
|
@ -396,7 +396,7 @@ checkPipePitfalls _ (T_Pipeline id _ commands) = do
|
|||
mapM_ (f . (\ 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 func (x:_) = func (getId $ getCommandTokenOrThis x)
|
||||
first _ _ = return ()
|
||||
hasShortParameter char = any (\x -> "-" `isPrefixOf` x && char `elem` x)
|
||||
hasParameter string =
|
||||
|
@ -2472,7 +2472,7 @@ prop_checkReadWithoutR1 = verify checkReadWithoutR "read -a foo"
|
|||
prop_checkReadWithoutR2 = verifyNot checkReadWithoutR "read -ar foo"
|
||||
checkReadWithoutR _ t@T_SimpleCommand {} | t `isUnqualifiedCommand` "read" =
|
||||
unless ("r" `elem` map snd (getAllFlags t)) $
|
||||
info (getId t) 2162 "read without -r will mangle backslashes."
|
||||
info (getId $ getCommandTokenOrThis t) 2162 "read without -r will mangle backslashes."
|
||||
checkReadWithoutR _ _ = return ()
|
||||
|
||||
prop_checkUncheckedCd1 = verifyTree checkUncheckedCdPushdPopd "cd ~/src; rm -r foo"
|
||||
|
|
|
@ -183,7 +183,7 @@ prop_checkNeedlessExpr4 = verifyNot checkNeedlessExpr "foo=$(expr foo \\< regex)
|
|||
checkNeedlessExpr = CommandCheck (Basename "expr") f where
|
||||
f t =
|
||||
when (all (`notElem` exceptions) (words $ arguments t)) $
|
||||
style (getId t) 2003
|
||||
style (getId $ getCommandTokenOrThis t) 2003
|
||||
"expr is antiquated. Consider rewriting this using $((..)), ${} or [[ ]]."
|
||||
-- These operators are hard to replicate in POSIX
|
||||
exceptions = [ ":", "<", ">", "<=", ">=" ]
|
||||
|
@ -741,20 +741,20 @@ checkLocalScope = CommandCheck (Exactly "local") $ \t ->
|
|||
whenShell [Bash, Dash] $ do -- Ksh allows it, Sh doesn't support local
|
||||
path <- getPathM t
|
||||
unless (any isFunction path) $
|
||||
err (getId t) 2168 "'local' is only valid in functions."
|
||||
err (getId $ getCommandTokenOrThis t) 2168 "'local' is only valid in functions."
|
||||
|
||||
prop_checkDeprecatedTempfile1 = verify checkDeprecatedTempfile "var=$(tempfile)"
|
||||
prop_checkDeprecatedTempfile2 = verifyNot checkDeprecatedTempfile "tempfile=$(mktemp)"
|
||||
checkDeprecatedTempfile = CommandCheck (Basename "tempfile") $
|
||||
\t -> warn (getId t) 2186 "tempfile is deprecated. Use mktemp instead."
|
||||
\t -> warn (getId $ getCommandTokenOrThis t) 2186 "tempfile is deprecated. Use mktemp instead."
|
||||
|
||||
prop_checkDeprecatedEgrep = verify checkDeprecatedEgrep "egrep '.+'"
|
||||
checkDeprecatedEgrep = CommandCheck (Basename "egrep") $
|
||||
\t -> info (getId t) 2196 "egrep is non-standard and deprecated. Use grep -E instead."
|
||||
\t -> info (getId $ getCommandTokenOrThis t) 2196 "egrep is non-standard and deprecated. Use grep -E instead."
|
||||
|
||||
prop_checkDeprecatedFgrep = verify checkDeprecatedFgrep "fgrep '*' files"
|
||||
checkDeprecatedFgrep = CommandCheck (Basename "fgrep") $
|
||||
\t -> info (getId t) 2197 "fgrep is non-standard and deprecated. Use grep -F instead."
|
||||
\t -> info (getId $ getCommandTokenOrThis t) 2197 "fgrep is non-standard and deprecated. Use grep -F instead."
|
||||
|
||||
prop_checkWhileGetoptsCase1 = verify checkWhileGetoptsCase "while getopts 'a:b' x; do case $x in a) foo;; esac; done"
|
||||
prop_checkWhileGetoptsCase2 = verify checkWhileGetoptsCase "while getopts 'a:' x; do case $x in a) foo;; b) bar;; esac; done"
|
||||
|
@ -948,7 +948,7 @@ checkFindRedirections = CommandCheck (Basename "find") f
|
|||
|
||||
prop_checkWhich = verify checkWhich "which '.+'"
|
||||
checkWhich = CommandCheck (Basename "which") $
|
||||
\t -> info (getId t) 2230 "which is non-standard. Use builtin 'command -v' instead."
|
||||
\t -> info (getId $ getCommandTokenOrThis t) 2230 "which is non-standard. Use builtin 'command -v' instead."
|
||||
|
||||
prop_checkSudoRedirect1 = verify checkSudoRedirect "sudo echo 3 > /proc/file"
|
||||
prop_checkSudoRedirect2 = verify checkSudoRedirect "sudo cmd < input"
|
||||
|
|
|
@ -2682,8 +2682,8 @@ readAssignmentWordExt lenient = try $ do
|
|||
indices <- many readArrayIndex
|
||||
hasLeftSpace <- fmap (not . null) spacing
|
||||
pos <- getPosition
|
||||
op <- readAssignmentOp
|
||||
id <- endSpan start
|
||||
op <- readAssignmentOp
|
||||
hasRightSpace <- fmap (not . null) spacing
|
||||
isEndOfCommand <- fmap isJust $ optionMaybe (try . lookAhead $ (void (oneOf "\r\n;&|)") <|> eof))
|
||||
if not hasLeftSpace && (hasRightSpace || isEndOfCommand)
|
||||
|
|
Loading…
Reference in New Issue