Hello,

I have a strange (low level) problem with the Data.Text library.

Running the simple program below on a certain text file causes a low level
error.


 runghc ./ReadFiles.hs testfile
ghc(16402,0xb0103000) malloc: *** error for object 0x2501710: pointer being
freed was not allocated
*** set a breakpoint in malloc_error_break to debug
ghc(16402,0xb0103000) malloc: *** error for object 0x2501710: pointer being
freed was not allocated
*** set a breakpoint in malloc_error_break to debug
ReadFiles.hs: testfile: hGetContents: invalid argument (Illegal byte
sequence)


module Main where

import qualified Data.Text.IO as TI
import qualified Data.Text as T
import System


main = do
  args <- getArgs
  let fileName:_  = args
  txt <- TI.readFile fileName

  putStrLn $ show txt


Unfortunately I can 't post the specific data file.
But according to the file program it is a text file with :
 Non-ISO extended-ASCII text, with very long lines, with CRLF, LF line
terminators encoding.


How can I debug this problem ? What would you guys do ?  Trying gdb ?

 thanks in advance,

Pieter


-- 
Pieter Laeremans <pie...@laeremans.org>

"The future is here. It's just not evenly distributed yet."  W. Gibson
_______________________________________________
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe

Reply via email to