Use mapM_ and sequence_ instead of reimplementing them
This commit is contained in:
parent
cc424bac11
commit
ffbbfcfe25
|
@ -382,7 +382,7 @@ getAssociativeArrays t =
|
||||||
nub . execWriter $ doAnalysis f t
|
nub . execWriter $ doAnalysis f t
|
||||||
where
|
where
|
||||||
f :: Token -> Writer [String] ()
|
f :: Token -> Writer [String] ()
|
||||||
f t@T_SimpleCommand {} = fromMaybe (return ()) $ do
|
f t@T_SimpleCommand {} = sequence_ $ do
|
||||||
name <- getCommandName t
|
name <- getCommandName t
|
||||||
let assocNames = ["declare","local","typeset"]
|
let assocNames = ["declare","local","typeset"]
|
||||||
guard $ elem name assocNames
|
guard $ elem name assocNames
|
||||||
|
|
|
@ -404,7 +404,7 @@ prop_checkArithmeticOpCommand1 = verify checkArithmeticOpCommand "i=i + 1"
|
||||||
prop_checkArithmeticOpCommand2 = verify checkArithmeticOpCommand "foo=bar * 2"
|
prop_checkArithmeticOpCommand2 = verify checkArithmeticOpCommand "foo=bar * 2"
|
||||||
prop_checkArithmeticOpCommand3 = verifyNot checkArithmeticOpCommand "foo + opts"
|
prop_checkArithmeticOpCommand3 = verifyNot checkArithmeticOpCommand "foo + opts"
|
||||||
checkArithmeticOpCommand _ (T_SimpleCommand id [T_Assignment {}] (firstWord:_)) =
|
checkArithmeticOpCommand _ (T_SimpleCommand id [T_Assignment {}] (firstWord:_)) =
|
||||||
maybe (return ()) check $ getGlobOrLiteralString firstWord
|
mapM_ check $ getGlobOrLiteralString firstWord
|
||||||
where
|
where
|
||||||
check op =
|
check op =
|
||||||
when (op `elem` ["+", "-", "*", "/"]) $
|
when (op `elem` ["+", "-", "*", "/"]) $
|
||||||
|
@ -415,7 +415,7 @@ checkArithmeticOpCommand _ _ = return ()
|
||||||
prop_checkWrongArit = verify checkWrongArithmeticAssignment "i=i+1"
|
prop_checkWrongArit = verify checkWrongArithmeticAssignment "i=i+1"
|
||||||
prop_checkWrongArit2 = verify checkWrongArithmeticAssignment "n=2; i=n*2"
|
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:[]) []) =
|
||||||
fromMaybe (return ()) $ do
|
sequence_ $ do
|
||||||
str <- getNormalString val
|
str <- getNormalString val
|
||||||
match <- matchRegex regex str
|
match <- matchRegex regex str
|
||||||
var <- match !!! 0
|
var <- match !!! 0
|
||||||
|
@ -2524,7 +2524,7 @@ checkUnpassedInFunctions params root =
|
||||||
|
|
||||||
referenceList :: [(String, Bool, Token)]
|
referenceList :: [(String, Bool, Token)]
|
||||||
referenceList = execWriter $
|
referenceList = execWriter $
|
||||||
doAnalysis (fromMaybe (return ()) . checkCommand) root
|
doAnalysis (sequence_ . checkCommand) root
|
||||||
checkCommand :: Token -> Maybe (Writer [(String, Bool, Token)] ())
|
checkCommand :: Token -> Maybe (Writer [(String, Bool, Token)] ())
|
||||||
checkCommand t@(T_SimpleCommand _ _ (cmd:args)) = do
|
checkCommand t@(T_SimpleCommand _ _ (cmd:args)) = do
|
||||||
str <- getLiteralString cmd
|
str <- getLiteralString cmd
|
||||||
|
@ -2648,9 +2648,7 @@ prop_checkSuspiciousIFS1 = verify checkSuspiciousIFS "IFS=\"\\n\""
|
||||||
prop_checkSuspiciousIFS2 = verifyNot checkSuspiciousIFS "IFS=$'\\t'"
|
prop_checkSuspiciousIFS2 = verifyNot checkSuspiciousIFS "IFS=$'\\t'"
|
||||||
prop_checkSuspiciousIFS3 = verify checkSuspiciousIFS "IFS=' \\t\\n'"
|
prop_checkSuspiciousIFS3 = verify checkSuspiciousIFS "IFS=' \\t\\n'"
|
||||||
checkSuspiciousIFS params (T_Assignment _ _ "IFS" [] value) =
|
checkSuspiciousIFS params (T_Assignment _ _ "IFS" [] value) =
|
||||||
potentially $ do
|
mapM_ check $ getLiteralString value
|
||||||
str <- getLiteralString value
|
|
||||||
return $ check str
|
|
||||||
where
|
where
|
||||||
hasDollarSingle = shellType params == Bash || shellType params == Ksh
|
hasDollarSingle = shellType params == Bash || shellType params == Ksh
|
||||||
n = if hasDollarSingle then "$'\\n'" else "'<literal linefeed here>'"
|
n = if hasDollarSingle then "$'\\n'" else "'<literal linefeed here>'"
|
||||||
|
@ -3465,7 +3463,7 @@ prop_checkTranslatedStringVariable3 = verifyNot checkTranslatedStringVariable "$
|
||||||
prop_checkTranslatedStringVariable4 = verifyNot checkTranslatedStringVariable "var=val; $\"$var\""
|
prop_checkTranslatedStringVariable4 = verifyNot checkTranslatedStringVariable "var=val; $\"$var\""
|
||||||
prop_checkTranslatedStringVariable5 = verifyNot checkTranslatedStringVariable "foo=var; bar=val2; $\"foo bar\""
|
prop_checkTranslatedStringVariable5 = verifyNot checkTranslatedStringVariable "foo=var; bar=val2; $\"foo bar\""
|
||||||
checkTranslatedStringVariable params (T_DollarDoubleQuoted id [T_Literal _ s]) =
|
checkTranslatedStringVariable params (T_DollarDoubleQuoted id [T_Literal _ s]) =
|
||||||
fromMaybe (return ()) $ do
|
sequence_ $ do
|
||||||
guard $ all isVariableChar s
|
guard $ all isVariableChar s
|
||||||
Map.lookup s assignments
|
Map.lookup s assignments
|
||||||
return $
|
return $
|
||||||
|
|
|
@ -122,7 +122,7 @@ buildCommandMap = foldl' addCheck Map.empty
|
||||||
|
|
||||||
|
|
||||||
checkCommand :: Map.Map CommandName (Token -> Analysis) -> Token -> Analysis
|
checkCommand :: Map.Map CommandName (Token -> Analysis) -> Token -> Analysis
|
||||||
checkCommand map t@(T_SimpleCommand id cmdPrefix (cmd:rest)) = fromMaybe (return ()) $ do
|
checkCommand map t@(T_SimpleCommand id cmdPrefix (cmd:rest)) = sequence_ $ do
|
||||||
name <- getLiteralString cmd
|
name <- getLiteralString cmd
|
||||||
return $
|
return $
|
||||||
if '/' `elem` name
|
if '/' `elem` name
|
||||||
|
@ -575,7 +575,7 @@ checkPrintfVar = CommandCheck (Exactly "printf") (f . arguments) where
|
||||||
f _ = return ()
|
f _ = return ()
|
||||||
|
|
||||||
check format more = do
|
check format more = do
|
||||||
fromMaybe (return ()) $ do
|
sequence_ $ do
|
||||||
string <- getLiteralString format
|
string <- getLiteralString format
|
||||||
let formats = getPrintfFormats string
|
let formats = getPrintfFormats string
|
||||||
let formatCount = length formats
|
let formatCount = length formats
|
||||||
|
@ -945,7 +945,7 @@ checkCatastrophicRm = CommandCheck (Basename "rm") $ \t ->
|
||||||
Nothing ->
|
Nothing ->
|
||||||
checkWord' token
|
checkWord' token
|
||||||
|
|
||||||
checkWord' token = fromMaybe (return ()) $ do
|
checkWord' token = sequence_ $ do
|
||||||
filename <- getPotentialPath token
|
filename <- getPotentialPath token
|
||||||
let path = fixPath filename
|
let path = fixPath filename
|
||||||
return . when (path `elem` importantPaths) $
|
return . when (path `elem` importantPaths) $
|
||||||
|
|
|
@ -586,7 +586,7 @@ readConditionContents single =
|
||||||
return $ TC_Nullary id typ x
|
return $ TC_Nullary id typ x
|
||||||
)
|
)
|
||||||
|
|
||||||
checkTrailingOp x = fromMaybe (return ()) $ do
|
checkTrailingOp x = sequence_ $ do
|
||||||
(T_Literal id str) <- getTrailingUnquotedLiteral x
|
(T_Literal id str) <- getTrailingUnquotedLiteral x
|
||||||
trailingOp <- find (`isSuffixOf` str) binaryTestOps
|
trailingOp <- find (`isSuffixOf` str) binaryTestOps
|
||||||
return $ parseProblemAtId id ErrorC 1108 $
|
return $ parseProblemAtId id ErrorC 1108 $
|
||||||
|
|
Loading…
Reference in New Issue