Skip to content

Commit 15ff87c

Browse files
authored
Merge pull request koalaman#2119 from josephcsible/refactors
Various refactorings
2 parents dff8f94 + 2cfd1f2 commit 15ff87c

File tree

6 files changed

+28
-35
lines changed

6 files changed

+28
-35
lines changed

shellcheck.hs

+1-1
Original file line numberDiff line numberDiff line change
@@ -507,7 +507,7 @@ ioInterface options files = do
507507
where
508508
find filename deflt = do
509509
sources <- findM ((allowable inputs) `andM` doesFileExist) $
510-
(adjustPath filename):(map (</> filename) $ map adjustPath $ sourcePathFlag ++ sourcePathAnnotation)
510+
(adjustPath filename):(map ((</> filename) . adjustPath) $ sourcePathFlag ++ sourcePathAnnotation)
511511
case sources of
512512
Nothing -> return deflt
513513
Just first -> return first

src/ShellCheck/ASTLib.hs

+2-2
Original file line numberDiff line numberDiff line change
@@ -178,7 +178,7 @@ getOpts (gnu, arbitraryLongOpts) string longopts args = process args
178178
process [] = return []
179179
process (token:rest) = do
180180
case getLiteralStringDef "\0" token of
181-
'-':'-':[] -> return $ listToArgs rest
181+
"--" -> return $ listToArgs rest
182182
'-':'-':word -> do
183183
let (name, arg) = span (/= '=') word
184184
needsArg <-
@@ -466,7 +466,7 @@ getCommandNameAndToken direct t = fromMaybe (Nothing, t) $ do
466466
"run" -> firstArg -- Used by bats
467467
"exec" -> do
468468
opts <- getBsdOpts "cla:" args
469-
(_, (t, _)) <- listToMaybe $ filter (null . fst) opts
469+
(_, (t, _)) <- find (null . fst) opts
470470
return t
471471
_ -> fail ""
472472

src/ShellCheck/Analytics.hs

+12-12
Original file line numberDiff line numberDiff line change
@@ -417,7 +417,7 @@ prop_checkAssignAteCommand4 = verifyNot checkAssignAteCommand "A=foo ls -l"
417417
prop_checkAssignAteCommand5 = verify checkAssignAteCommand "PAGER=cat grep bar"
418418
prop_checkAssignAteCommand6 = verifyNot checkAssignAteCommand "PAGER=\"cat\" grep bar"
419419
prop_checkAssignAteCommand7 = verify checkAssignAteCommand "here=pwd"
420-
checkAssignAteCommand _ (T_SimpleCommand id (T_Assignment _ _ _ _ assignmentTerm:[]) list) =
420+
checkAssignAteCommand _ (T_SimpleCommand id [T_Assignment _ _ _ _ assignmentTerm] list) =
421421
-- Check if first word is intended as an argument (flag or glob).
422422
if firstWordIsArg list
423423
then
@@ -449,7 +449,7 @@ checkArithmeticOpCommand _ _ = return ()
449449

450450
prop_checkWrongArit = verify checkWrongArithmeticAssignment "i=i+1"
451451
prop_checkWrongArit2 = verify checkWrongArithmeticAssignment "n=2; i=n*2"
452-
checkWrongArithmeticAssignment params (T_SimpleCommand id (T_Assignment _ _ _ _ val:[]) []) =
452+
checkWrongArithmeticAssignment params (T_SimpleCommand id [T_Assignment _ _ _ _ val] []) =
453453
sequence_ $ do
454454
str <- getNormalString val
455455
match <- matchRegex regex str
@@ -2518,7 +2518,7 @@ checkCharRangeGlob p t@(T_Glob id str) |
25182518
where
25192519
isCharClass str = "[" `isPrefixOf` str && "]" `isSuffixOf` str
25202520
contents = dropNegation . drop 1 . take (length str - 1) $ str
2521-
hasDupes = any (>1) . map length . group . sort . filter (/= '-') $ contents
2521+
hasDupes = any ((>1) . length) . group . sort . filter (/= '-') $ contents
25222522
dropNegation s =
25232523
case s of
25242524
'!':rest -> rest
@@ -2881,7 +2881,7 @@ checkTestArgumentSplitting params t =
28812881
then
28822882
-- Ksh appears to stop processing after unrecognized tokens, so operators
28832883
-- will effectively work with globs, but only the first match.
2884-
when (op `elem` ['-':c:[] | c <- "bcdfgkprsuwxLhNOGRS" ]) $
2884+
when (op `elem` [['-', c] | c <- "bcdfgkprsuwxLhNOGRS" ]) $
28852885
warn (getId token) 2245 $
28862886
op ++ " only applies to the first expansion of this glob. Use a loop to check any/all."
28872887
else
@@ -3408,7 +3408,7 @@ checkPipeToNowhere params t =
34083408

