[GHC] #10380: "thread blocked indefinitely" exception while blocking on a socket

#10380: "thread blocked indefinitely" exception while blocking on a socket -------------------------------------+------------------------------------- Reporter: akio | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: | Version: 7.10.1 libraries/base | Operating System: Linux Keywords: | Type of failure: Incorrect result Architecture: | at runtime Unknown/Multiple | Blocked By: Test Case: | Related Tickets: Blocking: | Differential Revisions: | -------------------------------------+------------------------------------- First start a TCP server, e.g. nc. {{{ % nc localhost -l 1234 > /dev/null }}} On another shell, compile the following program and run it: {{{ % ghc -threaded sock.hs % ./sock localhost 1234 receiver: thread blocked indefinitely in an MVar operation }}} {{{#!hs {-# LANGUAGE ViewPatterns #-} import Control.Applicative -- GHC 7.8 compatibility import Control.Concurrent import qualified Control.Exception as Ex import Control.Monad import qualified Data.ByteString.Char8 as S import Network.Socket import qualified Network.Socket.ByteString as Sock import Network.BSD (getHostByName, hostAddresses) import System.Environment import System.Mem main :: IO () main = do [host, read -> fromInteger -> port] <- getArgs sock <- connectTo host port forkVerbose "sender" $ forever $ do _ <- Sock.send sock $ S.replicate 40000 '0' return () forkVerbose "receiver" $ forever $ do dat <- Sock.recv sock 2048 putStrLn $ "received: " ++ show dat forever $ do threadDelay 1000000 performGC forkVerbose :: String -> IO () -> IO () forkVerbose name act = void $ forkIO $ do act; msg "exiting normally" `Ex.catch` \e -> msg $ show (e :: Ex.SomeException) where msg s = putStrLn $ name ++ ": " ++ s connectTo :: HostName -> PortNumber -> IO Socket connectTo hostName port = do addr <- SockAddrInet port <$> lookupHost hostName sock <- socket AF_INET Stream 0 connect sock addr return sock lookupHost :: String -> IO HostAddress lookupHost name = do hostInfo <- getHostByName name case hostAddresses hostInfo of [] -> error ("Invalid host name: " ++ name) (a:_) -> return a }}} GHC 7.8.3 doesn't have this problem. I suspect that this is a regression in the event manager. When there is an event, `GHC.Event.Manager.onFdEvent` seems to remove all callbacks associated to the `fd`, whether or not they match the current event. In the program above, the callback for `recv` may be removed permanently when the socket becomes ready for `send`ing, causing the "receiver" thread to deadlock. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/10380 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#10380: "thread blocked indefinitely" exception while blocking on a socket -------------------------------------+------------------------------------- Reporter: akio | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: libraries/base | Version: 7.10.1 Resolution: | Keywords: Operating System: Linux | Architecture: Type of failure: Incorrect result | Unknown/Multiple at runtime | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Revisions: -------------------------------------+------------------------------------- Changes (by liyang): * cc: liyang (added) -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/10380#comment:1 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#10380: "thread blocked indefinitely" exception while blocking on a socket -------------------------------------+------------------------------------- Reporter: akio | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: libraries/base | Version: 7.10.1 Resolution: | Keywords: Operating System: Linux | Architecture: Type of failure: Incorrect result | Unknown/Multiple at runtime | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Revisions: -------------------------------------+------------------------------------- Changes (by AndreasVoellmy): * cc: AndreasVoellmy (added) -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/10380#comment:2 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#10380: "thread blocked indefinitely" exception while blocking on a socket -------------------------------------+------------------------------------- Reporter: akio | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: libraries/base | Version: 7.10.1 Resolution: | Keywords: Operating System: Linux | Architecture: Type of failure: Incorrect result | Unknown/Multiple at runtime | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Revisions: -------------------------------------+------------------------------------- Comment (by akio): Bryan Buecking has confirmed that the following patch fixes the issue. The patch was taken from the base commit of D849. Strangely I can't find the commit (635619c) in the repository. {{{ diff --git a/libraries/base/GHC/Event/Manager.hs b/libraries/base/GHC/Event/Manager.hs index 11b01ad..cd039b1 100644 --- a/libraries/base/GHC/Event/Manager.hs +++ b/libraries/base/GHC/Event/Manager.hs @@ -456,20 +456,26 @@ onFdEvent mgr fd evs | otherwise = do fdds <- withMVar (callbackTableVar mgr fd) $ \tbl -> - IT.delete (fromIntegral fd) tbl >>= maybe (return []) selectCallbacks + IT.delete (fromIntegral fd) tbl >>= maybe (return []) (selectCallbacks tbl) forM_ fdds $ \(FdData reg _ cb) -> cb reg evs where -- | Here we look through the list of registrations for the fd of interest -- and sort out which match the events that were triggered. We re-arm - -- the fd as appropriate and return this subset. - selectCallbacks :: [FdData] -> IO [FdData] - selectCallbacks fdds = do + -- the fd as appropriate and return a list containing the callbacks + -- that should be invoked. + selectCallbacks :: IntTable [FdData] -> [FdData] -> IO [FdData] + selectCallbacks tbl fdds = do let matches :: FdData -> Bool matches fd' = evs `I.eventIs` I.elEvent (fdEvents fd') - (triggered, saved) = partition matches fdds + (triggered, notTriggered) = partition matches fdds + saved = notTriggered ++ filter (\fd' -> I.elLifetime (fdEvents fd') == MultiShot) triggered savedEls = eventsOf saved allEls = eventsOf fdds + -- Reinsert multishot registrations. + -- We deleted the table entry for this fd above so we there isn't a preexisting entry + IT.insertWith (\_ _-> saved) (fromIntegral fd) saved tbl + case I.elLifetime allEls of -- we previously armed the fd for multiple shots, no need to rearm MultiShot | allEls == savedEls -> }}} -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/10380#comment:3 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#10380: "thread blocked indefinitely" exception while blocking on a socket -------------------------------------+------------------------------------- Reporter: akio | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: libraries/base | Version: 7.10.1 Resolution: | Keywords: Operating System: Linux | Architecture: Type of failure: Incorrect result | Unknown/Multiple at runtime | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Revisions: -------------------------------------+------------------------------------- Comment (by carter): is this related to ticket #10317? -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/10380#comment:4 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#10380: "thread blocked indefinitely" exception while blocking on a socket -------------------------------------+------------------------------------- Reporter: akio | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: libraries/base | Version: 7.10.1 Resolution: | Keywords: Operating System: Linux | Architecture: Type of failure: Incorrect result | Unknown/Multiple at runtime | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Revisions: -------------------------------------+------------------------------------- Comment (by bgamari): Yes, this looks like this is a manifestation of #10317 which is fixed by Phab:D849 which unfortunately has yet to be merged. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/10380#comment:5 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#10380: "thread blocked indefinitely" exception while blocking on a socket -------------------------------------+------------------------------------- Reporter: akio | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: libraries/base | Version: 7.10.1 Resolution: | Keywords: Operating System: Linux | Architecture: Type of failure: Incorrect result | Unknown/Multiple at runtime | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Revisions: -------------------------------------+------------------------------------- Changes (by basvandijk): * cc: basvandijk (added) -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/10380#comment:6 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#10380: "thread blocked indefinitely" exception while blocking on a socket -------------------------------------+------------------------------------- Reporter: akio | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: libraries/base | Version: 7.10.1 Resolution: | Keywords: Operating System: Linux | Architecture: Type of failure: Incorrect result | Unknown/Multiple at runtime | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Revisions: -------------------------------------+------------------------------------- Changes (by kazu-yamamoto): * cc: kazu-yamamoto (added) -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/10380#comment:7 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#10380: "thread blocked indefinitely" exception while blocking on a socket -------------------------------------+------------------------------------- Reporter: akio | Owner: Type: bug | Status: closed Priority: normal | Milestone: Component: libraries/base | Version: 7.10.1 Resolution: duplicate | Keywords: Operating System: Linux | Architecture: Type of failure: Incorrect result | Unknown/Multiple at runtime | Test Case: Blocked By: | Blocking: Related Tickets: #10317 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by thomie): * status: new => closed * resolution: => duplicate * related: => #10317 Comment: The example from the description works fine with 7.10.2. Assuming this was indeed a duplicate of #10317. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/10380#comment:8 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler
participants (1)
-
GHC