module Network.Xmpp.Concurrent.Monad where
import Control.Applicative ((<$>))
import Control.Concurrent
import Control.Concurrent.STM
import qualified Control.Exception.Lifted as Ex
import Control.Monad.State
import Network.Xmpp.Concurrent.Types
import Network.Xmpp.Stream
import Network.Xmpp.Types
withConnection :: (Stream -> IO (b, Stream))
-> Session
-> IO (Either XmppFailure b)
withConnection a session = do
wait <- newEmptyTMVarIO
Ex.mask_ $ do
throwTo (readerThread session) $ Interrupt wait
s <- Ex.catch
(atomically $ do
_ <- takeTMVar (writeSemaphore session)
s <- takeTMVar (streamRef session)
putTMVar wait ()
return s
)
(\e -> atomically (putTMVar wait ()) >>
Ex.throwIO (e :: Ex.SomeException)
)
Ex.catches
(do
(res, s') <- a s
wl <- withStream' (gets $ streamSend . streamHandle) s'
atomically $ do
putTMVar (writeSemaphore session) wl
putTMVar (streamRef session) s'
return $ Right res
)
[ Ex.Handler $ \e -> return $ Left (e :: XmppFailure)
, Ex.Handler $ \e -> killStream s
>> Ex.throwIO (e :: Ex.SomeException)
]
modifyHandlers :: (EventHandlers -> EventHandlers) -> Session -> IO ()
modifyHandlers f session = atomically $ modifyTMVar_ (eventHandlers session) f
where
modifyTMVar_ :: TMVar a -> (a -> a) -> STM ()
modifyTMVar_ var g = do
x <- takeTMVar var
putTMVar var (g x)
setConnectionClosedHandler :: (XmppFailure -> Session -> IO ()) -> Session -> IO ()
setConnectionClosedHandler eh session = do
modifyHandlers (\s -> s{connectionClosedHandler =
\e -> eh e session}) session
runConnectionClosedHandler :: Session -> XmppFailure -> IO ()
runConnectionClosedHandler session e = do
h <- connectionClosedHandler <$> atomically (readTMVar
$ eventHandlers session)
h e
runHandler :: (EventHandlers -> IO a) -> Session -> IO a
runHandler h session = h =<< atomically (readTMVar $ eventHandlers session)
endSession :: Session -> IO ()
endSession session = do
stopThreads session
_ <- flip withConnection session $ \stream -> do
_ <- closeStreams stream
return ((), stream)
return ()
closeConnection :: Session -> IO ()
closeConnection session = do
_ <-flip withConnection session $ \stream -> do
_ <- closeStreams stream
return ((), stream)
runConnectionClosedHandler session StreamEndFailure