34093409
sequence_ $ do
34103410
T_Redirecting _ redirs cmd <- return stage
3411-
fds <- sequence $ map getRedirectionFds redirs
3411+
fds <- mapM getRedirectionFds redirs
34123412

34133413
let fdAndToken :: [(Integer, Token)]
34143414
fdAndToken =
@@ -3441,7 +3441,7 @@ checkPipeToNowhere params t =
34413441

34423442
commandSpecificException name cmd =
34433443
case name of
3444-
"du" -> any (`elem` ["exclude-from", "files0-from"]) $ map snd $ getAllFlags cmd
3444+
"du" -> any ((`elem` ["exclude-from", "files0-from"]) . snd) $ getAllFlags cmd
34453445
_ -> False
34463446

34473447
warnAboutDupes (n, list@(_:_:_)) =
@@ -3845,7 +3845,7 @@ checkAliasUsedInSameParsingUnit params root =
38453845
-- Group them by whether they start on the same line where the previous one ended
38463846
units = groupByLink followsOnLine commands
38473847
in
3848-
execWriter $ sequence_ $ map checkUnit units
3848+
execWriter $ mapM_ checkUnit units
38493849
where
38503850
lineSpan t =
38513851
let m = tokenPositions params in do
@@ -3895,13 +3895,13 @@ groupByLink :: (a -> a -> Bool) -> [a] -> [[a]]
38953895
groupByLink f list =
38963896
case list of
38973897
[] -> []
3898-
(x:xs) -> g x [] xs
3898+
(x:xs) -> foldr c n xs x []
38993899
where
3900-
g current span (next:rest) =
3900+
c next rest current span =
39013901
if f current next
3902-
then g next (current:span) rest
3903-
else (reverse $ current:span) : g next [] rest
3904-
g current span [] = [reverse (current:span)]
3902+
then rest next (current:span)
3903+
else (reverse $ current:span) : rest next []
3904+
n current span = [reverse (current:span)]
39053905

39063906

39073907
prop_checkBlatantRecursion1 = verify checkBlatantRecursion ":(){ :|:& };:"

src/ShellCheck/AnalyzerLib.hs

