mirror of
				https://github.com/koalaman/shellcheck.git
				synced 2025-11-04 18:28:23 +08:00 
			
		
		
		
	Use list comprehensions instead of clunky combinations of map and filter
This commit is contained in:
		@@ -706,7 +706,7 @@ checkReadExpansions = CommandCheck (Exactly "read") check
 | 
			
		||||
    options = getGnuOpts flagsForRead
 | 
			
		||||
    getVars cmd = fromMaybe [] $ do
 | 
			
		||||
        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
 | 
			
		||||
    warning t = potentially $ do
 | 
			
		||||
@@ -995,7 +995,7 @@ missingDestination handler token = do
 | 
			
		||||
        _ -> return ()
 | 
			
		||||
  where
 | 
			
		||||
    args = getAllFlags token
 | 
			
		||||
    params = map fst $ filter (\(_,x) -> x == "") args
 | 
			
		||||
    params = [x | (x,"") <- args]
 | 
			
		||||
    hasTarget =
 | 
			
		||||
        any (\(_,x) -> x /= "" && x `isPrefixOf` "target-directory") args
 | 
			
		||||
 | 
			
		||||
@@ -1083,7 +1083,7 @@ checkSudoArgs = CommandCheck (Basename "sudo") f
 | 
			
		||||
  where
 | 
			
		||||
    f t = potentially $ do
 | 
			
		||||
        opts <- parseOpts t
 | 
			
		||||
        let nonFlags = map snd $ filter (\(flag, _) -> flag == "") opts
 | 
			
		||||
        let nonFlags = [x | ("",x) <- opts]
 | 
			
		||||
        commandArg <- nonFlags !!! 0
 | 
			
		||||
        command <- getLiteralString commandArg
 | 
			
		||||
        guard $ command `elem` builtins
 | 
			
		||||
 
 | 
			
		||||
@@ -295,7 +295,7 @@ prop_pstreeSumsCorrectly kvs targets =
 | 
			
		||||
    -- Trivial O(n * m) implementation
 | 
			
		||||
    dumbPrefixSums :: [(Int, Int)] -> [Int] -> [Int]
 | 
			
		||||
    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
 | 
			
		||||
    -- PSTree O(n * log m) implementation
 | 
			
		||||
    smartPrefixSums :: [(Int, Int)] -> [Int] -> [Int]
 | 
			
		||||
 
 | 
			
		||||
		Reference in New Issue
	
	Block a user