diff --git a/src/ShellCheck/Analytics.hs b/src/ShellCheck/Analytics.hs index e8bee4f..e33d873 100644 --- a/src/ShellCheck/Analytics.hs +++ b/src/ShellCheck/Analytics.hs @@ -1234,10 +1234,10 @@ checkLiteralBreakingTest _ t = potentially $ return () comparisonWarning list = do - token <- listToMaybe $ filter hasEquals list + token <- find hasEquals list return $ err (getId token) 2077 "You need spaces around the comparison operator." tautologyWarning t s = do - token <- listToMaybe $ filter isNonEmpty $ getWordParts t + token <- find isNonEmpty $ getWordParts t return $ err (getId token) 2157 s prop_checkConstantNullary = verify checkConstantNullary "[[ '$(foo)' ]]" @@ -2910,7 +2910,7 @@ checkLoopVariableReassignment params token = where check = do str <- loopVariable token - next <- listToMaybe $ filter (\x -> loopVariable x == Just str) path + next <- find (\x -> loopVariable x == Just str) path return $ do warn (getId token) 2165 "This nested loop overrides the index variable of its parent." warn (getId next) 2167 "This parent loop has its index variable overridden." diff --git a/src/ShellCheck/Checks/ShellSupport.hs b/src/ShellCheck/Checks/ShellSupport.hs index e340d41..742cfa5 100644 --- a/src/ShellCheck/Checks/ShellSupport.hs +++ b/src/ShellCheck/Checks/ShellSupport.hs @@ -340,8 +340,8 @@ checkBashisms = ForShell [Sh, Dash] $ \t -> do potentially $ do allowed' <- Map.lookup name allowedFlags allowed <- allowed' - (word, flag) <- listToMaybe $ - filter (\x -> (not . null . snd $ x) && snd x `notElem` allowed) flags + (word, flag) <- find + (\x -> (not . null . snd $ x) && snd x `notElem` allowed) flags return . warnMsg (getId word) $ name ++ " -" ++ flag ++ " is" when (name == "source") $ warnMsg id "'source' in place of '.' is" diff --git a/src/ShellCheck/Parser.hs b/src/ShellCheck/Parser.hs index 339b50b..f295560 100644 --- a/src/ShellCheck/Parser.hs +++ b/src/ShellCheck/Parser.hs @@ -34,7 +34,7 @@ import Control.Monad.Identity import Control.Monad.Trans import Data.Char import Data.Functor -import Data.List (isPrefixOf, isInfixOf, isSuffixOf, partition, sortBy, intercalate, nub) +import Data.List (isPrefixOf, isInfixOf, isSuffixOf, partition, sortBy, intercalate, nub, find) import Data.Maybe import Data.Monoid import Debug.Trace @@ -589,7 +589,7 @@ readConditionContents single = checkTrailingOp x = fromMaybe (return ()) $ do (T_Literal id str) <- getTrailingUnquotedLiteral x - trailingOp <- listToMaybe (filter (`isSuffixOf` str) binaryTestOps) + trailingOp <- find (`isSuffixOf` str) binaryTestOps return $ parseProblemAtId id ErrorC 1108 $ "You need a space before and after the " ++ trailingOp ++ " ."