[Haskell-cafe] An Extra Empty Line
Hong Yang
hyangfji at gmail.com
Tue Sep 10 05:00:26 CEST 2013
Hi Dear Haskellers,
I have this small program to grep recursively in parallel. It works fine,
but generates the last line empty. Is this empty line coming from
mapConcurrently()?
Thanks,
Hong
-- mygrepr.hs
-- lrf.pl is an old Perl script to get all non-duplicate files recursively
under the current directory, since some of directories have tons of links
-- the program runs concurrently on either specified number of threads or
3/4 of the number of available cores
module Main (main) where
import Control.Concurrent.Async
import Control.Monad
import Data.List
import Data.List.Split
import GHC.Conc
import System.Environment ( getArgs )
import System.Exit
import System.Process
import Text.Regex.Posix
main :: IO ()
main = do
hs_argv <- getArgs
if null hs_argv || any (=~ "-h") hs_argv || any (=~ "--h") hs_argv then
putStrLn "mygrepr [+RTS -N[x] -RTS] [OPTION]... PATTERN"
else do
numCores <- getNumProcessors
numCapas <- getNumCapabilities
let numT | numCapas > 1 = numCapas
| otherwise = max numCapas (numCores `div` 4 *
3)
_ <- setNumCapabilities numT
let numThreads = fromIntegral numT :: Double
findResult <- readProcess "lrf.pl" [] []
let files = lines findResult
let num_of_files = fromIntegral $ length files :: Double
let chunks = chunksOf (ceiling (num_of_files/numThreads)) files
results <- mapConcurrently (grep hs_argv) chunks
let (_, grepResult, _) = unzip3 results
putStr $ unlines $ nub $ filter (\line -> not (line =~ "Binary file
.* matches")) $ lines (concat grepResult)
grep :: [String] -> [String] -> IO (ExitCode, String, String)
grep hs_argv files = readProcessWithExitCode
"/tool/pandora64/.package/grep-2.5.4/bin/grep" (hs_argv ++ files) []
-------------- next part --------------
An HTML attachment was scrubbed...
URL: <http://www.haskell.org/pipermail/haskell-cafe/attachments/20130909/d49c6dd7/attachment.htm>
More information about the Haskell-Cafe
mailing list