#5797: readRawBufferPtr cannot be interrupted by exception on Windows with
-threaded
-------------------------------+--------------------------------------------
    Reporter:  joeyadams       |       Owner:                             
        Type:  bug             |      Status:  new                        
    Priority:  normal          |   Milestone:                             
   Component:  libraries/base  |     Version:  7.2.2                      
    Keywords:                  |          Os:  Windows                    
Architecture:  x86             |     Failure:  Incorrect result at runtime
  Difficulty:  Unknown         |    Testcase:                             
   Blockedby:                  |    Blocking:                             
     Related:                  |  
-------------------------------+--------------------------------------------

Comment(by simonmar):

 Ah, so I forgot that we did try to make `threadWaitRead` do something on
 Windows.  Here's its implementation:

 {{{
 threadWaitRead :: Fd -> IO ()
 threadWaitRead fd
 #ifdef mingw32_HOST_OS
   -- we have no IO manager implementing threadWaitRead on Windows.
   -- fdReady does the right thing, but we have to call it in a
   -- separate thread, otherwise threadWaitRead won't be interruptible,
   -- and this only works with -threaded.
   | threaded  = withThread (waitFd fd 0)
   | otherwise = case fd of
                   0 -> do _ <- hWaitForInput stdin (-1)
                           return ()
                         -- hWaitForInput does work properly, but we can
 only
                         -- do this for stdin since we know its FD.
                   _ -> error "threadWaitRead requires -threaded on
 Windows, or use System.IO.hWaitForInput"
 #else
   = GHC.Conc.threadWaitRead fd
 #endif

 withThread :: IO a -> IO a
 withThread io = do
   m <- newEmptyMVar
   _ <- mask_ $ forkIO $ try io >>= putMVar m
   x <- takeMVar m
   case x of
     Right a -> return a
     Left e  -> throwIO (e :: IOException)

 waitFd :: Fd -> CInt -> IO ()
 waitFd fd write = do
    throwErrnoIfMinus1_ "fdReady" $
         fdReady (fromIntegral fd) write iNFINITE 0

 iNFINITE :: CInt
 iNFINITE = 0xFFFFFFFF -- urgh

 foreign import ccall safe "fdReady"
   fdReady :: CInt -> CInt -> CInt -> CInt -> IO CInt
 }}}

 And we can see why it doesn't work with a socket: the 4th argument to
 `fdReady` should be non-zero for a socket, but we're always passing zero
 here, because we have no information about whether the `Fd` passed to
 `threadWaitRead` is a socket or not.

 You could build your own version of `threadWaitRead` that works for
 sockets quite easy by modifying the above code.

-- 
Ticket URL: <http://hackage.haskell.org/trac/ghc/ticket/5797#comment:5>
GHC <http://www.haskell.org/ghc/>
The Glasgow Haskell Compiler

_______________________________________________
Glasgow-haskell-bugs mailing list
Glasgow-haskell-bugs@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-bugs

Reply via email to