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.

127 lines
4.6 KiB

{-# LANGUAGE OverloadedStrings #-}
Change module structure We can treat all functions related to SASL negotiation as a submodule to Pontarius XMPP if there are no dependencies from the internal Network.Xmpp modules to the SASL functionality. Because of this, `auth' and `authSimple' were moved from Session.hs to Sasl.hs. As the bind and the `{urn:ietf:params:xml:ns:xmpp-session}session' functionality are related only to the SASL negotation functionality, these functions has been moved to the SASL submodule as well. As these changes only leaves `connect' in the Session module, it seems fitting to move `connect' to Network.Xmpp.Stream (not Network.Xmpp.Connection, as `connect' depends on `startStream'). The internal Network.Xmpp modules (Connection.hs) no longer depend on the Concurrent submodule. This will decrease the coupling between Network.Xmpp and the concurrent implementation, making it easier for developers to replace the concurrent implementation if they wanted to. As Network.Xmpp.Connection is really a module that breaks the encapsulation that is Network.Xmpp and the concurrent interface, I have renamed it Network.Xmpp.Internal. As this frees up the Network.Xmpp.Connection name, Network.Xmpp.Connection_ can reclaim it. The high-level "utility" functions of Network.Xmpp.Utilities, Network.Xmpp.Presence, and Network.Xmpp.Message has been moved to Network.Xmpp.Utilities. This module contains functions that at most only depend on the internal Network.Xmpp.Types module, and doesn't belong in any other module. The functionality of Jid.hs was moved to Types.hs. Moved some of the functions of Network.Xmpp.Pickle to Network.Xmpp.Marshal, and removed the Network.Xmpp.Pickle module. A module imports diagram corresponding to the one of my last patch shows the new module structure. I also include a diagram showing the `Sasl' and `Concurrent' module imports.
13 years ago
{-# LANGUAGE RecordWildCards #-}
{-# OPTIONS_HADDOCK hide #-}
module Network.Xmpp.Utilities (presTo, message, answerMessage, openElementToEvents, renderOpenElement, renderElement) where
import Network.Xmpp.Types
import Control.Monad.STM
import Control.Concurrent.STM.TVar
import Prelude
Change module structure We can treat all functions related to SASL negotiation as a submodule to Pontarius XMPP if there are no dependencies from the internal Network.Xmpp modules to the SASL functionality. Because of this, `auth' and `authSimple' were moved from Session.hs to Sasl.hs. As the bind and the `{urn:ietf:params:xml:ns:xmpp-session}session' functionality are related only to the SASL negotation functionality, these functions has been moved to the SASL submodule as well. As these changes only leaves `connect' in the Session module, it seems fitting to move `connect' to Network.Xmpp.Stream (not Network.Xmpp.Connection, as `connect' depends on `startStream'). The internal Network.Xmpp modules (Connection.hs) no longer depend on the Concurrent submodule. This will decrease the coupling between Network.Xmpp and the concurrent implementation, making it easier for developers to replace the concurrent implementation if they wanted to. As Network.Xmpp.Connection is really a module that breaks the encapsulation that is Network.Xmpp and the concurrent interface, I have renamed it Network.Xmpp.Internal. As this frees up the Network.Xmpp.Connection name, Network.Xmpp.Connection_ can reclaim it. The high-level "utility" functions of Network.Xmpp.Utilities, Network.Xmpp.Presence, and Network.Xmpp.Message has been moved to Network.Xmpp.Utilities. This module contains functions that at most only depend on the internal Network.Xmpp.Types module, and doesn't belong in any other module. The functionality of Jid.hs was moved to Types.hs. Moved some of the functions of Network.Xmpp.Pickle to Network.Xmpp.Marshal, and removed the Network.Xmpp.Pickle module. A module imports diagram corresponding to the one of my last patch shows the new module structure. I also include a diagram showing the `Sasl' and `Concurrent' module imports.
13 years ago
import Data.XML.Types
import qualified Data.Attoparsec.Text as AP
import qualified Data.Text as Text
import qualified Data.ByteString as BS
import qualified Data.Text as Text
import qualified Data.Text.Encoding as Text
import System.IO.Unsafe(unsafePerformIO)
import Data.Conduit.List as CL
-- import Data.Typeable
import Control.Applicative ((<$>))
import Control.Exception
import Control.Monad.Trans.Class
import Data.Conduit as C
import Data.XML.Types
import qualified Text.XML.Stream.Render as TXSR
import Text.XML.Unresolved as TXU
-- TODO: Not used, and should probably be removed.
-- | Creates a new @IdGenerator@. Internally, it will maintain an infinite list
-- of IDs ('[\'a\', \'b\', \'c\'...]'). The argument is a prefix to prepend the
-- IDs with. Calling the function will extract an ID and update the generator's
-- internal state so that the same ID will not be generated again.
idGenerator :: Text.Text -> IO IdGenerator
idGenerator prefix = atomically $ do
tvar <- newTVar $ ids prefix
return $ IdGenerator $ next tvar
where
-- Transactionally extract the next ID from the infinite list of IDs.
next :: TVar [Text.Text] -> IO Text.Text
next tvar = atomically $ do
list <- readTVar tvar
case list of
[] -> error "empty list in Utilities.hs"
(x:xs) -> do
writeTVar tvar xs
return x
-- Generates an infinite and predictable list of IDs, all beginning with the
-- provided prefix. Adds the prefix to all combinations of IDs (ids').
ids :: Text.Text -> [Text.Text]
ids p = Prelude.map (\ id -> Text.append p id) ids'
where
-- Generate all combinations of IDs, with increasing length.
ids' :: [Text.Text]
ids' = Prelude.map Text.pack $ Prelude.concatMap ids'' [1..]
-- Generates all combinations of IDs with the given length.
ids'' :: Integer -> [String]
ids'' 0 = [""]
ids'' l = [x:xs | x <- repertoire, xs <- ids'' (l - 1)]
-- Characters allowed in IDs.
repertoire :: String
repertoire = ['a'..'z']
-- Constructs a "Version" based on the major and minor version numbers.
versionFromNumbers :: Integer -> Integer -> Version
versionFromNumbers major minor = Version major minor
Change module structure We can treat all functions related to SASL negotiation as a submodule to Pontarius XMPP if there are no dependencies from the internal Network.Xmpp modules to the SASL functionality. Because of this, `auth' and `authSimple' were moved from Session.hs to Sasl.hs. As the bind and the `{urn:ietf:params:xml:ns:xmpp-session}session' functionality are related only to the SASL negotation functionality, these functions has been moved to the SASL submodule as well. As these changes only leaves `connect' in the Session module, it seems fitting to move `connect' to Network.Xmpp.Stream (not Network.Xmpp.Connection, as `connect' depends on `startStream'). The internal Network.Xmpp modules (Connection.hs) no longer depend on the Concurrent submodule. This will decrease the coupling between Network.Xmpp and the concurrent implementation, making it easier for developers to replace the concurrent implementation if they wanted to. As Network.Xmpp.Connection is really a module that breaks the encapsulation that is Network.Xmpp and the concurrent interface, I have renamed it Network.Xmpp.Internal. As this frees up the Network.Xmpp.Connection name, Network.Xmpp.Connection_ can reclaim it. The high-level "utility" functions of Network.Xmpp.Utilities, Network.Xmpp.Presence, and Network.Xmpp.Message has been moved to Network.Xmpp.Utilities. This module contains functions that at most only depend on the internal Network.Xmpp.Types module, and doesn't belong in any other module. The functionality of Jid.hs was moved to Types.hs. Moved some of the functions of Network.Xmpp.Pickle to Network.Xmpp.Marshal, and removed the Network.Xmpp.Pickle module. A module imports diagram corresponding to the one of my last patch shows the new module structure. I also include a diagram showing the `Sasl' and `Concurrent' module imports.
13 years ago
-- | Add a recipient to a presence notification.
presTo :: Presence -> Jid -> Presence
presTo pres to = pres{presenceTo = Just to}
-- | An empty message.
message :: Message
message = Message { messageID = Nothing
, messageFrom = Nothing
, messageTo = Nothing
, messageLangTag = Nothing
, messageType = Normal
, messagePayload = []
}
-- Produce an answer message with the given payload, switching the "from" and
-- "to" attributes in the original message.
answerMessage :: Message -> [Element] -> Maybe Message
answerMessage Message{messageFrom = Just frm, ..} payload =
Just Message{ messageFrom = messageTo
, messageID = Nothing
, messageTo = Just frm
, messagePayload = payload
, ..
}
answerMessage _ _ = Nothing
openElementToEvents :: Element -> [Event]
openElementToEvents (Element name as ns) = EventBeginElement name as : goN ns []
where
goE (Element name' as' ns') =
(EventBeginElement name' as' :)
. goN ns'
. (EventEndElement name' :)
goN [] = id
goN [x] = goN' x
goN (x:xs) = goN' x . goN xs
goN' (NodeElement e) = goE e
goN' (NodeInstruction i) = (EventInstruction i :)
goN' (NodeContent c) = (EventContent c :)
goN' (NodeComment t) = (EventComment t :)
renderOpenElement :: Element -> BS.ByteString
renderOpenElement e = Text.encodeUtf8 . Text.concat . unsafePerformIO
$ CL.sourceList (openElementToEvents e) $$ TXSR.renderText def =$ CL.consume
renderElement :: Element -> BS.ByteString
renderElement e = Text.encodeUtf8 . Text.concat . unsafePerformIO
$ CL.sourceList (elementToEvents e) $$ TXSR.renderText def =$ CL.consume
where
elementToEvents :: Element -> [Event]
elementToEvents e@(Element name _ _) = openElementToEvents e ++ [EventEndElement name]