Skip to content

Commit

Permalink
Fix warnings on Windows
Browse files Browse the repository at this point in the history
  • Loading branch information
igfoo committed Jan 12, 2013
1 parent 753e3e3 commit 8564b7f
Showing 1 changed file with 5 additions and 5 deletions.
10 changes: 5 additions & 5 deletions libraries/base/Control/Concurrent.hs
Original file line number Diff line number Diff line change
Expand Up @@ -128,7 +128,7 @@ import GHC.Base
import System.Posix.Types ( Fd )
import Foreign.StablePtr
import Foreign.C.Types
import Control.Monad ( when )
import Control.Monad

#ifdef mingw32_HOST_OS
import Foreign.C
Expand Down Expand Up @@ -460,8 +460,8 @@ threadWaitReadSTM :: Fd -> IO (STM (), IO ())
threadWaitReadSTM fd
#ifdef mingw32_HOST_OS
| threaded = do v <- newTVarIO Nothing
mask_ $ forkIO $ do result <- try (waitFd fd 0)
atomically (writeTVar v $ Just result)
mask_ $ void $ forkIO $ do result <- try (waitFd fd 0)
atomically (writeTVar v $ Just result)
let waitAction = do result <- readTVar v
case result of
Nothing -> retry
Expand All @@ -482,8 +482,8 @@ threadWaitWriteSTM :: Fd -> IO (STM (), IO ())
threadWaitWriteSTM fd
#ifdef mingw32_HOST_OS
| threaded = do v <- newTVarIO Nothing
mask_ $ forkIO $ do result <- try (waitFd fd 1)
atomically (writeTVar v $ Just result)
mask_ $ void $ forkIO $ do result <- try (waitFd fd 1)
atomically (writeTVar v $ Just result)
let waitAction = do result <- readTVar v
case result of
Nothing -> retry
Expand Down

0 comments on commit 8564b7f

Please sign in to comment.