#4262: GHC's runtime never terminates unused worker threads
---------------------------------------------------------+------------------
Reporter: Remi | Owner:
Type: bug | Status: new
Priority: normal | Milestone: 7.0.1
Component: Runtime System | Version:
6.12.3
Keywords: worker thread foreign function interface | Testcase:
Blockedby: | Difficulty:
Os: Unknown/Multiple | Blocking:
Architecture: Unknown/Multiple | Failure:
Runtime performance bug
---------------------------------------------------------+------------------
Comment(by ezyang):
Here is a somewhat refined test-case, though POSIX only.
{{{
{-# LANGUAGE ForeignFunctionInterface #-}
module Main where
import Control.Concurrent
import Control.Monad
import Foreign.C.Types
import System.Mem
import System.Posix.Process
import System.Directory
import Control.Concurrent.QSem
foreign import ccall safe sleep :: CUInt -> IO ()
main = do
let amount = 200
qsem <- newQSem 0
replicateM_ amount . forkIO $ (sleep 2 >> signalQSem qsem)
replicateM_ amount $ waitQSem qsem
-- POSIX only: check thread usage manually
pid <- getProcessID
let dir = "/proc/" ++ show pid ++ "/task"
contents <- getDirectoryContents dir
let status = length contents - 2 -- . and ..
print status
}}}
--
Ticket URL: <http://hackage.haskell.org/trac/ghc/ticket/4262#comment:3>
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