[GHC] #15595: Stack overflow in withArgs leads to infinite memory-consuming loop
GHC
ghc-devs at haskell.org
Mon Sep 3 11:54:29 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: |
----------------------------------+--------------------------------------
Comment (by osa1):
Right, so this is because the thread is in masked state and stack overflow
exception is not actually raised because of this. If I change the program
above to this:
{{{#!haskell
{-# LANGUAGE ForeignFunctionInterface #-}
import Foreign.C
import Foreign.Ptr
import GHC.Foreign (withCStringsLen)
import GHC.IO.Encoding (utf8)
import Control.Exception (mask_)
foreign import ccall unsafe "setProgArgv"
c_setProgArgv :: CInt -> Ptr CString -> IO ()
main :: IO ()
main = do
putStrLn "Starting"
mask_ $
withCStringsLen utf8 (replicate 1000 "") $ \len css -> do
c_setProgArgv (fromIntegral len) css
putStrLn "Done"
}}}
(only difference is that I added a `mask_`) this also loops.
Not sure about what's the right thing to do here ...
--
Ticket URL: <http://ghc.haskell.org/trac/ghc/ticket/15595#comment:2>
GHC <http://www.haskell.org/ghc/>
The Glasgow Haskell Compiler
More information about the ghc-tickets
mailing list