-- | Utility functions
--
-- Note: this module is bound to change even more than the rest of the API :)
module Network.Transport.Util (spawn) where

import Network.Transport
  ( Transport
  , EndPoint(..)
  , EndPointAddress
  , newEndPoint
  )
import Control.Exception (throwIO)
import Control.Concurrent (forkIO)
import Control.Concurrent.MVar (newEmptyMVar, putMVar, takeMVar)

-- | Fork a new thread, create a new end point on that thread, and run the specified IO operation on that thread.
--
-- Returns the address of the new end point.
spawn :: Transport -> (EndPoint -> IO ()) -> IO EndPointAddress
spawn :: Transport -> (EndPoint -> IO ()) -> IO EndPointAddress
spawn Transport
transport EndPoint -> IO ()
proc = do
  MVar (Either (TransportError NewEndPointErrorCode) EndPointAddress)
addrMVar <- forall a. IO (MVar a)
newEmptyMVar
  IO () -> IO ThreadId
forkIO forall a b. (a -> b) -> a -> b
$ do
    Either (TransportError NewEndPointErrorCode) EndPoint
mEndPoint <- Transport
-> IO (Either (TransportError NewEndPointErrorCode) EndPoint)
newEndPoint Transport
transport
    case Either (TransportError NewEndPointErrorCode) EndPoint
mEndPoint of
      Left TransportError NewEndPointErrorCode
err ->
        forall a. MVar a -> a -> IO ()
putMVar MVar (Either (TransportError NewEndPointErrorCode) EndPointAddress)
addrMVar (forall a b. a -> Either a b
Left TransportError NewEndPointErrorCode
err)
      Right EndPoint
endPoint -> do
        forall a. MVar a -> a -> IO ()
putMVar MVar (Either (TransportError NewEndPointErrorCode) EndPointAddress)
addrMVar (forall a b. b -> Either a b
Right (EndPoint -> EndPointAddress
address EndPoint
endPoint))
        EndPoint -> IO ()
proc EndPoint
endPoint
  Either (TransportError NewEndPointErrorCode) EndPointAddress
mAddr <- forall a. MVar a -> IO a
takeMVar MVar (Either (TransportError NewEndPointErrorCode) EndPointAddress)
addrMVar
  case Either (TransportError NewEndPointErrorCode) EndPointAddress
mAddr of
    Left TransportError NewEndPointErrorCode
err   -> forall e a. Exception e => e -> IO a
throwIO TransportError NewEndPointErrorCode
err
    Right EndPointAddress
addr -> forall (m :: * -> *) a. Monad m => a -> m a
return EndPointAddress
addr