You can not select more than 25 topics
Topics must start with a letter or number, can include dashes ('-') and can be up to 35 characters long.
60 lines
2.1 KiB
60 lines
2.1 KiB
|
13 years ago
|
{-# OPTIONS_HADDOCK hide #-}
|
||
|
13 years ago
|
module Network.Xmpp.Concurrent.Message where
|
||
|
13 years ago
|
|
||
|
13 years ago
|
import Network.Xmpp.Concurrent.Types
|
||
|
13 years ago
|
import Control.Concurrent.STM
|
||
|
|
import Data.IORef
|
||
|
|
import Network.Xmpp.Types
|
||
|
|
import Network.Xmpp.Concurrent.Types
|
||
|
13 years ago
|
import Network.Xmpp.Concurrent.Basic
|
||
|
13 years ago
|
|
||
|
|
-- | Read an element from the inbound stanza channel, acquiring a copy of the
|
||
|
|
-- channel as necessary.
|
||
|
13 years ago
|
pullMessage :: Session -> IO (Either MessageError Message)
|
||
|
13 years ago
|
pullMessage session = do
|
||
|
13 years ago
|
stanza <- atomically . readTChan $ stanzaCh session
|
||
|
|
case stanza of
|
||
|
|
MessageS m -> return $ Right m
|
||
|
|
MessageErrorS e -> return $ Left e
|
||
|
|
_ -> pullMessage session
|
||
|
13 years ago
|
|
||
|
13 years ago
|
-- | Get the next received message
|
||
|
13 years ago
|
getMessage :: Session -> IO Message
|
||
|
13 years ago
|
getMessage = waitForMessage (const True)
|
||
|
|
|
||
|
13 years ago
|
-- | Pulls a (non-error) message and returns it if the given predicate returns
|
||
|
|
-- @True@.
|
||
|
13 years ago
|
waitForMessage :: (Message -> Bool) -> Session -> IO Message
|
||
|
13 years ago
|
waitForMessage f session = do
|
||
|
|
s <- pullMessage session
|
||
|
|
case s of
|
||
|
|
Left _ -> waitForMessage f session
|
||
|
|
Right m | f m -> return m
|
||
|
|
| otherwise -> waitForMessage f session
|
||
|
|
|
||
|
|
-- | Pulls an error message and returns it if the given predicate returns @True@.
|
||
|
13 years ago
|
waitForMessageError :: (MessageError -> Bool) -> Session -> IO MessageError
|
||
|
13 years ago
|
waitForMessageError f session = do
|
||
|
|
s <- pullMessage session
|
||
|
|
case s of
|
||
|
|
Right _ -> waitForMessageError f session
|
||
|
|
Left m | f m -> return m
|
||
|
|
| otherwise -> waitForMessageError f session
|
||
|
|
|
||
|
|
|
||
|
|
-- | Pulls a message and returns it if the given predicate returns @True@.
|
||
|
|
filterMessages :: (MessageError -> Bool)
|
||
|
|
-> (Message -> Bool)
|
||
|
13 years ago
|
-> Session -> IO (Either MessageError Message)
|
||
|
13 years ago
|
filterMessages f g session = do
|
||
|
|
s <- pullMessage session
|
||
|
|
case s of
|
||
|
|
Left e | f e -> return $ Left e
|
||
|
|
| otherwise -> filterMessages f g session
|
||
|
|
Right m | g m -> return $ Right m
|
||
|
|
| otherwise -> filterMessages f g session
|
||
|
|
|
||
|
|
-- | Send a message stanza.
|
||
|
13 years ago
|
sendMessage :: Message -> Session -> IO ()
|
||
|
13 years ago
|
sendMessage m session = sendStanza (MessageS m) session
|