module GHC.Conc.IO
( ensureIOManagerIsRunning
, ioManagerCapabilitiesChanged
, threadDelay
, registerDelay
, threadWaitRead
, threadWaitWrite
, threadWaitReadSTM
, threadWaitWriteSTM
, closeFdWith
#ifdef mingw32_HOST_OS
, asyncRead
, asyncWrite
, asyncDoProc
, asyncReadBA
, asyncWriteBA
, ConsoleEvent(..)
, win32ConsoleHandler
, toWin32ConsoleEvent
#endif
) where
import Foreign
import GHC.Base
import GHC.Conc.Sync as Sync
import GHC.Real ( fromIntegral )
import System.Posix.Types
#ifdef mingw32_HOST_OS
import qualified GHC.Conc.Windows as Windows
import GHC.Conc.Windows (asyncRead, asyncWrite, asyncDoProc, asyncReadBA,
asyncWriteBA, ConsoleEvent(..), win32ConsoleHandler,
toWin32ConsoleEvent)
#else
import qualified GHC.Event.Thread as Event
#endif
ensureIOManagerIsRunning :: IO ()
#ifndef mingw32_HOST_OS
ensureIOManagerIsRunning = Event.ensureIOManagerIsRunning
#else
ensureIOManagerIsRunning = Windows.ensureIOManagerIsRunning
#endif
ioManagerCapabilitiesChanged :: IO ()
#ifndef mingw32_HOST_OS
ioManagerCapabilitiesChanged = Event.ioManagerCapabilitiesChanged
#else
ioManagerCapabilitiesChanged = return ()
#endif
threadWaitRead :: Fd -> IO ()
threadWaitRead fd
#ifndef mingw32_HOST_OS
| threaded = Event.threadWaitRead fd
#endif
| otherwise = IO $ \s ->
case fromIntegral fd of { I# fd# ->
case waitRead# fd# s of { s' -> (# s', () #)
}}
threadWaitWrite :: Fd -> IO ()
threadWaitWrite fd
#ifndef mingw32_HOST_OS
| threaded = Event.threadWaitWrite fd
#endif
| otherwise = IO $ \s ->
case fromIntegral fd of { I# fd# ->
case waitWrite# fd# s of { s' -> (# s', () #)
}}
threadWaitReadSTM :: Fd -> IO (Sync.STM (), IO ())
threadWaitReadSTM fd
#ifndef mingw32_HOST_OS
| threaded = Event.threadWaitReadSTM fd
#endif
| otherwise = do
m <- Sync.newTVarIO False
t <- Sync.forkIO $ do
threadWaitRead fd
Sync.atomically $ Sync.writeTVar m True
let waitAction = do b <- Sync.readTVar m
if b then return () else retry
let killAction = Sync.killThread t
return (waitAction, killAction)
threadWaitWriteSTM :: Fd -> IO (Sync.STM (), IO ())
threadWaitWriteSTM fd
#ifndef mingw32_HOST_OS
| threaded = Event.threadWaitWriteSTM fd
#endif
| otherwise = do
m <- Sync.newTVarIO False
t <- Sync.forkIO $ do
threadWaitWrite fd
Sync.atomically $ Sync.writeTVar m True
let waitAction = do b <- Sync.readTVar m
if b then return () else retry
let killAction = Sync.killThread t
return (waitAction, killAction)
closeFdWith :: (Fd -> IO ())
-> Fd
-> IO ()
closeFdWith close fd
#ifndef mingw32_HOST_OS
| threaded = Event.closeFdWith close fd
#endif
| otherwise = close fd
threadDelay :: Int -> IO ()
threadDelay time
#ifdef mingw32_HOST_OS
| threaded = Windows.threadDelay time
#else
| threaded = Event.threadDelay time
#endif
| otherwise = IO $ \s ->
case time of { I# time# ->
case delay# time# s of { s' -> (# s', () #)
}}
registerDelay :: Int -> IO (TVar Bool)
registerDelay usecs
#ifdef mingw32_HOST_OS
| threaded = Windows.registerDelay usecs
#else
| threaded = Event.registerDelay usecs
#endif
| otherwise = errorWithoutStackTrace "registerDelay: requires -threaded"
foreign import ccall unsafe "rtsSupportsBoundThreads" threaded :: Bool