Consider the following program:

module Stack where

import System.IO.Unsafe

main = print (sim (replicate 1299959 ()))

sim []     = True
sim (_:xs) = goodStack (sim xs)

goodStack x = fromJust (Just x)          --no stack overflow
badStack  x = unsafePerformIO (return x) --stack overflow

fromJust (Just x) = x

I always thought that unsafePerformIO would do something similar as
goodStack. i.e. be stack neutral:

$ ghc --make -o stack Stack
[1 of 1] Compiling Main             ( Stack.hs, Stack.o )
Linking stack ...
$ stack +RTS -K0.00001M
True

But if you exchange goodStack with badStack, the picture changes
unfortunately to:

$ ghc --make -o stack Stack
[1 of 1] Compiling Main             ( Stack.hs, Stack.o )
Linking stack ...
$ stack +RTS -K9.883647M
Stack space overflow: current size 9883644 bytes.
Use `+RTS -Ksize' to increase it.
$ stack +RTS -K9.883648M
True

I am using:
$ ghc --version
The Glorious Glasgow Haskell Compilation System, version 6.8.2

Is this behaviour necessary? Is there any work around, e.g., employing
the foreign function interface?

Thanks for your time!
Bernd
_______________________________________________
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users

Reply via email to