Hurr durr -- I was wondering why the left-fold numbers looked so slow,
then after looking at memory profiles I realized I forgot to add
strictness to the enumerator/iteratee benchmarks. Here are the
corrected numbers (with benchmarks attached):

enumerator
====================
5.414 / 2.090 / 0.360
5.415 / 1.950 / 0.320
5.429 / 2.010 / 0.360

iteratee
====================
5.447 / 1.620 / 0.470
5.389 / 2.030 / 0.300
5.457 / 1.960 / 0.390
module Main (main) where
import Data.Enumerator
import Data.Enumerator.IO
import qualified Data.ByteString as B
import qualified Data.ByteString.Char8 as B8
import System.IO
import System.Environment

iterLines :: Monad m => Iteratee e B.ByteString m Integer
iterLines = continue (step 0) where
	step acc EOF = yield acc EOF
	step acc (Chunks xs) = continue $ step $! foldl foldStep acc xs
	foldStep acc bytes = acc + countChar '\n' bytes

countChar :: Char -> B.ByteString -> Integer
countChar c = B8.foldl (\acc c' -> if c' == c then acc + 1 else acc) 0

main :: IO ()
main = do
	filename:_ <- getArgs
	h <- openBinaryFile filename ReadMode
	run (iterLines >>== enumHandle 4096 h) >>= print
module Main (main) where
import Data.Iteratee
import Data.Iteratee.IO
import Data.Iteratee.WrappedByteString
import Data.Word (Word8)
import qualified Data.ByteString as B
import qualified Data.ByteString.Char8 as B8
import System.IO
import System.Environment

iterLines :: Monad m => IterateeG WrappedByteString Word8 m Integer
iterLines = IterateeG (step 0) where
	step acc s@(EOF _) = return $ Done acc s
	step acc (Chunk wrapped) = return $ Cont (IterateeG (step $! acc')) Nothing where
		acc' = acc + countChar '\n' (unWrap wrapped)

countChar :: Char -> B.ByteString -> Integer
countChar c = B8.foldl (\acc c' -> if c' == c then acc + 1 else acc) 0

main :: IO ()
main = do
	filename:_ <- getArgs
	h <- openBinaryFile filename ReadMode
	enumHandle h iterLines >>= run >>= print
import qualified Data.ByteString.Lazy as B
import qualified Data.ByteString.Lazy.Char8 as B8
import System.IO
import System.Environment

countChar :: Char -> B.ByteString -> Integer
countChar c = B8.foldl' (\acc c' -> if c' == c then acc + 1 else acc) 0

countHandle :: Handle -> IO Integer
countHandle h = fmap (countChar '\n') (B.hGetContents h)

main :: IO ()
main = do
	filename:_ <- getArgs
	h <- openBinaryFile filename ReadMode
	countHandle h >>= print
import qualified Data.ByteString as B
import qualified Data.ByteString.Char8 as B8
import System.IO
import System.Environment

countChar :: Char -> B.ByteString -> Integer
countChar c = B8.foldl' (\acc c' -> if c' == c then acc + 1 else acc) 0

countHandle :: Handle -> IO Integer
countHandle h = loop 0 where
	loop acc = do
		bytes <- B.hGet h 4096
		if B.null bytes
			then return acc
			else let acc' = acc + countChar '\n' bytes in loop $! acc'

main :: IO ()
main = do
	filename:_ <- getArgs
	h <- openBinaryFile filename ReadMode
	countHandle h >>= print
_______________________________________________
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe

Reply via email to