@@ -417,7 +417,7 @@ prop_checkAssignAteCommand4 = verifyNot checkAssignAteCommand "A=foo ls -l"
417
417
prop_checkAssignAteCommand5 = verify checkAssignAteCommand " PAGER=cat grep bar"
418
418
prop_checkAssignAteCommand6 = verifyNot checkAssignAteCommand " PAGER=\" cat\" grep bar"
419
419
prop_checkAssignAteCommand7 = verify checkAssignAteCommand " here=pwd"
420
- checkAssignAteCommand _ (T_SimpleCommand id ( T_Assignment _ _ _ _ assignmentTerm: [] ) list) =
420
+ checkAssignAteCommand _ (T_SimpleCommand id [ T_Assignment _ _ _ _ assignmentTerm] list) =
421
421
-- Check if first word is intended as an argument (flag or glob).
422
422
if firstWordIsArg list
423
423
then
@@ -449,7 +449,7 @@ checkArithmeticOpCommand _ _ = return ()
449
449
450
450
prop_checkWrongArit = verify checkWrongArithmeticAssignment " i=i+1"
451
451
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] [] ) =
453
453
sequence_ $ do
454
454
str <- getNormalString val
455
455
match <- matchRegex regex str
@@ -2518,7 +2518,7 @@ checkCharRangeGlob p t@(T_Glob id str) |
2518
2518
where
2519
2519
isCharClass str = " [" `isPrefixOf` str && " ]" `isSuffixOf` str
2520
2520
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
2522
2522
dropNegation s =
2523
2523
case s of
2524
2524
' !' : rest -> rest
@@ -2881,7 +2881,7 @@ checkTestArgumentSplitting params t =
2881
2881
then
2882
2882
-- Ksh appears to stop processing after unrecognized tokens, so operators
2883
2883
-- will effectively work with globs, but only the first match.
2884
- when (op `elem` [' -' : c : [ ] | c <- " bcdfgkprsuwxLhNOGRS" ]) $
2884
+ when (op `elem` [[ ' -' , c ] | c <- " bcdfgkprsuwxLhNOGRS" ]) $
2885
2885
warn (getId token) 2245 $
2886
2886
op ++ " only applies to the first expansion of this glob. Use a loop to check any/all."
2887
2887
else
@@ -3408,7 +3408,7 @@ checkPipeToNowhere params t =
3408
3408
3409
3409
sequence_ $ do
3410
3410
T_Redirecting _ redirs cmd <- return stage
3411
- fds <- sequence $ map getRedirectionFds redirs
3411
+ fds <- mapM getRedirectionFds redirs
3412
3412
3413
3413
let fdAndToken :: [(Integer , Token )]
3414
3414
fdAndToken =
@@ -3441,7 +3441,7 @@ checkPipeToNowhere params t =
3441
3441
3442
3442
commandSpecificException name cmd =
3443
3443
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
3445
3445
_ -> False
3446
3446
3447
3447
warnAboutDupes (n, list@ (_: _: _)) =
@@ -3845,7 +3845,7 @@ checkAliasUsedInSameParsingUnit params root =
3845
3845
-- Group them by whether they start on the same line where the previous one ended
3846
3846
units = groupByLink followsOnLine commands
3847
3847
in
3848
- execWriter $ sequence_ $ map checkUnit units
3848
+ execWriter $ mapM_ checkUnit units
3849
3849
where
3850
3850
lineSpan t =
3851
3851
let m = tokenPositions params in do
@@ -3895,13 +3895,13 @@ groupByLink :: (a -> a -> Bool) -> [a] -> [[a]]
3895
3895
groupByLink f list =
3896
3896
case list of
3897
3897
[] -> []
3898
- (x: xs) -> g x [] xs
3898
+ (x: xs) -> foldr c n xs x []
3899
3899
where
3900
- g current span (next : rest) =
3900
+ c next rest current span =
3901
3901
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 )]
3905
3905
3906
3906
3907
3907
prop_checkBlatantRecursion1 = verify checkBlatantRecursion " :(){ :|:& };:"
0 commit comments