From 35033a9f2fdca88b916b62bbff284c218167d8f4 Mon Sep 17 00:00:00 2001 From: "Joseph C. Sible" Date: Mon, 28 Dec 2020 16:22:53 -0500 Subject: [PATCH 01/14] Remove unnecessary use of Maybe from shellFor --- src/ShellCheck/AnalyzerLib.hs | 6 +++--- 1 file changed, 3 insertions(+), 3 deletions(-) diff --git a/src/ShellCheck/AnalyzerLib.hs b/src/ShellCheck/AnalyzerLib.hs index 194bf18..9265a3f 100644 --- a/src/ShellCheck/AnalyzerLib.hs +++ b/src/ShellCheck/AnalyzerLib.hs @@ -258,9 +258,9 @@ determineShell fallbackShell t = fromMaybe Bash $ executableFromShebang :: String -> String executableFromShebang = shellFor where - shellFor s | "/env " `isInfixOf` s = fromMaybe "" $ do - [flag, shell] <- matchRegex re s - return shell + shellFor s | "/env " `isInfixOf` s = case matchRegex re s of + Just [flag, shell] -> shell + _ -> "" shellFor s | ' ' `elem` s = shellFor $ takeWhile (/= ' ') s shellFor s = reverse . takeWhile (/= '/') . reverse $ s re = mkRegex "/env +(-S|--split-string=?)? *([^ ]*)" From eaccd3d02c2e9c2f64d796801220ced38cce57fd Mon Sep 17 00:00:00 2001 From: "Joseph C. Sible" Date: Mon, 28 Dec 2020 16:32:10 -0500 Subject: [PATCH 02/14] Simplify parser --- src/ShellCheck/Parser.hs | 4 ++-- 1 file changed, 2 insertions(+), 2 deletions(-) diff --git a/src/ShellCheck/Parser.hs b/src/ShellCheck/Parser.hs index dbadc7c..104e0a4 100644 --- a/src/ShellCheck/Parser.hs +++ b/src/ShellCheck/Parser.hs @@ -392,7 +392,7 @@ unexpecting s p = try $ notFollowedBy2 = unexpecting "" -isFollowedBy p = (lookAhead . try $ p *> return True) <|> return False +isFollowedBy p = (lookAhead . try $ p $> True) <|> return False reluctantlyTill p end = (lookAhead (void (try end) <|> eof) >> return []) <|> do @@ -2715,7 +2715,7 @@ readConditionCommand = do pos <- getPosition hasDashAo <- isFollowedBy $ do - c <- choice $ map (\s -> try $ string s) ["-o", "-a", "or", "and"] + c <- choice $ try . string <$> ["-o", "-a", "or", "and"] posEnd <- getPosition parseProblemAtWithEnd pos posEnd ErrorC 1139 $ "Use " ++ alt c ++ " instead of '" ++ c ++ "' between test commands." From 46f177b5beb5c9862bfd5e3d10cc25a844af4c4c Mon Sep 17 00:00:00 2001 From: "Joseph C. Sible" Date: Mon, 28 Dec 2020 17:14:18 -0500 Subject: [PATCH 03/14] Simplify parseArgs --- src/ShellCheck/AnalyzerLib.hs | 8 +++----- 1 file changed, 3 insertions(+), 5 deletions(-) diff --git a/src/ShellCheck/AnalyzerLib.hs b/src/ShellCheck/AnalyzerLib.hs index 9265a3f..a1e089a 100644 --- a/src/ShellCheck/AnalyzerLib.hs +++ b/src/ShellCheck/AnalyzerLib.hs @@ -687,12 +687,10 @@ getModifiedVariableCommand base@(T_SimpleCommand id cmdPrefix (T_NormalWord _ (T parseArgs :: Maybe (Token, Token, String, DataType) parseArgs = do args <- getGnuOpts "d:n:O:s:u:C:c:t" rest - let names = map snd $ filter (\(x,y) -> null x) args - if null names - then + case [y | ("",(_,y)) <- args] of + [] -> return (base, base, "MAPFILE", DataArray SourceExternal) - else do - (_, first) <- listToMaybe names + first:_ -> do name <- getLiteralString first guard $ isVariableName name return (base, first, name, DataArray SourceExternal) From 0607039d419a075df594fd5c38153e2d4863e834 Mon Sep 17 00:00:00 2001 From: "Joseph C. Sible" Date: Mon, 28 Dec 2020 17:21:47 -0500 Subject: [PATCH 04/14] Simplify actualArgs --- src/ShellCheck/Checks/Commands.hs | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/src/ShellCheck/Checks/Commands.hs b/src/ShellCheck/Checks/Commands.hs index aa4edd4..f1996ef 100644 --- a/src/ShellCheck/Checks/Commands.hs +++ b/src/ShellCheck/Checks/Commands.hs @@ -122,7 +122,7 @@ checkGetOpts str flags args f = toTokens = map (T_Literal (Id 0)) . words opts = fromMaybe [] $ f (toTokens str) actualFlags = filter (not . null) $ map fst opts - actualArgs = map (\(_, (_, x)) -> onlyLiteralString x) $ filter (null . fst) opts + actualArgs = [onlyLiteralString x | ("", (_, x)) <- opts] -- Short options prop_checkGetOptsS1 = checkGetOpts "-f x" ["f"] [] $ getOpts (True, True) "f:" [] From cb4f4e7edc8721e12bd7a4ace9f88e8468961c53 Mon Sep 17 00:00:00 2001 From: "Joseph C. Sible" Date: Mon, 28 Dec 2020 17:34:52 -0500 Subject: [PATCH 05/14] Use mapM_ instead of reimplementing it --- src/ShellCheck/Analytics.hs | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/src/ShellCheck/Analytics.hs b/src/ShellCheck/Analytics.hs index 2fb1253..3d5692a 100644 --- a/src/ShellCheck/Analytics.hs +++ b/src/ShellCheck/Analytics.hs @@ -3808,7 +3808,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 From 2c0766825e3e25589467c03435416f2fa3d9062f Mon Sep 17 00:00:00 2001 From: "Joseph C. Sible" Date: Mon, 28 Dec 2020 17:45:11 -0500 Subject: [PATCH 06/14] Implement groupByLink in terms of foldr --- src/ShellCheck/Analytics.hs | 10 +++++----- 1 file changed, 5 insertions(+), 5 deletions(-) diff --git a/src/ShellCheck/Analytics.hs b/src/ShellCheck/Analytics.hs index 3d5692a..70d7f8e 100644 --- a/src/ShellCheck/Analytics.hs +++ b/src/ShellCheck/Analytics.hs @@ -3858,13 +3858,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 ":(){ :|:& };:" From dfbcc9595e0b80e25c61bfedb7ad0347ff045395 Mon Sep 17 00:00:00 2001 From: "Joseph C. Sible" Date: Mon, 28 Dec 2020 17:48:58 -0500 Subject: [PATCH 07/14] Use mapM instead of reimplementing it --- src/ShellCheck/Analytics.hs | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/src/ShellCheck/Analytics.hs b/src/ShellCheck/Analytics.hs index 70d7f8e..945397c 100644 --- a/src/ShellCheck/Analytics.hs +++ b/src/ShellCheck/Analytics.hs @@ -3371,7 +3371,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 = From 848056367267e75cb3db0e45ec282a58105c0ed0 Mon Sep 17 00:00:00 2001 From: "Joseph C. Sible" Date: Mon, 28 Dec 2020 17:55:54 -0500 Subject: [PATCH 08/14] Use syntactic sugar instead of building lists by hand --- src/ShellCheck/ASTLib.hs | 2 +- src/ShellCheck/Analytics.hs | 6 +++--- src/ShellCheck/Checks/Commands.hs | 2 +- 3 files changed, 5 insertions(+), 5 deletions(-) diff --git a/src/ShellCheck/ASTLib.hs b/src/ShellCheck/ASTLib.hs index dcc9904..6e48bf3 100644 --- a/src/ShellCheck/ASTLib.hs +++ b/src/ShellCheck/ASTLib.hs @@ -177,7 +177,7 @@ getOpts (gnu, arbitraryLongOpts) string longopts args = process args process [] = return [] process (token:rest) = do case getLiteralStringDef "\0" token of - '-':'-':[] -> return $ listToArgs rest + "--" -> return $ listToArgs rest '-':'-':word -> do let (name, arg) = span (/= '=') word needsArg <- diff --git a/src/ShellCheck/Analytics.hs b/src/ShellCheck/Analytics.hs index 945397c..c8473eb 100644 --- a/src/ShellCheck/Analytics.hs +++ b/src/ShellCheck/Analytics.hs @@ -394,7 +394,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 @@ -426,7 +426,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 @@ -2844,7 +2844,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 diff --git a/src/ShellCheck/Checks/Commands.hs b/src/ShellCheck/Checks/Commands.hs index f1996ef..771083e 100644 --- a/src/ShellCheck/Checks/Commands.hs +++ b/src/ShellCheck/Checks/Commands.hs @@ -916,7 +916,7 @@ checkWhileGetoptsCase = CommandCheck (Exactly "getopts") f fromGlob t = case t of - T_Glob _ ('[':c:']':[]) -> return [c] + T_Glob _ ['[', c, ']'] -> return [c] T_Glob _ "*" -> return "*" T_Glob _ "?" -> return "?" _ -> Nothing From e7820479f0502ea4571ec797d286c9037a81d967 Mon Sep 17 00:00:00 2001 From: "Joseph C. Sible" Date: Mon, 28 Dec 2020 17:56:25 -0500 Subject: [PATCH 09/14] Use find --- src/ShellCheck/ASTLib.hs | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/src/ShellCheck/ASTLib.hs b/src/ShellCheck/ASTLib.hs index 6e48bf3..c038ebe 100644 --- a/src/ShellCheck/ASTLib.hs +++ b/src/ShellCheck/ASTLib.hs @@ -425,7 +425,7 @@ getCommandNameAndToken direct t = fromMaybe (Nothing, t) $ do "run" -> firstArg -- Used by bats "exec" -> do opts <- getBsdOpts "cla:" args - (_, (t, _)) <- listToMaybe $ filter (null . fst) opts + (_, (t, _)) <- find (null . fst) opts return t _ -> fail "" From 34939ca0b7dce27472543466eeab1f68df317274 Mon Sep 17 00:00:00 2001 From: "Joseph C. Sible" Date: Mon, 28 Dec 2020 18:00:14 -0500 Subject: [PATCH 10/14] Fuse map into any --- src/ShellCheck/Analytics.hs | 4 ++-- 1 file changed, 2 insertions(+), 2 deletions(-) diff --git a/src/ShellCheck/Analytics.hs b/src/ShellCheck/Analytics.hs index c8473eb..98fd5d7 100644 --- a/src/ShellCheck/Analytics.hs +++ b/src/ShellCheck/Analytics.hs @@ -2481,7 +2481,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 @@ -3404,7 +3404,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@(_:_:_)) = From 81e84c293944292dfb05cf09048a5eb8bbfca40b Mon Sep 17 00:00:00 2001 From: "Joseph C. Sible" Date: Mon, 28 Dec 2020 18:03:14 -0500 Subject: [PATCH 11/14] Use execState instead of snd . runState --- src/ShellCheck/AnalyzerLib.hs | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/src/ShellCheck/AnalyzerLib.hs b/src/ShellCheck/AnalyzerLib.hs index a1e089a..f8e490e 100644 --- a/src/ShellCheck/AnalyzerLib.hs +++ b/src/ShellCheck/AnalyzerLib.hs @@ -270,7 +270,7 @@ executableFromShebang = shellFor -- This is used to populate parentMap in Parameters getParentTree :: Token -> Map.Map Id Token getParentTree t = - snd . snd $ runState (doStackAnalysis pre post t) ([], Map.empty) + snd $ execState (doStackAnalysis pre post t) ([], Map.empty) where pre t = modify (first ((:) t)) post t = do From e272fa04eed3e3f205e048a207d99e4cb011efcd Mon Sep 17 00:00:00 2001 From: "Joseph C. Sible" Date: Mon, 28 Dec 2020 18:04:32 -0500 Subject: [PATCH 12/14] Remove redundant bind and return --- src/ShellCheck/Parser.hs | 3 +-- 1 file changed, 1 insertion(+), 2 deletions(-) diff --git a/src/ShellCheck/Parser.hs b/src/ShellCheck/Parser.hs index 104e0a4..a17be91 100644 --- a/src/ShellCheck/Parser.hs +++ b/src/ShellCheck/Parser.hs @@ -209,8 +209,7 @@ startSpan = IncompleteInterval <$> getPosition endSpan (IncompleteInterval start) = do endPos <- getPosition - id <- getNextIdBetween start endPos - return id + getNextIdBetween start endPos getSpanPositionsFor m = do start <- getPosition From 953d9bc56dedba7a09829f2442204ae4b23074e1 Mon Sep 17 00:00:00 2001 From: "Joseph C. Sible" Date: Mon, 28 Dec 2020 18:05:55 -0500 Subject: [PATCH 13/14] Remove unused helper stub --- src/ShellCheck/Parser.hs | 4 ---- 1 file changed, 4 deletions(-) diff --git a/src/ShellCheck/Parser.hs b/src/ShellCheck/Parser.hs index a17be91..48d1cfa 100644 --- a/src/ShellCheck/Parser.hs +++ b/src/ShellCheck/Parser.hs @@ -2088,10 +2088,6 @@ readSimpleCommand = called "simple command" $ do then action else getParser def cmd rest - cStyleComment cmd = - case cmd of - _ -> False - validateCommand cmd = case cmd of (T_NormalWord _ [T_Literal _ "//"]) -> commentWarning (getId cmd) From 2cfd1f27140d15132a031ef71a715e522a40837b Mon Sep 17 00:00:00 2001 From: "Joseph C. Sible" Date: Mon, 28 Dec 2020 18:10:47 -0500 Subject: [PATCH 14/14] Fuse maps --- shellcheck.hs | 2 +- src/ShellCheck/Checks/Commands.hs | 2 +- 2 files changed, 2 insertions(+), 2 deletions(-) diff --git a/shellcheck.hs b/shellcheck.hs index f1757ef..d7e818d 100644 --- a/shellcheck.hs +++ b/shellcheck.hs @@ -507,7 +507,7 @@ ioInterface options files = do where find filename deflt = do sources <- findM ((allowable inputs) `andM` doesFileExist) $ - (adjustPath filename):(map ( filename) $ map adjustPath $ sourcePathFlag ++ sourcePathAnnotation) + (adjustPath filename):(map (( filename) . adjustPath) $ sourcePathFlag ++ sourcePathAnnotation) case sources of Nothing -> return deflt Just first -> return first diff --git a/src/ShellCheck/Checks/Commands.hs b/src/ShellCheck/Checks/Commands.hs index 771083e..5be5a9a 100644 --- a/src/ShellCheck/Checks/Commands.hs +++ b/src/ShellCheck/Checks/Commands.hs @@ -951,7 +951,7 @@ checkCatastrophicRm = CommandCheck (Basename "rm") $ \t -> when (isRecursive t) $ mapM_ (mapM_ checkWord . braceExpand) $ arguments t where - isRecursive = any (`elem` ["r", "R", "recursive"]) . map snd . getAllFlags + isRecursive = any ((`elem` ["r", "R", "recursive"]) . snd) . getAllFlags checkWord token = case getLiteralString token of