#4845: internal error: threadStackUnderflow: not enough space for return values
---------------------------------+------------------------------------------
Reporter: igloo | Owner: simonmar
Type: bug | Status: new
Priority: highest | Milestone: 7.2.1
Component: Runtime System | Version: 7.1
Keywords: | Testcase:
Blockedby: | Difficulty:
Os: Unknown/Multiple | Blocking:
Architecture: Unknown/Multiple | Failure: None/Unknown
---------------------------------+------------------------------------------
With (the type-incorrect) `Foo.hs`:
{{{
module Foo where
import Data.Char
import System.Directory
main :: IO ()
main = do return ()
return ()
return ()
return ()
return ()
return ()
return ()
return ()
return ()
let xs :: [(Int, Bool, Char, Char, Char)]
xs = undefined
mapM_ f xs
return ()
return ()
f :: (Int, Char, Char, Char) -> IO ()
f _ = return ()
f1 :: IO ()
f1 = return ()
f2 :: IO ()
f2 = return ()
f3 :: IO ()
f3 = return ()
f4 :: IO ()
f4 = return ()
}}}
I get:
{{{
$ ghci Foo.hs
GHCi, version 7.1.20101216: http://www.haskell.org/ghc/ :? for help
Loading package ghc-prim ... linking ... done.
Loading package integer-gmp ... linking ... done.
Loading package base ... linking ... done.
Loading package ffi-1.0 ... linking ... done.
[1 of 1] Compiling Foo ( Foo.hs, interpreted )
ghc-stage2: internal error: threadStackUnderflow: not enough space for
return values
(GHC version 7.1.20101216 for x86_64_unknown_linux)
Please report this as a GHC bug:
http://www.haskell.org/ghc/reportabug
}}}
--
Ticket URL: <http://hackage.haskell.org/trac/ghc/ticket/4845>
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