Browse Source

Improve RFC 6121 (XMPP-IM) code.

Move the functionality from Network.Xmpp.IM.Message and *.Presence to Network.Xmpp.Stanza since it is not specific to RFC 6121.
Implement presence functionality of RFC 6121
Fix hslint errors and warning
master
Philipp Balzarek 13 years ago
parent
commit
570cdafd43
  1. 12
      pontarius-xmpp.cabal
  2. 10
      source/Network/Xmpp.hs
  3. 23
      source/Network/Xmpp/IM.hs
  4. 183
      source/Network/Xmpp/IM/Message.hs
  5. 113
      source/Network/Xmpp/IM/Presence.hs
  6. 52
      source/Network/Xmpp/IM/Roster.hs
  7. 76
      source/Network/Xmpp/Stanza.hs
  8. 39
      source/Network/Xmpp/Utilities.hs

12
pontarius-xmpp.cabal

@ -61,15 +61,20 @@ Library
, xml-conduit >=1.0 , xml-conduit >=1.0
, xml-picklers >=0.3.2 , xml-picklers >=0.3.2
Exposed-modules: Network.Xmpp Exposed-modules: Network.Xmpp
, Network.Xmpp.IM
, Network.Xmpp.Internal , Network.Xmpp.Internal
Other-modules: Network.Xmpp.Concurrent Other-modules: Network.Xmpp.Concurrent
, Network.Xmpp.Concurrent.Types
, Network.Xmpp.Concurrent.Basic , Network.Xmpp.Concurrent.Basic
, Network.Xmpp.Concurrent.IQ , Network.Xmpp.Concurrent.IQ
, Network.Xmpp.Concurrent.Message , Network.Xmpp.Concurrent.Message
, Network.Xmpp.Concurrent.Monad
, Network.Xmpp.Concurrent.Presence , Network.Xmpp.Concurrent.Presence
, Network.Xmpp.Concurrent.Threads , Network.Xmpp.Concurrent.Threads
, Network.Xmpp.Concurrent.Monad , Network.Xmpp.Concurrent.Types
, Network.Xmpp.IM.Message
, Network.Xmpp.IM.Presence
, Network.Xmpp.IM.Roster
, Network.Xmpp.IM.Roster.Types
, Network.Xmpp.Marshal , Network.Xmpp.Marshal
, Network.Xmpp.Sasl , Network.Xmpp.Sasl
, Network.Xmpp.Sasl.Common , Network.Xmpp.Sasl.Common
@ -79,12 +84,11 @@ Library
, Network.Xmpp.Sasl.Mechanisms.Scram , Network.Xmpp.Sasl.Mechanisms.Scram
, Network.Xmpp.Sasl.StringPrep , Network.Xmpp.Sasl.StringPrep
, Network.Xmpp.Sasl.Types , Network.Xmpp.Sasl.Types
, Network.Xmpp.Stanza
, Network.Xmpp.Stream , Network.Xmpp.Stream
, Network.Xmpp.Tls , Network.Xmpp.Tls
, Network.Xmpp.Types , Network.Xmpp.Types
, Network.Xmpp.Utilities , Network.Xmpp.Utilities
, Network.Xmpp.IM.Roster
, Network.Xmpp.IM.Roster.Types
GHC-Options: -Wall GHC-Options: -Wall
Source-Repository head Source-Repository head

10
source/Network/Xmpp.hs

@ -82,6 +82,7 @@ module Network.Xmpp
-- occur in a system such as email. It is not to be confused with -- occur in a system such as email. It is not to be confused with
-- /instant messaging/ which is handled in the 'Network.Xmpp.IM' module -- /instant messaging/ which is handled in the 'Network.Xmpp.IM' module
, Message(..) , Message(..)
, message
, MessageError(..) , MessageError(..)
, MessageType(..) , MessageType(..)
-- *** Creating -- *** Creating
@ -103,6 +104,12 @@ module Network.Xmpp
, PresenceType(..) , PresenceType(..)
, PresenceError(..) , PresenceError(..)
-- *** Creating -- *** Creating
, presence
, presenceOffline
, presenceOnline
, presenceSubscribe
, presenceSubscribed
, presenceUnsubscribe
, presTo , presTo
-- *** Sending -- *** Sending
-- | Sends a presence stanza. In general, the presence stanza should have no -- | Sends a presence stanza. In general, the presence stanza should have no
@ -157,7 +164,8 @@ module Network.Xmpp
) where ) where
import Network.Xmpp.Concurrent import Network.Xmpp.Concurrent
import Network.Xmpp.Utilities
import Network.Xmpp.Sasl import Network.Xmpp.Sasl
import Network.Xmpp.Sasl.Types import Network.Xmpp.Sasl.Types
import Network.Xmpp.Stanza
import Network.Xmpp.Types import Network.Xmpp.Types
import Network.Xmpp.Utilities

