[Haskell-cafe] Streaming bytes and performance
Konstantin Litvinenko
to.darkangel at gmail.com
Mon Mar 18 09:53:13 CET 2013
Hi All!
I tune my toy project for performance and hit the wall on simple, in
imperative world, task. Here is the code that model what I'm trying to
achieve
import qualified Data.ByteString.Lazy as L
import Data.Word8(isSpace)
import Data.Word
import Control.Monad.State
type Stream = State L.ByteString
get_byte :: Stream (Maybe Word8)
get_byte = do
s <- get
case L.uncons s of
Nothing -> return Nothing
Just (x, xs) -> put xs >> return (Just x)
main = do
f <- L.readFile "test.txt"
let r = evalState count_spaces f
print r
where
count_spaces = go 0
where
go a = do
x <- get_byte
case x of
Just x' -> if isSpace x' then go (a + 1) else go a
Nothing -> return a
It takes the file and count spaces, in imperative way, consuming bytes
one by one. The problem is: How to rewrite this to get rid of constant
allocation of state but still working with stream of bytes? I can
rewrite this as one-liner L.foldl, but that doesn't help me in any way
to optimize my toy project where all algorithms build upon consuming
stream of bytes.
PS. My main lang is C++ over 10 years and I only learn Haskell :)
More information about the Haskell-Cafe
mailing list