Browse Source

minor formatting and documentation changes

master
Jon Kristensen 14 years ago
parent
commit
ff87c3a290
  1. 33
      src/Network/XMPP/Message.hs
  2. 30
      src/Network/XMPP/Presence.hs

33
src/Network/XMPP/Message.hs

@ -1,20 +1,19 @@
{-# LANGUAGE RecordWildCards #-} {-# LANGUAGE RecordWildCards #-}
-- | Message handling
module Network.XMPP.Message module Network.XMPP.Message
( Message(..) ( Message(..)
, MessageType(..)
, MessageError(..) , MessageError(..)
, message , MessageType(..)
, answerMessage , answerMessage
) , message
where ) where
import Data.Text(Text) import Data.Text (Text)
import Data.XML.Types import Data.XML.Types
import Network.XMPP.Types import Network.XMPP.Types
-- The empty message -- | An empty message.
message :: Message message :: Message
message = Message { messageID = Nothing message = Message { messageID = Nothing
, messageFrom = Nothing , messageFrom = Nothing
@ -24,22 +23,14 @@ message = Message { messageID = Nothing
, messagePayload = [] , messagePayload = []
} }
-- Produce an answer message with the given payload, switching the "from" and
---- | Create simple message, containing nothing but a body text -- "to" attributes in the original message.
--simpleMessage :: JID -- ^ Recipient answerMessage :: Message -> [Element] -> Maybe Message
-- -> Text -- ^ Myssage body answerMessage Message{messageFrom = Just frm, ..} payload =
-- -> Message Just Message{ messageFrom = messageTo
--simpleMessage to txt = message { messageTo = Just to
-- , messageBody = Just txt
-- }
answerMessage :: Message -> Text -> [Element] -> Maybe Message
answerMessage Message{messageFrom = Just frm, ..} txt payload =
Just $ Message{ messageFrom = messageTo
, messageID = Nothing , messageID = Nothing
, messageTo = Just frm , messageTo = Just frm
, messagePayload = payload , messagePayload = payload
, .. , ..
} }
answerMessage _ _ _ = Nothing answerMessage _ _ = Nothing

30
src/Network/XMPP/Presence.hs

@ -1,10 +1,11 @@
{-# OPTIONS_HADDOCK hide #-} {-# OPTIONS_HADDOCK hide #-}
module Network.XMPP.Presence where module Network.XMPP.Presence where
import Data.Text(Text) import Data.Text(Text)
import Network.XMPP.Types import Network.XMPP.Types
-- | The empty presence. -- | An empty presence.
presence :: Presence presence :: Presence
presence = Presence { presenceID = Nothing presence = Presence { presenceID = Nothing
, presenceFrom = Nothing , presenceFrom = Nothing
@ -14,41 +15,42 @@ presence = Presence { presenceID = Nothing
, presencePayload = [] , presencePayload = []
} }
-- | Request subscription with an entity -- | Request subscription with an entity.
presenceSubscribe :: JID -> Presence presenceSubscribe :: JID -> Presence
presenceSubscribe to = presence { presenceTo = Just to presenceSubscribe to = presence { presenceTo = Just to
, presenceType = Just Subscribe , presenceType = Just Subscribe
} }
-- | Is presence a subscription request -- | Is presence a subscription request?
isPresenceSubscribe :: Presence -> Bool isPresenceSubscribe :: Presence -> Bool
isPresenceSubscribe pres = presenceType pres == (Just Subscribe) isPresenceSubscribe pres = presenceType pres == (Just Subscribe)
-- | Approve a subscripton of an entity -- | Approve a subscripton of an entity.
presenceSubscribed :: JID -> Presence presenceSubscribed :: JID -> Presence
presenceSubscribed to = presence { presenceTo = Just to presenceSubscribed to = presence { presenceTo = Just to
, presenceType = Just Subscribed , presenceType = Just Subscribed
} }
-- | Is presence a subscription approval -- | Is presence a subscription approval?
isPresenceSubscribed :: Presence -> Bool isPresenceSubscribed :: Presence -> Bool
isPresenceSubscribed pres = presenceType pres == (Just Subscribed) isPresenceSubscribed pres = presenceType pres == (Just Subscribed)
-- | End a subscription with an entity -- | End a subscription with an entity.
presenceUnsubscribe :: JID -> Presence presenceUnsubscribe :: JID -> Presence
presenceUnsubscribe to = presence { presenceTo = Just to presenceUnsubscribe to = presence { presenceTo = Just to
, presenceType = Just Unsubscribed , presenceType = Just Unsubscribed
} }
-- | Is presence an unsubscription request -- | Is presence an unsubscription request?
isPresenceUnsubscribe :: Presence -> Bool isPresenceUnsubscribe :: Presence -> Bool
isPresenceUnsubscribe pres = presenceType pres == (Just Unsubscribe) isPresenceUnsubscribe pres = presenceType pres == (Just Unsubscribe)
-- | Signal to the server that the client is available for communication -- | Signal to the server that the client is available for communication.
presenceOnline :: Presence presenceOnline :: Presence
presenceOnline = presence presenceOnline = presence
-- | Signal to the server that the client is no longer available for communication. -- | Signal to the server that the client is no longer available for
-- communication.
presenceOffline :: Presence presenceOffline :: Presence
presenceOffline = presence {presenceType = Just Unavailable} presenceOffline = presence {presenceType = Just Unavailable}
@ -63,16 +65,16 @@ presenceOffline = presence {presenceType = Just Unavailable}
-- , presenceStatus = txt -- , presenceStatus = txt
-- } -- }
-- | Set the current availability status. This implicitly sets the clients -- | Set the current availability status. This implicitly sets the client's
-- status online -- status online.
--presenceAvail :: ShowType -> Presence --presenceAvail :: ShowType -> Presence
--presenceAvail showType = status Nothing (Just showType) Nothing --presenceAvail showType = status Nothing (Just showType) Nothing
-- | Set the current status message. This implicitly sets the clients -- | Set the current status message. This implicitly sets the client's status
-- status online -- online.
--presenceMessage :: Text -> Presence --presenceMessage :: Text -> Presence
--presenceMessage txt = status (Just txt) Nothing Nothing --presenceMessage txt = status (Just txt) Nothing Nothing
-- | Add a recipient to a presence notification -- | Add a recipient to a presence notification.
presTo :: Presence -> JID -> Presence presTo :: Presence -> JID -> Presence
presTo pres to = pres{presenceTo = Just to} presTo pres to = pres{presenceTo = Just to}
Loading…
Cancel
Save