23
source/Network/Xmpp/IM.hs

@ -1,14 +1,19 @@
-- | RFC 6121: Instant Messaging and Presence
--
module Network.Xmpp.IM module Network.Xmpp.IM
( -- * Instant Messages ( -- * Instant Messages
subject MessageBody(..)
, thread , MessageThread(..)
, body , MessageSubject(..)
, bodies , instantMessage
, newIM , getIM
, simpleIM , withIM
, answerIM -- * Presence
-- * Presence , ShowStatus(..)
, module Network.Xmpp.IM.Presence , IMPresence(..)
, imPresence
, getIMPresence
, withIMPresence
-- * Roster -- * Roster
, Roster(..) , Roster(..)
, Item(..) , Item(..)

183
source/Network/Xmpp/IM/Message.hs

@ -1,119 +1,64 @@
{-# LANGUAGE OverloadedStrings #-} {-# LANGUAGE OverloadedStrings #-}
{-# OPTIONS_HADDOCK hide #-} {-# OPTIONS_HADDOCK hide #-}
module Network.Xmpp.IM.Message module Network.Xmpp.IM.Message where
where
import Control.Applicative ((<$>))
import Data.Maybe (maybeToList, listToMaybe)
import Data.Text (Text) import Data.Text (Text)
import Data.XML.Pickle import Data.XML.Pickle
import Data.XML.Types import Data.XML.Types
import Network.Xmpp.Marshal import Network.Xmpp.Marshal
import Network.Xmpp.Types import Network.Xmpp.Types
import Network.Xmpp.Stanza
import Data.List
import Data.Function
data MessageBody = MessageBody { bodyLang :: (Maybe LangTag) data MessageBody = MessageBody { bodyLang :: Maybe LangTag
, bodyContent :: Text , bodyContent :: Text
} }
data MessageThread = MessageThread { theadID :: Text data MessageThread = MessageThread { theadID :: Text
, threadParent :: (Maybe Text) , threadParent :: Maybe Text
} }
data MessageSubject = MessageSubject { subjectLang :: (Maybe LangTag) data MessageSubject = MessageSubject { subjectLang :: Maybe LangTag
, subjectContent :: Text , subjectContent :: Text
} }
xpMessageSubject :: PU [Element] MessageSubject -- | The instant message (IM) specific part of a message.
xpMessageSubject = xpUnliftElems . data InstantMessage = InstantMessage { imThread :: Maybe MessageThread
xpWrap (\(l, s) -> MessageSubject l s) , imSubject :: [MessageSubject]
(\(MessageSubject l s) -> (l,s)) , imBody :: [MessageBody]
$ xpElem "{jabber:client}subject" xpLangTag $ xpContent xpId }
xpMessageBody :: PU [Element] MessageBody instantMessage :: InstantMessage
xpMessageBody = xpUnliftElems . instantMessage = InstantMessage { imThread = Nothing
xpWrap (\(l, s) -> MessageBody l s) , imSubject = []
(\(MessageBody l s) -> (l,s)) , imBody = []
$ xpElem "{jabber:client}body" xpLangTag $ xpContent xpId }
xpMessageThread :: PU [Element] MessageThread -- | Get the IM specific parts of a message. Returns 'Nothing' when the received
xpMessageThread = xpUnliftElems -- payload is not valid IM data.
. xpWrap (\(t, p) -> MessageThread p t) getIM :: Message -> Maybe InstantMessage
(\(MessageThread p t) -> (t,p)) getIM im = either (const Nothing) Just . unpickle xpIM $ messagePayload im
$ xpElem "{jabber:client}thread"
(xpAttrImplied "parent" xpId)
(xpContent xpId)
-- | Get the subject elements of a message (if any). Messages may sanitizeIM :: InstantMessage -> InstantMessage
-- contain multiple subjects if each of them has a distinct xml:lang sanitizeIM im = im{imBody = nubBy ((==) `on` bodyLang) $ imBody im}
-- attribute
subject :: Message -> [MessageSubject] -- | Append IM data to a message
subject m = ms withIM :: Message -> InstantMessage -> Message
where withIM m im = m{ messagePayload = messagePayload m
-- xpFindMatches will _always_ return Right ++ pickleTree xpIM (sanitizeIM im) }
Right ms = unpickle (xpFindMatches xpMessageSubject) $ messagePayload m
imToElements :: InstantMessage -> [Element]
-- | Get the thread elements of a message (if any). The thread of a imToElements im = pickle xpIM (sanitizeIM im)
-- message is considered opaque, that is, no meaning, other than it's
-- literal identity, may be derived from it and it is not human
-- readable
thread :: Message -> Maybe MessageThread
thread m = ms
where
-- xpFindMatches will _always_ return Right
Right ms = unpickle (xpOption xpMessageThread) $ messagePayload m
-- | Get the body elements of a message (if any). Messages may contain
-- multiple bodies if each of them has a distinct xml:lang attribute
bodies :: Message -> [MessageBody]
bodies m = ms
where
-- xpFindMatches will _always_ return Right
Right ms = unpickle (xpFindMatches xpMessageBody) $ messagePayload m
-- | Return the first body element, regardless of it's language.
body :: Message -> Maybe Text
body m = bodyContent <$> listToMaybe (bodies m)
-- | Generate a new instant message
newIM
:: Jid
-> Maybe StanzaID
-> Maybe LangTag
-> MessageType
-> Maybe MessageSubject
-> Maybe MessageThread
-> Maybe MessageBody
-> [Element]
-> Message
newIM t i lang tp sbj thrd bdy payload = Message
{ messageID = i
, messageFrom = Nothing
, messageTo = Just t
, messageLangTag = lang
, messageType = tp
, messagePayload = concat $
maybeToList (pickle xpMessageSubject <$> sbj)
++ maybeToList (pickle xpMessageThread <$> thrd)
++ maybeToList (pickle xpMessageBody <$> bdy)
++ [payload]
}
-- | Generate a simple message -- | Generate a simple message
simpleIM :: Jid -- ^ recipient simpleIM :: Jid -- ^ recipient
-> Text -- ^ body -> Text -- ^ body
-> Message -> Message
simpleIM t bd = newIM simpleIM to bd = withIM message{messageTo = Just to}
t instantMessage{imBody = [MessageBody Nothing bd]}
Nothing
Nothing
Normal
Nothing
Nothing
(Just $ MessageBody Nothing bd)
[]
-- | Generate an answer from a received message. The recepient is -- | Generate an answer from a received message. The recepient is
-- taken from the original sender, the sender is set to Nothing, -- taken from the original sender, the sender is set to Nothing,
@ -121,17 +66,47 @@ simpleIM t bd = newIM
-- thread are inherited, the remaining payload is replaced by the -- thread are inherited, the remaining payload is replaced by the
-- given one. -- given one.
-- --
-- If multiple message bodies are given they must have different language tags -- If multiple message bodies are given they MUST have different language tags
answerIM :: [MessageBody] -> [Element] -> Message -> Message answerIM :: [MessageBody] -> Message -> Maybe Message
answerIM bd payload msg = Message answerIM bd msg = case getIM msg of
{ messageID = messageID msg Nothing -> Nothing
, messageFrom = Nothing Just im -> Just $ flip withIM (im{imBody = bd}) $
, messageTo = messageFrom msg message { messageID = messageID msg
, messageLangTag = messageLangTag msg , messageFrom = Nothing
, messageType = messageType msg , messageTo = messageFrom msg
, messagePayload = concat $ , messageLangTag = messageLangTag msg
(pickle xpMessageSubject <$> subject msg) , messageType = messageType msg
++ maybeToList (pickle xpMessageThread <$> thread msg) }
++ (pickle xpMessageBody <$> bd)
++ [payload] --------------------------
} -- Picklers --------------
--------------------------
xpIM :: PU [Element] InstantMessage
xpIM = xpWrap (\(t, s, b) -> InstantMessage t s b)
(\(InstantMessage t s b) -> (t, s, b)) $
xp3Tuple
xpMessageThread
xpMessageSubject
xpMessageBody
xpMessageSubject :: PU [Element] [MessageSubject]
xpMessageSubject = xpUnliftElems .
xpWrap (map $ \(l, s) -> MessageSubject l s)
(map $ \(MessageSubject l s) -> (l,s))
$ xpElems "{jabber:client}subject" xpLangTag $ xpContent xpId
xpMessageBody :: PU [Element] [MessageBody]
xpMessageBody = xpUnliftElems .
xpWrap (map $ \(l, s) -> MessageBody l s)
(map $ \(MessageBody l s) -> (l,s))
$ xpElems "{jabber:client}body" xpLangTag $ xpContent xpId
xpMessageThread :: PU [Element] (Maybe MessageThread)
xpMessageThread = xpUnliftElems
. xpOption
. xpWrap (\(t, p) -> MessageThread p t)
(\(MessageThread p t) -> (t,p))
$ xpElem "{jabber:client}thread"
(xpAttrImplied "parent" xpId)
(xpContent xpId)

113
source/Network/Xmpp/IM/Presence.hs

@ -1,75 +1,66 @@
{-# OPTIONS_HADDOCK hide #-} {-# OPTIONS_HADDOCK hide #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE NoMonomorphismRestriction #-}
module Network.Xmpp.IM.Presence where module Network.Xmpp.IM.Presence where
import Network.Xmpp.Types import Data.Text (Text)
import Data.XML.Pickle
import Data.XML.Types
import Network.Xmpp.Types
-- | An empty presence. data ShowStatus = StatusAway
presence :: Presence | StatusChat
presence = Presence { presenceID = Nothing | StatusDnd
, presenceFrom = Nothing | StatusXa
, presenceTo = Nothing
, presenceLangTag = Nothing
, presenceType = Nothing
, presencePayload = []
}
-- | Request subscription with an entity. instance Show ShowStatus where
presenceSubscribe :: Jid -> Presence show StatusAway = "away"
presenceSubscribe to = presence { presenceTo = Just to show StatusChat = "chat"
, presenceType = Just Subscribe show StatusDnd = "dnd"
} show StatusXa = "xa"
-- | Is presence a subscription request? instance Read ShowStatus where
isPresenceSubscribe :: Presence -> Bool readsPrec _ "away" = [(StatusAway, "")]
isPresenceSubscribe pres = presenceType pres == (Just Subscribe) readsPrec _ "chat" = [(StatusChat, "")]
readsPrec _ "dnd" = [(StatusDnd , "")]
readsPrec _ "xa" = [(StatusXa , "")]
readsPrec _ _ = []
-- | Approve a subscripton of an entity. data IMPresence = IMP { showStatus :: Maybe ShowStatus
presenceSubscribed :: Jid -> Presence , status :: Maybe Text
presenceSubscribed to = presence { presenceTo = Just to , priority :: Maybe Int
, presenceType = Just Subscribed }
}
-- | Is presence a subscription approval? imPresence :: IMPresence
isPresenceSubscribed :: Presence -> Bool imPresence = IMP { showStatus = Nothing
isPresenceSubscribed pres = presenceType pres == (Just Subscribed) , status = Nothing
, priority = Nothing
}
-- | End a subscription with an entity.
presenceUnsubscribe :: Jid -> Presence
presenceUnsubscribe to = presence { presenceTo = Just to
, presenceType = Just Unsubscribed
}
-- | Is presence an unsubscription request? getIMPresence :: Presence -> Maybe IMPresence
isPresenceUnsubscribe :: Presence -> Bool getIMPresence pres = case unpickle xpIMPresence (presencePayload pres) of
isPresenceUnsubscribe pres = presenceType pres == (Just Unsubscribe) Left _ -> Nothing
Right r -> Just r
-- | Signal to the server that the client is available for communication. withIMPresence :: IMPresence -> Presence -> Presence
presenceOnline :: Presence withIMPresence imPres pres = pres{presencePayload = presencePayload pres
presenceOnline = presence ++ pickleTree xpIMPresence
imPres}
-- | Signal to the server that the client is no longer available for --
-- communication. -- Picklers
presenceOffline :: Presence --
presenceOffline = presence {presenceType = Just Unavailable}
---- Change your status xpIMPresence :: PU [Element] IMPresence
--status xpIMPresence = xpUnliftElems $
-- :: Maybe Text -- ^ Status message xpWrap (\(s, st, p) -> IMP s st p)
-- -> Maybe ShowType -- ^ Status Type (\(IMP s st p) -> (s, st, p)) $
-- -> Maybe Int -- ^ Priority xp3Tuple
-- -> Presence (xpOption $ xpElemNodes "{jabber:client}show"
--status txt showType prio = presence { presenceShowType = showType (xpContent xpPrim))
-- , presencePriority = prio (xpOption $ xpElemNodes "{jabber:client}status"
-- , presenceStatus = txt (xpContent xpText))
-- } (xpOption $ xpElemNodes "{jabber:client}priority"
(xpContent xpPrim))
-- | Set the current availability status. This implicitly sets the client's
-- status online.
--presenceAvail :: ShowType -> Presence
--presenceAvail showType = status Nothing (Just showType) Nothing
-- | Set the current status message. This implicitly sets the client's status
-- online.
--presenceMessage :: Text -> Presence
--presenceMessage txt = status (Just txt) Nothing Nothing

52
source/Network/Xmpp/IM/Roster.hs

@ -1,5 +1,4 @@
{-# OPTIONS_HADDOCK hide #-} {-# OPTIONS_HADDOCK hide #-}
{-# LANGUAGE PatternGuards #-}
{-# LANGUAGE NoMonomorphismRestriction #-} {-# LANGUAGE NoMonomorphismRestriction #-}
{-# LANGUAGE OverloadedStrings #-} {-# LANGUAGE OverloadedStrings #-}
@ -9,7 +8,7 @@ import Control.Concurrent.STM
import Control.Monad import Control.Monad
import Data.List (nub) import Data.List (nub)
import qualified Data.Map.Strict as Map import qualified Data.Map.Strict as Map
import Data.Maybe (isJust) import Data.Maybe (isJust, fromMaybe)
import Data.Text (Text) import Data.Text (Text)
import Data.XML.Pickle import Data.XML.Pickle
import Data.XML.Types import Data.XML.Types
@ -60,9 +59,11 @@ rosterRemove j sess = do
IQResponseResult IQResult{} -> return True IQResponseResult IQResult{} -> return True
_ -> return False _ -> return False
-- | Retrieve the current Roster state
getRoster :: Session -> IO Roster getRoster :: Session -> IO Roster
getRoster session = atomically $ readTVar (rosterRef session) getRoster session = atomically $ readTVar (rosterRef session)
-- | Get the initial roster / refresh the roster. You don't need to call this on your own
initRoster :: Session -> IO () initRoster :: Session -> IO ()
initRoster session = do initRoster session = do
oldRoster <- getRoster session oldRoster <- getRoster session
@ -74,26 +75,25 @@ initRoster session = do
Just roster -> atomically $ writeTVar (rosterRef session) roster Just roster -> atomically $ writeTVar (rosterRef session) roster
handleRoster :: TVar Roster -> TChan Stanza -> Stanza -> IO Bool handleRoster :: TVar Roster -> TChan Stanza -> Stanza -> IO Bool
handleRoster ref outC sta = do handleRoster ref outC sta = case sta of
case sta of IQRequestS (iqr@IQRequest{iqRequestPayload =
IQRequestS (iqr@IQRequest{iqRequestPayload = iqb@Element{elementName = en}})
iqb@Element{elementName = en}}) | nameNamespace en == Just "jabber:iq:roster" -> do
| nameNamespace en == Just "jabber:iq:roster" -> do case iqRequestFrom iqr of
case iqRequestFrom iqr of Just _from -> return True -- Don't handle roster pushes from
Just _from -> return True -- Don't handle roster pushes from -- unauthorized sources
-- unauthorized sources Nothing -> case unpickleElem xpQuery iqb of
Nothing -> case unpickleElem xpQuery iqb of Right Query{ queryVer = v
Right Query{ queryVer = v , queryItems = [update]
, queryItems = [update] } -> do
} -> do handleUpdate v update
handleUpdate v update atomically . writeTChan outC $ result iqr
atomically . writeTChan outC $ result iqr return False
return False _ -> do
_ -> do errorM "Pontarius.Xmpp" "Invalid roster query"
errorM "Pontarius.Xmpp" "Invalid roster query" atomically . writeTChan outC $ badRequest iqr
atomically . writeTChan outC $ badRequest iqr return False
return False _ -> return True
_ -> return True
where where
handleUpdate v' update = atomically $ modifyTVar ref $ \(Roster v is) -> handleUpdate v' update = atomically $ modifyTVar ref $ \(Roster v is) ->
Roster (v' `mplus` v) $ case qiSubscription update of Roster (v' `mplus` v) $ case qiSubscription update of
@ -119,7 +119,7 @@ retrieveRoster oldRoster sess = do
return Nothing return Nothing
Right ros' -> return . Just $ toRoster ros' Right ros' -> return . Just $ toRoster ros'
IQResponseResult (IQResult{iqResultPayload = Nothing}) -> do IQResponseResult (IQResult{iqResultPayload = Nothing}) -> do
return $ oldRoster return oldRoster
-- sever indicated that no roster updates are necessary -- sever indicated that no roster updates are necessary
IQResponseTimeout -> do IQResponseTimeout -> do
errorM "Pontarius.Xmpp.Roster" "getRoster: request timed out" errorM "Pontarius.Xmpp.Roster" "getRoster: request timed out"
@ -134,11 +134,11 @@ retrieveRoster oldRoster sess = do
is) is)
toItem :: QueryItem -> Item toItem :: QueryItem -> Item
toItem qi = Item { approved = maybe False id (qiApproved qi) toItem qi = Item { approved = fromMaybe False (qiApproved qi)
, ask = qiAsk qi , ask = qiAsk qi
, jid = qiJid qi , jid = qiJid qi
, name = qiName qi , name = qiName qi
, subscription = maybe None id (qiSubscription qi) , subscription = fromMaybe None (qiSubscription qi)
, groups = nub $ qiGroups qi , groups = nub $ qiGroups qi
} }
@ -161,7 +161,7 @@ xpItems = xpWrap (map (\((app_, ask_, jid_, name_, sub_), groups_) ->
xpElems "{jabber:iq:roster}item" xpElems "{jabber:iq:roster}item"
(xp5Tuple (xp5Tuple
(xpAttribute' "approved" xpBool) (xpAttribute' "approved" xpBool)
(xpWrap (maybe False (const True)) (xpWrap isJust
(\p -> if p then Just () else Nothing) $ (\p -> if p then Just () else Nothing) $
xpOption $ xpAttribute_ "ask" "subscribe") xpOption $ xpAttribute_ "ask" "subscribe")
(xpAttribute "jid" xpPrim) (xpAttribute "jid" xpPrim)

76
source/Network/Xmpp/Stanza.hs

@ -0,0 +1,76 @@
{-# LANGUAGE RecordWildCards #-}
{-# OPTIONS_HADDOCK hide #-}
-- | Stanza related functions and constants
--
module Network.Xmpp.Stanza where
import Data.XML.Types
import Network.Xmpp.Types
-- | An empty message
message :: Message
message = Message { messageID = Nothing
, messageFrom = Nothing
, messageTo = Nothing
, messageLangTag = Nothing
, messageType = Normal
, messagePayload = []
}
-- | An empty presence.
presence :: Presence
presence = Presence { presenceID = Nothing
, presenceFrom = Nothing
, presenceTo = Nothing
, presenceLangTag = Nothing
, presenceType = Nothing
, presencePayload = []
}
-- | Request subscription with an entity.
presenceSubscribe :: Jid -> Presence
presenceSubscribe to = presence { presenceTo = Just to
, presenceType = Just Subscribe
}
-- | Approve a subscripton of an entity.
presenceSubscribed :: Jid -> Presence
presenceSubscribed to = presence { presenceTo = Just to
, presenceType = Just Subscribed
}
-- | End a subscription with an entity.
presenceUnsubscribe :: Jid -> Presence
presenceUnsubscribe to = presence { presenceTo = Just to
, presenceType = Just Unsubscribed
}
-- | Signal to the server that the client is available for communication.
presenceOnline :: Presence
presenceOnline = presence
-- | Signal to the server that the client is no longer available for
-- communication.
presenceOffline :: Presence
presenceOffline = presence {presenceType = Just Unavailable}
-- | Produce an answer message with the given payload, switching the "from" and
-- "to" attributes in the original message. Produces a 'Nothing' value of the
-- provided message message has no from attribute.
answerMessage :: Message -> [Element] -> Maybe Message
answerMessage Message{messageFrom = Just frm, ..} payload =
Just Message{ messageFrom = messageTo
, messageID = Nothing
, messageTo = Just frm
, messagePayload = payload
, ..
}
answerMessage _ _ = Nothing
-- | Add a recipient to a presence notification.
presTo :: Presence -> Jid -> Presence
presTo pres to = pres{presenceTo = Just to}

39
source/Network/Xmpp/Utilities.hs

@ -1,13 +1,10 @@
{-# LANGUAGE OverloadedStrings #-} {-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE RecordWildCards #-} {-# LANGUAGE RecordWildCards #-}
{-# OPTIONS_HADDOCK hide #-}
module Network.Xmpp.Utilities module Network.Xmpp.Utilities
( presTo ( openElementToEvents
, message
, answerMessage
, openElementToEvents
, renderOpenElement , renderOpenElement
, renderElement , renderElement
, checkHostName , checkHostName
@ -23,39 +20,11 @@ import qualified Data.Text as Text
import Data.Text(Text) import Data.Text(Text)
import qualified Data.Text.Encoding as Text import qualified Data.Text.Encoding as Text
import Data.XML.Types import Data.XML.Types
import Network.Xmpp.Types
import Prelude import Prelude
import System.IO.Unsafe(unsafePerformIO) import System.IO.Unsafe(unsafePerformIO)
import qualified Text.XML.Stream.Render as TXSR import qualified Text.XML.Stream.Render as TXSR
import Text.XML.Unresolved as TXU import Text.XML.Unresolved as TXU
-- | 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. Produces a 'Nothing' value of the
-- provided message message has no from attribute.
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 -> [Event]
openElementToEvents (Element name as ns) = EventBeginElement name as : goN ns [] openElementToEvents (Element name as ns) = EventBeginElement name as : goN ns []
where where
@ -85,7 +54,7 @@ renderElement e = Text.encodeUtf8 . Text.concat . unsafePerformIO
-- | Validates the hostname string in accordance with RFC 1123. -- | Validates the hostname string in accordance with RFC 1123.
checkHostName :: Text -> Maybe Text checkHostName :: Text -> Maybe Text
checkHostName t = do checkHostName t =
eitherToMaybeHostName $ AP.parseOnly hostnameP t eitherToMaybeHostName $ AP.parseOnly hostnameP t
where where
eitherToMaybeHostName = either (const Nothing) Just eitherToMaybeHostName = either (const Nothing) Just
@ -105,6 +74,6 @@ hostnameP = do
<|> do <|> do
_ <- AP.satisfy (== '.') _ <- AP.satisfy (== '.')
r <- hostnameP r <- hostnameP
if (Text.length label) + 1 + (Text.length r) > 255 if Text.length label + 1 + Text.length r > 255
then fail "Hostname too long." then fail "Hostname too long."
else return $ Text.concat [label, Text.pack ".", r] else return $ Text.concat [label, Text.pack ".", r]

Loading…
Cancel
Save