
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 this behaviour necessary? Is there any work around, e.g., employing the foreign function interface?
There's unsafeInlinePerformIO (sometimes called inlinePerformIO), which is usable in certain cases, but be very careful. From Data.ByteString.Internal: {-# INLINE inlinePerformIO #-} inlinePerformIO :: IO a -> a #if defined(__GLASGOW_HASKELL__) inlinePerformIO (IO m) = case m realWorld# of (# _, r #) -> r #else inlinePerformIO = unsafePerformIO #endif But even this might not give you tail recursion, depending on the context. Cheers, Simon