Use find instead of listToMaybe and filter

This commit is contained in:
Joseph C. Sible 2020-02-01 22:50:16 -05:00
parent 0f48bb78a5
commit f5c6771016
3 changed files with 7 additions and 7 deletions

View File

@ -1234,10 +1234,10 @@ checkLiteralBreakingTest _ t = potentially $
return () return ()
comparisonWarning list = do comparisonWarning list = do
token <- listToMaybe $ filter hasEquals list token <- find hasEquals list
return $ err (getId token) 2077 "You need spaces around the comparison operator." return $ err (getId token) 2077 "You need spaces around the comparison operator."
tautologyWarning t s = do tautologyWarning t s = do
token <- listToMaybe $ filter isNonEmpty $ getWordParts t token <- find isNonEmpty $ getWordParts t
return $ err (getId token) 2157 s return $ err (getId token) 2157 s
prop_checkConstantNullary = verify checkConstantNullary "[[ '$(foo)' ]]" prop_checkConstantNullary = verify checkConstantNullary "[[ '$(foo)' ]]"
@ -2910,7 +2910,7 @@ checkLoopVariableReassignment params token =
where where
check = do check = do
str <- loopVariable token str <- loopVariable token
next <- listToMaybe $ filter (\x -> loopVariable x == Just str) path next <- find (\x -> loopVariable x == Just str) path
return $ do return $ do
warn (getId token) 2165 "This nested loop overrides the index variable of its parent." 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." warn (getId next) 2167 "This parent loop has its index variable overridden."

View File

@ -340,8 +340,8 @@ checkBashisms = ForShell [Sh, Dash] $ \t -> do
potentially $ do potentially $ do
allowed' <- Map.lookup name allowedFlags allowed' <- Map.lookup name allowedFlags
allowed <- allowed' allowed <- allowed'
(word, flag) <- listToMaybe $ (word, flag) <- find
filter (\x -> (not . null . snd $ x) && snd x `notElem` allowed) flags (\x -> (not . null . snd $ x) && snd x `notElem` allowed) flags
return . warnMsg (getId word) $ name ++ " -" ++ flag ++ " is" return . warnMsg (getId word) $ name ++ " -" ++ flag ++ " is"
when (name == "source") $ warnMsg id "'source' in place of '.' is" when (name == "source") $ warnMsg id "'source' in place of '.' is"

View File

@ -34,7 +34,7 @@ import Control.Monad.Identity
import Control.Monad.Trans import Control.Monad.Trans
import Data.Char import Data.Char
import Data.Functor 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.Maybe
import Data.Monoid import Data.Monoid
import Debug.Trace import Debug.Trace
@ -589,7 +589,7 @@ readConditionContents single =
checkTrailingOp x = fromMaybe (return ()) $ do checkTrailingOp x = fromMaybe (return ()) $ do
(T_Literal id str) <- getTrailingUnquotedLiteral x (T_Literal id str) <- getTrailingUnquotedLiteral x
trailingOp <- listToMaybe (filter (`isSuffixOf` str) binaryTestOps) trailingOp <- find (`isSuffixOf` str) binaryTestOps
return $ parseProblemAtId id ErrorC 1108 $ return $ parseProblemAtId id ErrorC 1108 $
"You need a space before and after the " ++ trailingOp ++ " ." "You need a space before and after the " ++ trailingOp ++ " ."