Browse Source
As previously mentioned, `Context' is simply a bunch of thread management features. This patch moves the `Context' fields into `Session', and the `Network.Xmpp.Concurrent.Channel' modules into `Network.Xmpp.Concurrent'.master
13 changed files with 159 additions and 185 deletions
@ -1,12 +1,111 @@ |
|||||||
{-# OPTIONS_HADDOCK hide #-} |
{-# OPTIONS_HADDOCK hide #-} |
||||||
|
{-# LANGUAGE OverloadedStrings #-} |
||||||
module Network.Xmpp.Concurrent |
module Network.Xmpp.Concurrent |
||||||
( Context |
( module Network.Xmpp.Concurrent.Monad |
||||||
, module Network.Xmpp.Concurrent.Monad |
|
||||||
, module Network.Xmpp.Concurrent.Threads |
, module Network.Xmpp.Concurrent.Threads |
||||||
, module Network.Xmpp.Concurrent.Channels |
, module Network.Xmpp.Concurrent.Basic |
||||||
|
, module Network.Xmpp.Concurrent.Types |
||||||
|
, module Network.Xmpp.Concurrent.Message |
||||||
|
, module Network.Xmpp.Concurrent.Presence |
||||||
|
, module Network.Xmpp.Concurrent.IQ |
||||||
|
, toChans |
||||||
|
, newSession |
||||||
|
, writeWorker |
||||||
) where |
) where |
||||||
|
|
||||||
import Network.Xmpp.Concurrent.Types |
|
||||||
import Network.Xmpp.Concurrent.Monad |
import Network.Xmpp.Concurrent.Monad |
||||||
import Network.Xmpp.Concurrent.Threads |
import Network.Xmpp.Concurrent.Threads |
||||||
import Network.Xmpp.Concurrent.Channels |
import Control.Applicative((<$>),(<*>)) |
||||||
|
import Control.Concurrent |
||||||
|
import Control.Concurrent.STM |
||||||
|
import Control.Monad |
||||||
|
import qualified Data.ByteString as BS |
||||||
|
import Data.IORef |
||||||
|
import qualified Data.Map as Map |
||||||
|
import Data.Maybe (fromMaybe) |
||||||
|
import Data.XML.Types |
||||||
|
import Network.Xmpp.Concurrent.Basic |
||||||
|
import Network.Xmpp.Concurrent.IQ |
||||||
|
import Network.Xmpp.Concurrent.Message |
||||||
|
import Network.Xmpp.Concurrent.Presence |
||||||
|
import Network.Xmpp.Concurrent.Types |
||||||
|
import Network.Xmpp.Concurrent.Threads |
||||||
|
import Network.Xmpp.Marshal |
||||||
|
import Network.Xmpp.Pickle |
||||||
|
import Network.Xmpp.Types |
||||||
|
import Text.Xml.Stream.Elements |
||||||
|
|
||||||
|
toChans :: TChan Stanza |
||||||
|
-> TVar IQHandlers |
||||||
|
-> Stanza |
||||||
|
-> IO () |
||||||
|
toChans stanzaC iqHands sta = atomically $ do |
||||||
|
writeTChan stanzaC sta |
||||||
|
case sta of |
||||||
|
IQRequestS i -> handleIQRequest iqHands i |
||||||
|
IQResultS i -> handleIQResponse iqHands (Right i) |
||||||
|
IQErrorS i -> handleIQResponse iqHands (Left i) |
||||||
|
_ -> return () |
||||||
|
where |
||||||
|
-- If the IQ request has a namespace, send it through the appropriate channel. |
||||||
|
handleIQRequest :: TVar IQHandlers -> IQRequest -> STM () |
||||||
|
handleIQRequest handlers iq = do |
||||||
|
(byNS, _) <- readTVar handlers |
||||||
|
let iqNS = fromMaybe "" (nameNamespace . elementName $ iqRequestPayload iq) |
||||||
|
case Map.lookup (iqRequestType iq, iqNS) byNS of |
||||||
|
Nothing -> return () -- TODO: send error stanza |
||||||
|
Just ch -> do |
||||||
|
sent <- newTVar False |
||||||
|
writeTChan ch $ IQRequestTicket sent iq |
||||||
|
handleIQResponse :: TVar IQHandlers -> Either IQError IQResult -> STM () |
||||||
|
handleIQResponse handlers iq = do |
||||||
|
(byNS, byID) <- readTVar handlers |
||||||
|
case Map.updateLookupWithKey (\_ _ -> Nothing) (iqID iq) byID of |
||||||
|
(Nothing, _) -> return () -- We are not supposed to send an error. |
||||||
|
(Just tmvar, byID') -> do |
||||||
|
let answer = either IQResponseError IQResponseResult iq |
||||||
|
_ <- tryPutTMVar tmvar answer -- Don't block. |
||||||
|
writeTVar handlers (byNS, byID') |
||||||
|
where |
||||||
|
iqID (Left err) = iqErrorID err |
||||||
|
iqID (Right iq') = iqResultID iq' |
||||||
|
|
||||||
|
|
||||||
|
-- | Creates and initializes a new Xmpp context. |
||||||
|
newSession :: TMVar Connection -> IO Session |
||||||
|
newSession con = do |
||||||
|
outC <- newTChanIO |
||||||
|
stanzaChan <- newTChanIO |
||||||
|
iqHandlers <- newTVarIO (Map.empty, Map.empty) |
||||||
|
eh <- newTVarIO $ EventHandlers { connectionClosedHandler = \_ -> return () } |
||||||
|
let stanzaHandler = toChans stanzaChan iqHandlers |
||||||
|
(kill, wLock, conState, readerThread) <- startThreadsWith stanzaHandler eh con |
||||||
|
writer <- forkIO $ writeWorker outC wLock |
||||||
|
idRef <- newTVarIO 1 |
||||||
|
let getId = atomically $ do |
||||||
|
curId <- readTVar idRef |
||||||
|
writeTVar idRef (curId + 1 :: Integer) |
||||||
|
return . read. show $ curId |
||||||
|
return $ Session { stanzaCh = stanzaChan |
||||||
|
, outCh = outC |
||||||
|
, iqHandlers = iqHandlers |
||||||
|
, writeRef = wLock |
||||||
|
, readerThread = readerThread |
||||||
|
, idGenerator = getId |
||||||
|
, conRef = conState |
||||||
|
, eventHandlers = eh |
||||||
|
, stopThreads = kill >> killThread writer |
||||||
|
} |
||||||
|
|
||||||
|
-- Worker to write stanzas to the stream concurrently. |
||||||
|
writeWorker :: TChan Stanza -> TMVar (BS.ByteString -> IO Bool) -> IO () |
||||||
|
writeWorker stCh writeR = forever $ do |
||||||
|
(write, next) <- atomically $ (,) <$> |
||||||
|
takeTMVar writeR <*> |
||||||
|
readTChan stCh |
||||||
|
r <- write $ renderElement (pickleElem xpStanza next) |
||||||
|
atomically $ putTMVar writeR write |
||||||
|
unless r $ do |
||||||
|
atomically $ unGetTChan stCh next -- If the writing failed, the |
||||||
|
-- connection is dead. |
||||||
|
threadDelay 250000 -- Avoid free spinning. |
||||||
|
|||||||
@ -1,8 +1,8 @@ |
|||||||
{-# OPTIONS_HADDOCK hide #-} |
{-# OPTIONS_HADDOCK hide #-} |
||||||
module Network.Xmpp.Concurrent.Channels.Basic where |
module Network.Xmpp.Concurrent.Basic where |
||||||
|
|
||||||
import Control.Concurrent.STM |
import Control.Concurrent.STM |
||||||
import Network.Xmpp.Concurrent.Channels.Types |
import Network.Xmpp.Concurrent.Types |
||||||
import Network.Xmpp.Types |
import Network.Xmpp.Types |
||||||
|
|
||||||
-- | Send a stanza to the server. |
-- | Send a stanza to the server. |
||||||
@ -1,112 +0,0 @@ |
|||||||
{-# OPTIONS_HADDOCK hide #-} |
|
||||||
{-# LANGUAGE OverloadedStrings #-} |
|
||||||
module Network.Xmpp.Concurrent.Channels |
|
||||||
( module Network.Xmpp.Concurrent.Channels.Basic |
|
||||||
, module Network.Xmpp.Concurrent.Channels.Types |
|
||||||
, module Network.Xmpp.Concurrent.Channels.Message |
|
||||||
, module Network.Xmpp.Concurrent.Channels.Presence |
|
||||||
, module Network.Xmpp.Concurrent.Channels.IQ |
|
||||||
, toChans |
|
||||||
, newSession |
|
||||||
, writeWorker |
|
||||||
) |
|
||||||
|
|
||||||
where |
|
||||||
|
|
||||||
import Control.Applicative((<$>),(<*>)) |
|
||||||
import Control.Concurrent |
|
||||||
import Control.Concurrent.STM |
|
||||||
import Control.Monad |
|
||||||
import qualified Data.ByteString as BS |
|
||||||
import Data.IORef |
|
||||||
import qualified Data.Map as Map |
|
||||||
import Data.Maybe (fromMaybe) |
|
||||||
import Data.XML.Types |
|
||||||
import Network.Xmpp.Concurrent.Channels.Basic |
|
||||||
import Network.Xmpp.Concurrent.Channels.IQ |
|
||||||
import Network.Xmpp.Concurrent.Channels.Message |
|
||||||
import Network.Xmpp.Concurrent.Channels.Presence |
|
||||||
import Network.Xmpp.Concurrent.Channels.Types |
|
||||||
import Network.Xmpp.Concurrent.Threads |
|
||||||
import Network.Xmpp.Concurrent.Types |
|
||||||
import Network.Xmpp.Marshal |
|
||||||
import Network.Xmpp.Pickle |
|
||||||
import Network.Xmpp.Types |
|
||||||
import Text.Xml.Stream.Elements |
|
||||||
|
|
||||||
toChans :: TChan Stanza |
|
||||||
-> TVar IQHandlers |
|
||||||
-> Stanza |
|
||||||
-> IO () |
|
||||||
toChans stanzaC iqHands sta = atomically $ do |
|
||||||
writeTChan stanzaC sta |
|
||||||
case sta of |
|
||||||
IQRequestS i -> handleIQRequest iqHands i |
|
||||||
IQResultS i -> handleIQResponse iqHands (Right i) |
|
||||||
IQErrorS i -> handleIQResponse iqHands (Left i) |
|
||||||
_ -> return () |
|
||||||
where |
|
||||||
-- If the IQ request has a namespace, send it through the appropriate channel. |
|
||||||
handleIQRequest :: TVar IQHandlers -> IQRequest -> STM () |
|
||||||
handleIQRequest handlers iq = do |
|
||||||
(byNS, _) <- readTVar handlers |
|
||||||
let iqNS = fromMaybe "" (nameNamespace . elementName $ iqRequestPayload iq) |
|
||||||
case Map.lookup (iqRequestType iq, iqNS) byNS of |
|
||||||
Nothing -> return () -- TODO: send error stanza |
|
||||||
Just ch -> do |
|
||||||
sent <- newTVar False |
|
||||||
writeTChan ch $ IQRequestTicket sent iq |
|
||||||
handleIQResponse :: TVar IQHandlers -> Either IQError IQResult -> STM () |
|
||||||
handleIQResponse handlers iq = do |
|
||||||
(byNS, byID) <- readTVar handlers |
|
||||||
case Map.updateLookupWithKey (\_ _ -> Nothing) (iqID iq) byID of |
|
||||||
(Nothing, _) -> return () -- We are not supposed to send an error. |
|
||||||
(Just tmvar, byID') -> do |
|
||||||
let answer = either IQResponseError IQResponseResult iq |
|
||||||
_ <- tryPutTMVar tmvar answer -- Don't block. |
|
||||||
writeTVar handlers (byNS, byID') |
|
||||||
where |
|
||||||
iqID (Left err) = iqErrorID err |
|
||||||
iqID (Right iq') = iqResultID iq' |
|
||||||
|
|
||||||
|
|
||||||
-- | Creates and initializes a new Xmpp context. |
|
||||||
newSession :: TMVar Connection -> IO Session |
|
||||||
newSession con = do |
|
||||||
outC <- newTChanIO |
|
||||||
stanzaChan <- newTChanIO |
|
||||||
iqHandlers <- newTVarIO (Map.empty, Map.empty) |
|
||||||
eh <- newTVarIO $ EventHandlers { connectionClosedHandler = \_ -> return () } |
|
||||||
let stanzaHandler = toChans stanzaChan iqHandlers |
|
||||||
(kill, wLock, conState, readerThread) <- startThreadsWith stanzaHandler eh con |
|
||||||
writer <- forkIO $ writeWorker outC wLock |
|
||||||
idRef <- newTVarIO 1 |
|
||||||
let getId = atomically $ do |
|
||||||
curId <- readTVar idRef |
|
||||||
writeTVar idRef (curId + 1 :: Integer) |
|
||||||
return . read. show $ curId |
|
||||||
let cont = Context { writeRef = wLock |
|
||||||
, readerThread = readerThread |
|
||||||
, idGenerator = getId |
|
||||||
, conRef = conState |
|
||||||
, eventHandlers = eh |
|
||||||
, stopThreads = kill >> killThread writer |
|
||||||
} |
|
||||||
return $ Session { context = cont |
|
||||||
, stanzaCh = stanzaChan |
|
||||||
, outCh = outC |
|
||||||
, iqHandlers = iqHandlers |
|
||||||
} |
|
||||||
|
|
||||||
-- Worker to write stanzas to the stream concurrently. |
|
||||||
writeWorker :: TChan Stanza -> TMVar (BS.ByteString -> IO Bool) -> IO () |
|
||||||
writeWorker stCh writeR = forever $ do |
|
||||||
(write, next) <- atomically $ (,) <$> |
|
||||||
takeTMVar writeR <*> |
|
||||||
readTChan stCh |
|
||||||
r <- write $ renderElement (pickleElem xpStanza next) |
|
||||||
atomically $ putTMVar writeR write |
|
||||||
unless r $ do |
|
||||||
atomically $ unGetTChan stCh next -- If the writing failed, the |
|
||||||
-- connection is dead. |
|
||||||
threadDelay 250000 -- Avoid free spinning. |
|
||||||
@ -1,32 +0,0 @@ |
|||||||
{-# OPTIONS_HADDOCK hide #-} |
|
||||||
module Network.Xmpp.Concurrent.Channels.Types where |
|
||||||
|
|
||||||
import Control.Concurrent.STM |
|
||||||
import Data.IORef |
|
||||||
import qualified Data.Map as Map |
|
||||||
import Data.Text (Text) |
|
||||||
import Network.Xmpp.Concurrent.Types |
|
||||||
import Network.Xmpp.Types |
|
||||||
|
|
||||||
-- | A concurrent interface to Pontarius XMPP. |
|
||||||
data Session = Session |
|
||||||
{ context :: Context |
|
||||||
, stanzaCh :: TChan Stanza -- All stanzas |
|
||||||
, outCh :: TChan Stanza |
|
||||||
, iqHandlers :: TVar IQHandlers |
|
||||||
-- Writing lock, so that only one thread could write to the stream at any |
|
||||||
-- given time. |
|
||||||
} |
|
||||||
|
|
||||||
-- | IQHandlers holds the registered channels for incomming IQ requests and |
|
||||||
-- TMVars of and TMVars for expected IQ responses |
|
||||||
type IQHandlers = (Map.Map (IQRequestType, Text) (TChan IQRequestTicket) |
|
||||||
, Map.Map StanzaId (TMVar IQResponse) |
|
||||||
) |
|
||||||
|
|
||||||
-- | Contains whether or not a reply has been sent, and the IQ request body to |
|
||||||
-- reply to. |
|
||||||
data IQRequestTicket = IQRequestTicket |
|
||||||
{ sentRef :: (TVar Bool) |
|
||||||
, iqRequestBody :: IQRequest |
|
||||||
} |
|
||||||
@ -1,12 +1,12 @@ |
|||||||
{-# OPTIONS_HADDOCK hide #-} |
{-# OPTIONS_HADDOCK hide #-} |
||||||
module Network.Xmpp.Concurrent.Channels.Message where |
module Network.Xmpp.Concurrent.Message where |
||||||
|
|
||||||
import Network.Xmpp.Concurrent.Channels.Types |
import Network.Xmpp.Concurrent.Types |
||||||
import Control.Concurrent.STM |
import Control.Concurrent.STM |
||||||
import Data.IORef |
import Data.IORef |
||||||
import Network.Xmpp.Types |
import Network.Xmpp.Types |
||||||
import Network.Xmpp.Concurrent.Types |
import Network.Xmpp.Concurrent.Types |
||||||
import Network.Xmpp.Concurrent.Channels.Basic |
import Network.Xmpp.Concurrent.Basic |
||||||
|
|
||||||
-- | Read an element from the inbound stanza channel, acquiring a copy of the |
-- | Read an element from the inbound stanza channel, acquiring a copy of the |
||||||
-- channel as necessary. |
-- channel as necessary. |
||||||
@ -1,12 +1,11 @@ |
|||||||
{-# OPTIONS_HADDOCK hide #-} |
{-# OPTIONS_HADDOCK hide #-} |
||||||
module Network.Xmpp.Concurrent.Channels.Presence where |
module Network.Xmpp.Concurrent.Presence where |
||||||
|
|
||||||
import Network.Xmpp.Concurrent.Channels.Types |
|
||||||
import Control.Concurrent.STM |
import Control.Concurrent.STM |
||||||
import Data.IORef |
import Data.IORef |
||||||
import Network.Xmpp.Types |
import Network.Xmpp.Types |
||||||
import Network.Xmpp.Concurrent.Types |
import Network.Xmpp.Concurrent.Types |
||||||
import Network.Xmpp.Concurrent.Channels.Basic |
import Network.Xmpp.Concurrent.Basic |
||||||
|
|
||||||
-- | Read an element from the inbound stanza channel, acquiring a copy of the |
-- | Read an element from the inbound stanza channel, acquiring a copy of the |
||||||
-- channel as necessary. |
-- channel as necessary. |
||||||
Loading…
Reference in new issue