Browse Source

Remove unsuitable `Read' instance for `Jid'

The way I understand it, the `Show' and `Read' instances are for `String' representations that can be Haskell code. A proper `Show' instance of `Jid' would produce something like `Jid (Just "test") "example.com" Nothing'. A proper `Read' instance of `Jid' would parse something like that `String' value, and would stop parsing when completed.

This patch automatically derives the `Show' instance from `Jid'. It also uses the previous `Show' instance to create a pretty printer, `jidToText'. It also provides a (trivial) `jidToTexts'. As an automatically derived `Read' instance could be used to create invalid `Jid' values and affect the correctness of applications using Pontarius XMPP, such a derivation has not been included. This required some changes in the `Jid' marshalling code, which assumed a `Read' instance.

Since we provide `jidFromText', I'm assuming that no-one needs a `Read' instance of `Jid'.

Fixes #24.
master
Jon Kristensen 13 years ago
parent
commit
c534456767
  1. 2
      source/Network/Xmpp.hs
  2. 2
      source/Network/Xmpp/IM/Roster.hs
  3. 38
      source/Network/Xmpp/Marshal.hs
  4. 6
      source/Network/Xmpp/Sasl.hs
  5. 2
      source/Network/Xmpp/Stream.hs
  6. 25
      source/Network/Xmpp/Types.hs

2
source/Network/Xmpp.hs

@ -48,6 +48,8 @@ module Network.Xmpp
, isFull , isFull
, jidFromText , jidFromText
, jidFromTexts , jidFromTexts
, jidToText
, jidToTexts
, getJid , getJid
-- * Stanzas -- * Stanzas
-- | The basic protocol data unit in XMPP is the XML stanza. The stanza is -- | The basic protocol data unit in XMPP is the XML stanza. The stanza is

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

