[GHC] #15595: Stack overflow in withArgs leads to infinite memory-consuming loop
GHC
ghc-devs at haskell.org
Mon Sep 3 11:50:07 UTC 2018
#15595: Stack overflow in withArgs leads to infinite memory-consuming loop
----------------------------------+--------------------------------------
Reporter: NeilMitchell | Owner: (none)
Type: bug | Status: new
Priority: normal | Milestone: 8.6.1
Component: Compiler | Version: 8.5
Resolution: | Keywords:
Operating System: Windows | Architecture: x86_64 (amd64)
Type of failure: Runtime crash | Test Case:
Blocked By: | Blocking:
Related Tickets: | Differential Rev(s):
Wiki Page: |
----------------------------------+--------------------------------------
Changes (by osa1):
* version: 8.4.3 => 8.5
Comment:
I did a little bit of debugging -- basically the RTS is throwing a stack
overflow exception, but the mutator is then trying to allocate more stack
space (maybe because stack overflow exception is somehow masked?), causing
a loop.
A different variant of this program exits with a stack overflow exception:
{{{#!haskell
{-# LANGUAGE ForeignFunctionInterface #-}
import Foreign.C.Types
import Foreign.C.String
import Foreign.C
import Foreign.Ptr
import GHC.Foreign (withCStringsLen)
foreign import ccall unsafe "setProgArgv"
c_setProgArgv :: CInt -> Ptr CString -> IO ()
main :: IO ()
main = do
putStrLn "Starting"
withCStringsLen utf8 (replicate 1000 "") $ \len css -> do
c_setProgArgv (fromIntegral len) css
}}}
Output:
{{{
$ ./Main +RTS -K1K
Starting
Main: Stack space overflow: current size 33624 bytes.
Main: Use `+RTS -Ksize -RTS' to increase it.
}}}
I don't know why the `withArgs` version doesn't fail with the same error
yet, but I think `Note [Throw to self when masked]` is relevant.
(Confirmed on GHC HEAD so updating the version)
--
Ticket URL: <http://ghc.haskell.org/trac/ghc/ticket/15595#comment:1>
GHC <http://www.haskell.org/ghc/>
The Glasgow Haskell Compiler
More information about the ghc-tickets
mailing list