Use list comprehensions instead of clunky combinations of map and filter

This commit is contained in:
Joseph C. Sible 2020-02-01 22:50:20 -05:00
parent f25b8bd03a
commit e6e89d68fd
2 changed files with 4 additions and 4 deletions

View File

@ -706,7 +706,7 @@ checkReadExpansions = CommandCheck (Exactly "read") check
options = getGnuOpts flagsForRead options = getGnuOpts flagsForRead
getVars cmd = fromMaybe [] $ do getVars cmd = fromMaybe [] $ do
opts <- options cmd opts <- options cmd
return . map snd $ filter (\(x,_) -> x == "" || x == "a") opts return [y | (x,y) <- opts, x == "" || x == "a"]
check cmd = mapM_ warning $ getVars cmd check cmd = mapM_ warning $ getVars cmd
warning t = potentially $ do warning t = potentially $ do
@ -995,7 +995,7 @@ missingDestination handler token = do
_ -> return () _ -> return ()
where where
args = getAllFlags token args = getAllFlags token
params = map fst $ filter (\(_,x) -> x == "") args params = [x | (x,"") <- args]
hasTarget = hasTarget =
any (\(_,x) -> x /= "" && x `isPrefixOf` "target-directory") args any (\(_,x) -> x /= "" && x `isPrefixOf` "target-directory") args
@ -1083,7 +1083,7 @@ checkSudoArgs = CommandCheck (Basename "sudo") f
where where
f t = potentially $ do f t = potentially $ do
opts <- parseOpts t opts <- parseOpts t
let nonFlags = map snd $ filter (\(flag, _) -> flag == "") opts let nonFlags = [x | ("",x) <- opts]
commandArg <- nonFlags !!! 0 commandArg <- nonFlags !!! 0
command <- getLiteralString commandArg command <- getLiteralString commandArg
guard $ command `elem` builtins guard $ command `elem` builtins

View File

@ -295,7 +295,7 @@ prop_pstreeSumsCorrectly kvs targets =
-- Trivial O(n * m) implementation -- Trivial O(n * m) implementation
dumbPrefixSums :: [(Int, Int)] -> [Int] -> [Int] dumbPrefixSums :: [(Int, Int)] -> [Int] -> [Int]
dumbPrefixSums kvs targets = dumbPrefixSums kvs targets =
let prefixSum target = sum . map snd . filter (\(k,v) -> k <= target) $ kvs let prefixSum target = sum [v | (k,v) <- kvs, k <= target]
in map prefixSum targets in map prefixSum targets
-- PSTree O(n * log m) implementation -- PSTree O(n * log m) implementation
smartPrefixSums :: [(Int, Int)] -> [Int] -> [Int] smartPrefixSums :: [(Int, Int)] -> [Int] -> [Int]