+7-9
Original file line numberDiff line numberDiff line change
@@ -258,9 +258,9 @@ determineShell fallbackShell t = fromMaybe Bash $
258258
executableFromShebang :: String -> String
259259
executableFromShebang = shellFor
260260
where
261-
shellFor s | "/env " `isInfixOf` s = fromMaybe "" $ do
262-
[flag, shell] <- matchRegex re s
263-
return shell
261+
shellFor s | "/env " `isInfixOf` s = case matchRegex re s of
262+
Just [flag, shell] -> shell
263+
_ -> ""
264264
shellFor s | ' ' `elem` s = shellFor $ takeWhile (/= ' ') s
265265
shellFor s = reverse . takeWhile (/= '/') . reverse $ s
266266
re = mkRegex "/env +(-S|--split-string=?)? *([^ ]*)"
@@ -270,7 +270,7 @@ executableFromShebang = shellFor
270270
-- This is used to populate parentMap in Parameters
271271
getParentTree :: Token -> Map.Map Id Token
272272
getParentTree t =
273-
snd . snd $ runState (doStackAnalysis pre post t) ([], Map.empty)
273+
snd $ execState (doStackAnalysis pre post t) ([], Map.empty)
274274
where
275275
pre t = modify (first ((:) t))
276276
post t = do
@@ -687,12 +687,10 @@ getModifiedVariableCommand base@(T_SimpleCommand id cmdPrefix (T_NormalWord _ (T
687687
parseArgs :: Maybe (Token, Token, String, DataType)
688688
parseArgs = do
689689
args <- getGnuOpts "d:n:O:s:u:C:c:t" rest
690-
let names = map snd $ filter (\(x,y) -> null x) args
691-
if null names
692-
then
690+
case [y | ("",(_,y)) <- args] of
691+
[] ->
693692
return (base, base, "MAPFILE", DataArray SourceExternal)
694-
else do
695-
(_, first) <- listToMaybe names
693+
first:_ -> do
696694
name <- getLiteralString first
697695
guard $ isVariableName name
698696
return (base, first, name, DataArray SourceExternal)

src/ShellCheck/Checks/Commands.hs

+3-3
Original file line numberDiff line numberDiff line change
@@ -122,7 +122,7 @@ checkGetOpts str flags args f =
122122
toTokens = map (T_Literal (Id 0)) . words
123123
opts = fromMaybe [] $ f (toTokens str)
124124
actualFlags = filter (not . null) $ map fst opts
125-
actualArgs = map (\(_, (_, x)) -> onlyLiteralString x) $ filter (null . fst) opts
125+
actualArgs = [onlyLiteralString x | ("", (_, x)) <- opts]
126126

127127
-- Short options
128128
prop_checkGetOptsS1 = checkGetOpts "-f x" ["f"] [] $ getOpts (True, True) "f:" []
@@ -916,7 +916,7 @@ checkWhileGetoptsCase = CommandCheck (Exactly "getopts") f
916916

917917
fromGlob t =
918918
case t of
919-
T_Glob _ ('[':c:']':[]) -> return [c]
919+
T_Glob _ ['[', c, ']'] -> return [c]
920920
T_Glob _ "*" -> return "*"
921921
T_Glob _ "?" -> return "?"
922922
_ -> Nothing
@@ -951,7 +951,7 @@ checkCatastrophicRm = CommandCheck (Basename "rm") $ \t ->
951951
when (isRecursive t) $
952952
mapM_ (mapM_ checkWord . braceExpand) $ arguments t
953953
where
954-
isRecursive = any (`elem` ["r", "R", "recursive"]) . map snd . getAllFlags
954+
isRecursive = any ((`elem` ["r", "R", "recursive"]) . snd) . getAllFlags
955955

956956
checkWord token =
957957
case getLiteralString token of

src/ShellCheck/Parser.hs

+3-8
Original file line numberDiff line numberDiff line change
@@ -211,8 +211,7 @@ startSpan = IncompleteInterval <$> getPosition
211211

212212
endSpan (IncompleteInterval start) = do
213213
endPos <- getPosition
214-
id <- getNextIdBetween start endPos
215-
return id
214+
getNextIdBetween start endPos
216215

217216
getSpanPositionsFor m = do
218217
start <- getPosition
@@ -394,7 +393,7 @@ unexpecting s p = try $
394393

395394
notFollowedBy2 = unexpecting ""
396395

397-
isFollowedBy p = (lookAhead . try $ p *> return True) <|> return False
396+
isFollowedBy p = (lookAhead . try $ p $> True) <|> return False
398397

399398
reluctantlyTill p end =
400399
(lookAhead (void (try end) <|> eof) >> return []) <|> do
@@ -2095,10 +2094,6 @@ readSimpleCommand = called "simple command" $ do
20952094
then action
20962095
else getParser def cmd rest
20972096

2098-
cStyleComment cmd =
2099-
case cmd of
2100-
_ -> False
2101-
21022097
validateCommand cmd =
21032098
case cmd of
21042099
(T_NormalWord _ [T_Literal _ "//"]) -> commentWarning (getId cmd)
@@ -2721,7 +2716,7 @@ readConditionCommand = do
27212716

27222717
pos <- getPosition
27232718
hasDashAo <- isFollowedBy $ do
2724-
c <- choice $ map (\s -> try $ string s) ["-o", "-a", "or", "and"]
2719+
c <- choice $ try . string <$> ["-o", "-a", "or", "and"]
27252720
posEnd <- getPosition
27262721
parseProblemAtWithEnd pos posEnd ErrorC 1139 $
27272722
"Use " ++ alt c ++ " instead of '" ++ c ++ "' between test commands."

0 commit comments

Comments
 (0)