module Network.Xmpp.Concurrent.IQ where
import Control.Applicative ((<$>))
import Control.Concurrent (forkIO)
import Control.Concurrent.STM
import Control.Concurrent.Thread.Delay (delay)
import Control.Monad
import qualified Data.Map as Map
import Data.Text (Text)
import Data.XML.Types
import Network.Xmpp.Concurrent.Basic
import Network.Xmpp.Concurrent.Types
import Network.Xmpp.Types
sendIQ :: Maybe Integer
-> Maybe Jid
-> IQRequestType
-> Maybe LangTag
-> Element
-> Session
-> IO (Either XmppFailure (STM (Maybe (Annotated IQResponse))))
sendIQ timeOut to tp lang body session = do
newId <- idGenerator session
j <- case to of
Just t -> return $ Right t
Nothing -> Left <$> getJid session
ref <- atomically $ do
resRef <- newEmptyTMVar
let value = (j, resRef)
(byNS, byId) <- readTVar (iqHandlers session)
writeTVar (iqHandlers session) (byNS, Map.insert newId value byId)
return resRef
res <- sendStanza (IQRequestS $ IQRequest newId Nothing to lang tp body) session
case res of
Right () -> do
case timeOut of
Nothing -> return ()
Just t -> void . forkIO $ do
delay t
doTimeOut (iqHandlers session) newId ref
return . Right $ readTMVar ref
Left e -> return $ Left e
where
doTimeOut handlers iqid var = atomically $ do
p <- tryPutTMVar var Nothing
when p $ do
(byNS, byId) <- readTVar (iqHandlers session)
writeTVar handlers (byNS, Map.delete iqid byId)
return ()
sendIQA' :: Maybe Integer
-> Maybe Jid
-> IQRequestType
-> Maybe LangTag
-> Element
-> Session
-> IO (Either IQSendError (Annotated IQResponse))
sendIQA' timeout to tp lang body session = do
ref <- sendIQ timeout to tp lang body session
either (return . Left . IQSendError) (fmap (maybe (Left IQTimeOut) Right)
. atomically) ref
sendIQ' :: Maybe Integer
-> Maybe Jid
-> IQRequestType
-> Maybe LangTag
-> Element
-> Session
-> IO (Either IQSendError IQResponse)
sendIQ' timeout to tp lang body session = fmap fst <$> sendIQA' timeout to tp lang body session
listenIQ :: IQRequestType
-> Text
-> Session
-> IO (Either (STM IQRequestTicket) (STM IQRequestTicket))
listenIQ tp ns session = do
let handlers = (iqHandlers session)
atomically $ do
(byNS, byID) <- readTVar handlers
iqCh <- newTChan
let (present, byNS') = Map.insertLookupWithKey'
(\_ _ old -> old)
(tp, ns)
iqCh
byNS
writeTVar handlers (byNS', byID)
case present of
Nothing -> return . Right $ readTChan iqCh
Just iqCh' -> do
clonedChan <- cloneTChan iqCh'
return . Left $ readTChan clonedChan
unlistenIQ :: IQRequestType
-> Text
-> Session
-> IO ()
unlistenIQ tp ns session = do
let handlers = (iqHandlers session)
atomically $ do
(byNS, byID) <- readTVar handlers
let byNS' = Map.delete (tp, ns) byNS
writeTVar handlers (byNS', byID)
return ()
answerIQ :: IQRequestTicket
-> Either StanzaError (Maybe Element)
-> IO (Maybe (Either XmppFailure ()))
answerIQ ticket = answerTicket ticket