What does unsafePerformIO do to the stack

Bernd Brassel bbr at informatik.uni-kiel.de
Fri Feb 1 07:39:13 EST 2008


Thanks for your answer Simon.

Simon Marlow wrote:
> Bernd Brassel wrote:
>> 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
> 
> goodStack == id, and GHC even with no optimisation will transform it
> into id, and inline it into sim.  So with goodStack, sim ends up being
> tail-recursive.  With badStack, sim is no longer tail recursive
> (unsafePerformIO is not inlined), so it runs out of stack.  Simple!

Is it really that simple? I guess that in a lazy language we have to
look a bit closer to see what is tail recursive and what is not. If I
understand you correctly, you say that if goodStack was not inlined you
would have a bad stack as well, right? But look at what it would be
doing. In a lazy language the call to sim would go to the heap and
whatever goodStack does to the stack is already done before sim is
restarted. And the same could be true with the unsafePerformIO-return
combination. What is the reason to hold anything on the stack for this
after the call to unsafe is finished?

I have tried the example with badStack in one other compiler and two
interpreters. None of them has any problem running the example. For one
of the interpreters I could exactly measure that the stack is constant
the whole time. And I know that no optimisation or inlining is going on
for that interpreter. Just try the example with hugs. It easily runs
through while replacing badStack with the function

pushStack True = True

immediately runs out of memory. (With this function, the example is
indeed not tail recursive and your argument is valid.)
So there is definitely something that unsafePerformIO does to the stack
in the ghc that is special to that compiler.




More information about the Glasgow-haskell-users mailing list