@ -164,7 +164,7 @@ xpItems = xpWrap (map (\((app_, ask_, jid_, name_, sub_), groups_) ->
(xpWrap isJust (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" xpJid)
(xpAttribute' "name" xpText) (xpAttribute' "name" xpText)
(xpAttribute' "subscription" xpPrim) (xpAttribute' "subscription" xpPrim)
) )

38
source/Network/Xmpp/Marshal.hs

@ -47,8 +47,8 @@ xpMessage = ("xpMessage" , "") <?+> xpWrap
(xp5Tuple (xp5Tuple
(xpDefault Normal $ xpAttr "type" xpPrim) (xpDefault Normal $ xpAttr "type" xpPrim)
(xpAttrImplied "id" xpPrim) (xpAttrImplied "id" xpPrim)
(xpAttrImplied "from" xpPrim) (xpAttrImplied "from" xpJid)
(xpAttrImplied "to" xpPrim) (xpAttrImplied "to" xpJid)
xpLangTag xpLangTag
-- TODO: NS? -- TODO: NS?
) )
@ -62,8 +62,8 @@ xpPresence = ("xpPresence" , "") <?+> xpWrap
(xpElem "{jabber:client}presence" (xpElem "{jabber:client}presence"
(xp5Tuple (xp5Tuple
(xpAttrImplied "id" xpPrim) (xpAttrImplied "id" xpPrim)
(xpAttrImplied "from" xpPrim) (xpAttrImplied "from" xpJid)
(xpAttrImplied "to" xpPrim) (xpAttrImplied "to" xpJid)
xpLangTag xpLangTag
(xpDefault Available $ xpAttr "type" xpPrim) (xpDefault Available $ xpAttr "type" xpPrim)
) )
@ -77,8 +77,8 @@ xpIQRequest = ("xpIQRequest" , "") <?+> xpWrap
(xpElem "{jabber:client}iq" (xpElem "{jabber:client}iq"
(xp5Tuple (xp5Tuple
(xpAttr "id" xpPrim) (xpAttr "id" xpPrim)
(xpAttrImplied "from" xpPrim) (xpAttrImplied "from" xpJid)
(xpAttrImplied "to" xpPrim) (xpAttrImplied "to" xpJid)
xpLangTag xpLangTag
((xpAttr "type" xpPrim)) ((xpAttr "type" xpPrim))
) )
@ -92,8 +92,8 @@ xpIQResult = ("xpIQResult" , "") <?+> xpWrap
(xpElem "{jabber:client}iq" (xpElem "{jabber:client}iq"
(xp5Tuple (xp5Tuple
(xpAttr "id" xpPrim) (xpAttr "id" xpPrim)
(xpAttrImplied "from" xpPrim) (xpAttrImplied "from" xpJid)
(xpAttrImplied "to" xpPrim) (xpAttrImplied "to" xpJid)
xpLangTag xpLangTag
((xpAttrFixed "type" "result")) ((xpAttrFixed "type" "result"))
) )
@ -141,8 +141,8 @@ xpMessageError = ("xpMessageError" , "") <?+> xpWrap
(xp5Tuple (xp5Tuple
(xpAttrFixed "type" "error") (xpAttrFixed "type" "error")
(xpAttrImplied "id" xpPrim) (xpAttrImplied "id" xpPrim)
(xpAttrImplied "from" xpPrim) (xpAttrImplied "from" xpJid)
(xpAttrImplied "to" xpPrim) (xpAttrImplied "to" xpJid)
(xpAttrImplied xmlLang xpPrim) (xpAttrImplied xmlLang xpPrim)
-- TODO: NS? -- TODO: NS?
) )
@ -158,8 +158,8 @@ xpPresenceError = ("xpPresenceError" , "") <?+> xpWrap
(xpElem "{jabber:client}presence" (xpElem "{jabber:client}presence"
(xp5Tuple (xp5Tuple
(xpAttrImplied "id" xpPrim) (xpAttrImplied "id" xpPrim)
(xpAttrImplied "from" xpPrim) (xpAttrImplied "from" xpJid)
(xpAttrImplied "to" xpPrim) (xpAttrImplied "to" xpJid)
xpLangTag xpLangTag
(xpAttrFixed "type" "error") (xpAttrFixed "type" "error")
) )
@ -175,8 +175,8 @@ xpIQError = ("xpIQError" , "") <?+> xpWrap
(xpElem "{jabber:client}iq" (xpElem "{jabber:client}iq"
(xp5Tuple (xp5Tuple
(xpAttr "id" xpPrim) (xpAttr "id" xpPrim)
(xpAttrImplied "from" xpPrim) (xpAttrImplied "from" xpJid)
(xpAttrImplied "to" xpPrim) (xpAttrImplied "to" xpJid)
xpLangTag xpLangTag
((xpAttrFixed "type" "error")) ((xpAttrFixed "type" "error"))
) )
@ -239,8 +239,8 @@ xpStream = xpElemAttrs
(Name "stream" (Just "http://etherx.jabber.org/streams") (Just "stream")) (Name "stream" (Just "http://etherx.jabber.org/streams") (Just "stream"))
(xp5Tuple (xp5Tuple
(xpAttr "version" xpId) (xpAttr "version" xpId)
(xpAttrImplied "from" xpPrim) (xpAttrImplied "from" xpJid)
(xpAttrImplied "to" xpPrim) (xpAttrImplied "to" xpJid)
(xpAttrImplied "id" xpId) (xpAttrImplied "id" xpId)
xpLangTag xpLangTag
) )
@ -272,3 +272,9 @@ xpStreamFeatures = ("xpStreamFeatures","") <?> xpWrap
xpElemNodes "{urn:ietf:params:xml:ns:xmpp-sasl}mechanisms" xpElemNodes "{urn:ietf:params:xml:ns:xmpp-sasl}mechanisms"
(xpAll $ xpElemNodes (xpAll $ xpElemNodes
"{urn:ietf:params:xml:ns:xmpp-sasl}mechanism" (xpContent xpId)) "{urn:ietf:params:xml:ns:xmpp-sasl}mechanism" (xpContent xpId))
xpJid :: PU Text Jid
xpJid = PU { unpickleTree = \input -> case jidFromText input of
Nothing -> UnpickleError $ ErrorMessage "Could not parse JID."
Just jid -> Result jid Nothing
, pickleTree = \input -> pack $ jidToText input }

6
source/Network/Xmpp/Sasl.hs

@ -102,7 +102,7 @@ xmppBind rsrc c = runErrorT $ do
case answer of case answer of
Right IQResult{iqResultPayload = Just b} -> do Right IQResult{iqResultPayload = Just b} -> do
lift $ debugM "Pontarius.Xmpp" "xmppBind: IQ result received; unpickling JID..." lift $ debugM "Pontarius.Xmpp" "xmppBind: IQ result received; unpickling JID..."
let jid = unpickleElem xpJid b let jid = unpickleElem xpJid' b
case jid of case jid of
Right jid' -> do Right jid' -> do
lift $ infoM "Pontarius.Xmpp" $ "Bound JID: " ++ show jid' lift $ infoM "Pontarius.Xmpp" $ "Bound JID: " ++ show jid'
@ -120,8 +120,8 @@ xmppBind rsrc c = runErrorT $ do
throwError XmppOtherFailure throwError XmppOtherFailure
where where
-- Extracts the character data in the `jid' element. -- Extracts the character data in the `jid' element.
xpJid :: PU [Node] Jid xpJid' :: PU [Node] Jid
xpJid = xpBind $ xpElemNodes jidName (xpContent xpPrim) xpJid' = xpBind $ xpElemNodes jidName (xpContent xpJid)
jidName = "{urn:ietf:params:xml:ns:xmpp-bind}jid" jidName = "{urn:ietf:params:xml:ns:xmpp-bind}jid"
-- A `bind' element pickler. -- A `bind' element pickler.

2
source/Network/Xmpp/Stream.hs

@ -200,7 +200,7 @@ startStream = runErrorT $ do
let to' = lookup "to" children let to' = lookup "to" children
ver' = lookup "version" children ver' = lookup "version" children
xl = lookup xmlLang children xl = lookup xmlLang children
in case () of () | Just (Nothing :: Maybe Jid) == (safeRead <$> to') -> in case () of () | Just Nothing == fmap jidFromText to' ->
runErrorT $ closeStreamWithError runErrorT $ closeStreamWithError
StreamBadNamespacePrefix Nothing StreamBadNamespacePrefix Nothing
"stream to not a valid JID" "stream to not a valid JID"

25
source/Network/Xmpp/Types.hs

@ -47,6 +47,8 @@ module Network.Xmpp.Types
, isFull , isFull
, jidFromText , jidFromText
, jidFromTexts , jidFromTexts
, jidToText
, jidToTexts
, StreamEnd(..) , StreamEnd(..)
, InvalidXmppXml(..) , InvalidXmppXml(..)
, SessionConfiguration(..) , SessionConfiguration(..)
@ -886,17 +888,18 @@ data Jid = Jid { -- | The @localpart@ of a JID is an optional identifier placed
-- the entity associated with an XMPP localpart at a domain -- the entity associated with an XMPP localpart at a domain
-- (i.e., @localpart\@domainpart/resourcepart@). -- (i.e., @localpart\@domainpart/resourcepart@).
, resourcepart :: !(Maybe Text) , resourcepart :: !(Maybe Text)
} deriving (Eq, Ord) } deriving (Eq, Ord, Show) -- A `Read' instance must validate.
instance Show Jid where -- | Converts a JID to a Text.
show (Jid nd dmn res) = jidToText :: Jid -> String
maybe "" ((++ "@") . Text.unpack) nd ++ Text.unpack dmn ++ jidToText (Jid nd dmn res) =
maybe "" (('/' :) . Text.unpack) res (maybe "" ((++ "@") . Text.unpack) nd) ++ (Text.unpack dmn) ++
maybe "" (('/' :) . Text.unpack) res
instance Read Jid where
readsPrec _ x = case jidFromText (Text.pack x) of -- | Converts a JID to up to three Text values: (the optional) localpart, the
Nothing -> [] -- domainpart, and (the optional) resourcepart.
Just j -> [(j,"")] jidToTexts :: Jid -> (Maybe Text, Text, Maybe Text)
jidToTexts (Jid nd dmn res) = (nd, dmn, res)
instance IsString Jid where instance IsString Jid where
fromString = fromJust . jidFromText . Text.pack fromString = fromJust . jidFromText . Text.pack

Loading…
Cancel
Save