> 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.

Yes, I've run into this before.  In fact this is one of those tricky
problems where you can't quite get tail-recursion where you want it:
(pseudo-ish code follows)

   peekCString ptr = do
     x <- peek ptr 
     if x == '\0' then return [] else do
     xs <- peekCString (ptr + 1)
     return (x:xs)

Any ideas?  I seem to recall the ML folks have a hack for dealing with
this.

One ugly solution that occurs to me is:

   peekCString ptr = do
     x <- peek ptr 
    if x == '\0' then return [] else do
    return (x : unsafePerformIO (peekCString (ptr + 1))

and then do a deepSeq before returning the list (deepSeq is
tail-recursive).  I'm sure there must be a cleverer solution - it has
that kind of smell about it.

Cheers,
        Simon

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

Reply via email to