[Haskell-cafe] A problem with bytestring 0.9.1.4 "hGetBuf: invalid argument"

Don Stewart dons at galois.com
Tue Aug 4 22:06:49 EDT 2009


haskellmail:
> Hi all,
> 
> I've recently came across a problem when processing a large text file (around
> 2G in size).
> 
> I wrote a Haskell program to count the number of lines in the file.
> 
> 
> module Main where
> 
> import System
> import qualified Data.ByteString.Char8 as S
> -- import Prelude as S
> 
> main :: IO ()
> main = do { args <- getArgs
>           ; case args of
>               { [ filename ] ->
>                     do { content <- S.readFile filename
>                        ; let lns = S.lines content
>                        ; putStrLn (show $ length lns)
>                        }
>               ; _ -> error "Usage : Wc <file>"
>               }
>           }
>                    
> 
> I get this error, if I use the ByteString module,
> ./Wc a.out
> Wc: {handle: a.out}: hGetBuf: invalid argument (illegal buffer size
> (-1909953139))
> Otherwise, it returns me the result.
> 
> Another observation is that if I reduce the size of the file, the ByteString
> version works too.
> 
> Is it a known limitation?
> 

Yes, you need to use Data.ByteString.Lazy.Char8 to process files larger
than this on a 32 bit machine (you'll have more space on a 64 bit
machine). 

-- Don


More information about the Haskell-Cafe mailing list