The following program gives me a stack overflow for a file "big.tex"
150000 bytes long.

-- Cut here --
module Main where

import Foreign.C.String
import Foreign.Ptr
import qualified GHC.IO

main =
   do
      (ptr,len) <- GHC.IO.slurpFile "big.tex"
      peekCStringLen (castPtr ptr,len)
      return ()
-- Cut here --

The message is "Stack space overflow: current size 1048576 bytes."

Could peekCStringLen be changed so it does not expect stack space
proportionate to the input string?  I use this method quite a lot
for slurping strings in and out, so as it is the situation is
inconvenient.




_______________________________________________ Glasgow-haskell-bugs mailing list [EMAIL PROTECTED] http://www.haskell.org/mailman/listinfo/glasgow-haskell-bugs

Reply via email to