|
|
|
@ -1,8 +1,10 @@ |
|
|
|
{-# OPTIONS_HADDOCK hide #-} |
|
|
|
{-# OPTIONS_HADDOCK hide #-} |
|
|
|
module Network.Xmpp.Concurrent.IQ where |
|
|
|
module Network.Xmpp.Concurrent.IQ where |
|
|
|
|
|
|
|
|
|
|
|
import Control.Concurrent (forkIO, threadDelay) |
|
|
|
import Control.Concurrent (forkIO) |
|
|
|
|
|
|
|
import Control.Concurrent.Thread.Delay (delay) |
|
|
|
import Control.Concurrent.STM |
|
|
|
import Control.Concurrent.STM |
|
|
|
|
|
|
|
|
|
|
|
import Control.Monad |
|
|
|
import Control.Monad |
|
|
|
|
|
|
|
|
|
|
|
import qualified Data.Map as Map |
|
|
|
import qualified Data.Map as Map |
|
|
|
@ -16,9 +18,9 @@ import Network.Xmpp.Types |
|
|
|
-- | Sends an IQ, returns Just a 'TMVar' that will be filled with the first |
|
|
|
-- | Sends an IQ, returns Just a 'TMVar' that will be filled with the first |
|
|
|
-- inbound IQ with a matching ID that has type @result@ or @error@ or Nothing if |
|
|
|
-- inbound IQ with a matching ID that has type @result@ or @error@ or Nothing if |
|
|
|
-- the stanza could not be sent |
|
|
|
-- the stanza could not be sent |
|
|
|
sendIQ :: Maybe Int -- ^ Timeout . When the timeout is reached the response |
|
|
|
sendIQ :: Maybe Integer -- ^ Timeout . When the timeout is reached the response |
|
|
|
-- TMVar will be filled with 'IQResponseTimeout' and the id |
|
|
|
-- TMVar will be filled with 'IQResponseTimeout' and the |
|
|
|
-- is removed from the list of IQ handlers. 'Nothing' |
|
|
|
-- id is removed from the list of IQ handlers. 'Nothing' |
|
|
|
-- deactivates the timeout |
|
|
|
-- deactivates the timeout |
|
|
|
-> Maybe Jid -- ^ Recipient (to) |
|
|
|
-> Maybe Jid -- ^ Recipient (to) |
|
|
|
-> IQRequestType -- ^ IQ type (@Get@ or @Set@) |
|
|
|
-> IQRequestType -- ^ IQ type (@Get@ or @Set@) |
|
|
|
@ -26,7 +28,7 @@ sendIQ :: Maybe Int -- ^ Timeout . When the timeout is reached the response |
|
|
|
-- default) |
|
|
|
-- default) |
|
|
|
-> Element -- ^ The IQ body (there has to be exactly one) |
|
|
|
-> Element -- ^ The IQ body (there has to be exactly one) |
|
|
|
-> Session |
|
|
|
-> Session |
|
|
|
-> IO (Maybe (TMVar IQResponse)) |
|
|
|
-> IO (Maybe (TMVar (Maybe IQResponse))) |
|
|
|
sendIQ timeOut to tp lang body session = do -- TODO: Add timeout |
|
|
|
sendIQ timeOut to tp lang body session = do -- TODO: Add timeout |
|
|
|
newId <- idGenerator session |
|
|
|
newId <- idGenerator session |
|
|
|
ref <- atomically $ do |
|
|
|
ref <- atomically $ do |
|
|
|
@ -41,7 +43,7 @@ sendIQ timeOut to tp lang body session = do -- TODO: Add timeout |
|
|
|
case timeOut of |
|
|
|
case timeOut of |
|
|
|
Nothing -> return () |
|
|
|
Nothing -> return () |
|
|
|
Just t -> void . forkIO $ do |
|
|
|
Just t -> void . forkIO $ do |
|
|
|
threadDelay t |
|
|
|
delay t |
|
|
|
doTimeOut (iqHandlers session) newId ref |
|
|
|
doTimeOut (iqHandlers session) newId ref |
|
|
|
return $ Just ref |
|
|
|
return $ Just ref |
|
|
|
else return Nothing |
|
|
|
else return Nothing |
|
|
|
@ -53,16 +55,16 @@ sendIQ timeOut to tp lang body session = do -- TODO: Add timeout |
|
|
|
writeTVar handlers (byNS, Map.delete iqid byId) |
|
|
|
writeTVar handlers (byNS, Map.delete iqid byId) |
|
|
|
return () |
|
|
|
return () |
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
-- | Like 'sendIQ', but waits for the answer IQ. |
|
|
|
-- | Like 'sendIQ', but waits for the answer IQ. Times out after 30 seconds |
|
|
|
sendIQ' :: Maybe Integer |
|
|
|
sendIQ' :: Maybe Jid |
|
|
|
-> Maybe Jid |
|
|
|
-> IQRequestType |
|
|
|
-> IQRequestType |
|
|
|
-> Maybe LangTag |
|
|
|
-> Maybe LangTag |
|
|
|
-> Element |
|
|
|
-> Element |
|
|
|
-> Session |
|
|
|
-> Session |
|
|
|
-> IO (Maybe IQResponse) |
|
|
|
-> IO (Maybe IQResponse) |
|
|
|
sendIQ' to tp lang body session = do |
|
|
|
sendIQ' timeout to tp lang body session = do |
|
|
|
ref <- sendIQ (Just 30000000) to tp lang body session |
|
|
|
ref <- sendIQ timeout to tp lang body session |
|
|
|
maybe (return Nothing) (fmap Just . atomically . takeTMVar) ref |
|
|
|
maybe (return Nothing) (fmap Just . atomically . takeTMVar) ref |
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|