#2797: ghci stack overflows when ghc does not
---------------------------------+------------------------------------------
Reporter: TristanAllwood | Owner:
Type: bug | Status: new
Priority: normal | Component: GHCi
Version: 6.11 | Severity: normal
Keywords: | Testcase:
Architecture: Unknown/Multiple | Os: Unknown/Multiple
---------------------------------+------------------------------------------
Happens with today's HEAD and 6.10.1
I appreciate I am playing a little fast and loose by using
unsafePerformIO.
{{{
module Main where
import System.IO.Unsafe
main :: IO ()
main = do
bar [] 5000000 `seq` return ()
bar :: [()] -> Int -> Int
bar stk 0 = error $ show stk
bar stk n = stk `seq` bar (push stk) (n-1)
push :: [()] -> [()]
push stk = unsafePerformIO . return $ take 2 (():stk)
}}}
{{{
$ ~/ghc/ghc/ghc/stage2-inplace/ghc -O0 --make -o GT2 ghciTest2.hs
[1 of 1] Compiling Main ( ghciTest2.hs, ghciTest2.o )
Linking GT2.exe ...
[EMAIL PROTECTED] ~/ghc/ghc-Stack-Tests
$ ./GT2.exe +RTS -k0.01k -K0.01k
GT2.exe: [(),()]
[EMAIL PROTECTED] ~/ghc/ghc-Stack-Tests
$ rm *.o *.exe *.hi ; ~/ghc/ghc/ghc/stage2-inplace/ghc -e 'main'
ghciTest2.hs +RTS -K40M
Stack space overflow: current size 40000000 bytes.
Use `+RTS -Ksize' to increase it.
}}}
Using {{{-K400M}}} ghci does get there.
--
Ticket URL: <http://hackage.haskell.org/trac/ghc/ticket/2797>
GHC <http://www.haskell.org/ghc/>
The Glasgow Haskell Compiler_______________________________________________
Glasgow-haskell-bugs mailing list
[email protected]
http://www.haskell.org/mailman/listinfo/glasgow-haskell-bugs