{-# LANGUAGE CPP #-}
{-# LANGUAGE RankNTypes #-}
{-# OPTIONS_GHC -Wno-dodgy-exports #-}
module System.IOManager
( WithIOManager
, IOManager (..)
, IOManagerError (..)
, withIOManager
, AssociateWithIOCP
, associateWithIOCP
) where
#if defined(mingw32_HOST_OS)
import System.Win32.Types (HANDLE)
import qualified System.Win32.Async.IOManager as Win32.Async
import Network.Socket (Socket)
#else
import Data.Void (Void)
#endif
#if defined(mingw32_HOST_OS)
type IOManagerError = Win32.Async.IOManagerError
#else
type IOManagerError = Void
#endif
#if defined(mingw32_HOST_OS)
newtype IOManager = IOManager {
associateWithIOManager :: Either HANDLE Socket -> IO ()
}
associateWithIOCP :: IOManager -> Either HANDLE Socket -> IO ()
associateWithIOCP = associateWithIOManager
#else
newtype IOManager = IOManager {
IOManager -> forall hole. hole -> IO ()
associateWithIOManager :: forall hole. hole -> IO ()
}
associateWithIOCP :: forall hole. IOManager -> hole -> IO ()
associateWithIOCP :: IOManager -> hole -> IO ()
associateWithIOCP = \IOManager
x -> IOManager -> forall hole. hole -> IO ()
associateWithIOManager IOManager
x
#endif
type AssociateWithIOCP = IOManager
{-# DEPRECATED AssociateWithIOCP "Usage of type alias AssociateWithIOCP is deprecated, use 'IOManager' instead " #-}
{-# DEPRECATED associateWithIOCP "Usage of 'associateWithIOCP' is deprecated, use 'associateWithIOManager' instead." #-}
type WithIOManager = forall a. (IOManager -> IO a) -> IO a
withIOManager :: WithIOManager
#if defined(mingw32_HOST_OS)
withIOManager = \f ->
Win32.Async.withIOManager $
\iocp -> f (IOManager $ \fd -> Win32.Async.associateWithIOCompletionPort fd iocp)
#else
withIOManager :: (IOManager -> IO a) -> IO a
withIOManager = \IOManager -> IO a
f -> IOManager -> IO a
f ((forall hole. hole -> IO ()) -> IOManager
IOManager ((forall hole. hole -> IO ()) -> IOManager)
-> (forall hole. hole -> IO ()) -> IOManager
forall a b. (a -> b) -> a -> b
$ \hole
_ -> () -> IO ()
forall (f :: * -> *) a. Applicative f => a -> f a
pure ())
#endif