mirror of
https://github.com/koalaman/shellcheck
synced 2025-07-07 05:21:34 -07:00
Merge pull request #2119 from josephcsible/refactors
Various refactorings
This commit is contained in:
commit
15ff87cf80
6 changed files with 28 additions and 35 deletions
|
@ -417,7 +417,7 @@ prop_checkAssignAteCommand4 = verifyNot checkAssignAteCommand "A=foo ls -l"
|
|||
prop_checkAssignAteCommand5 = verify checkAssignAteCommand "PAGER=cat grep bar"
|
||||
prop_checkAssignAteCommand6 = verifyNot checkAssignAteCommand "PAGER=\"cat\" grep bar"
|
||||
prop_checkAssignAteCommand7 = verify checkAssignAteCommand "here=pwd"
|
||||
checkAssignAteCommand _ (T_SimpleCommand id (T_Assignment _ _ _ _ assignmentTerm:[]) list) =
|
||||
checkAssignAteCommand _ (T_SimpleCommand id [T_Assignment _ _ _ _ assignmentTerm] list) =
|
||||
-- Check if first word is intended as an argument (flag or glob).
|
||||
if firstWordIsArg list
|
||||
then
|
||||
|
@ -449,7 +449,7 @@ checkArithmeticOpCommand _ _ = return ()
|
|||
|
||||
prop_checkWrongArit = verify checkWrongArithmeticAssignment "i=i+1"
|
||||
prop_checkWrongArit2 = verify checkWrongArithmeticAssignment "n=2; i=n*2"
|
||||
checkWrongArithmeticAssignment params (T_SimpleCommand id (T_Assignment _ _ _ _ val:[]) []) =
|
||||
checkWrongArithmeticAssignment params (T_SimpleCommand id [T_Assignment _ _ _ _ val] []) =
|
||||
sequence_ $ do
|
||||
str <- getNormalString val
|
||||
match <- matchRegex regex str
|
||||
|
@ -2518,7 +2518,7 @@ checkCharRangeGlob p t@(T_Glob id str) |
|
|||
where
|
||||
isCharClass str = "[" `isPrefixOf` str && "]" `isSuffixOf` str
|
||||
contents = dropNegation . drop 1 . take (length str - 1) $ str
|
||||
hasDupes = any (>1) . map length . group . sort . filter (/= '-') $ contents
|
||||
hasDupes = any ((>1) . length) . group . sort . filter (/= '-') $ contents
|
||||
dropNegation s =
|
||||
case s of
|
||||
'!':rest -> rest
|
||||
|
@ -2881,7 +2881,7 @@ checkTestArgumentSplitting params t =
|
|||
then
|
||||
-- Ksh appears to stop processing after unrecognized tokens, so operators
|
||||
-- will effectively work with globs, but only the first match.
|
||||
when (op `elem` ['-':c:[] | c <- "bcdfgkprsuwxLhNOGRS" ]) $
|
||||
when (op `elem` [['-', c] | c <- "bcdfgkprsuwxLhNOGRS" ]) $
|
||||
warn (getId token) 2245 $
|
||||
op ++ " only applies to the first expansion of this glob. Use a loop to check any/all."
|
||||
else
|
||||
|
@ -3408,7 +3408,7 @@ checkPipeToNowhere params t =
|
|||
|
||||
sequence_ $ do
|
||||
T_Redirecting _ redirs cmd <- return stage
|
||||
fds <- sequence $ map getRedirectionFds redirs
|
||||
fds <- mapM getRedirectionFds redirs
|
||||
|
||||
let fdAndToken :: [(Integer, Token)]
|
||||
fdAndToken =
|
||||
|
@ -3441,7 +3441,7 @@ checkPipeToNowhere params t =
|
|||
|
||||
commandSpecificException name cmd =
|
||||
case name of
|
||||
"du" -> any (`elem` ["exclude-from", "files0-from"]) $ map snd $ getAllFlags cmd
|
||||
"du" -> any ((`elem` ["exclude-from", "files0-from"]) . snd) $ getAllFlags cmd
|
||||
_ -> False
|
||||
|
||||
warnAboutDupes (n, list@(_:_:_)) =
|
||||
|
@ -3845,7 +3845,7 @@ checkAliasUsedInSameParsingUnit params root =
|
|||
-- Group them by whether they start on the same line where the previous one ended
|
||||
units = groupByLink followsOnLine commands
|
||||
in
|
||||
execWriter $ sequence_ $ map checkUnit units
|
||||
execWriter $ mapM_ checkUnit units
|
||||
where
|
||||
lineSpan t =
|
||||
let m = tokenPositions params in do
|
||||
|
@ -3895,13 +3895,13 @@ groupByLink :: (a -> a -> Bool) -> [a] -> [[a]]
|
|||
groupByLink f list =
|
||||
case list of
|
||||
[] -> []
|
||||
(x:xs) -> g x [] xs
|
||||
(x:xs) -> foldr c n xs x []
|
||||
where
|
||||
g current span (next:rest) =
|
||||
c next rest current span =
|
||||
if f current next
|
||||
then g next (current:span) rest
|
||||
else (reverse $ current:span) : g next [] rest
|
||||
g current span [] = [reverse (current:span)]
|
||||
then rest next (current:span)
|
||||
else (reverse $ current:span) : rest next []
|
||||
n current span = [reverse (current:span)]
|
||||
|
||||
|
||||
prop_checkBlatantRecursion1 = verify checkBlatantRecursion ":(){ :|:& };:"
|
||||
|
|
Loading…
Add table
Add a link
Reference in a new issue