Browse Source

Merge branch 'master' of git://github.com/Philonous/pontarius

master
Jon Kristensen 13 years ago
parent
commit
4f4aae4b0f
  1. 11
      source/Network/Xmpp/Marshal.hs
  2. 52
      source/Network/Xmpp/Stream.hs

11
source/Network/Xmpp/Marshal.hs

@ -247,7 +247,7 @@ xpStream = xpElemAttrs
-- Pickler/Unpickler for the stream features - TLS, SASL, and the rest. -- Pickler/Unpickler for the stream features - TLS, SASL, and the rest.
xpStreamFeatures :: PU [Node] StreamFeatures xpStreamFeatures :: PU [Node] StreamFeatures
xpStreamFeatures = xpWrap xpStreamFeatures = ("xpStreamFeatures","") <?> xpWrap
(\(tls, sasl, rest) -> StreamFeatures tls (mbl sasl) rest) (\(tls, sasl, rest) -> StreamFeatures tls (mbl sasl) rest)
(\(StreamFeatures tls sasl rest) -> (tls, lmb sasl, rest)) (\(StreamFeatures tls sasl rest) -> (tls, lmb sasl, rest))
(xpElemNodes (xpElemNodes
@ -264,10 +264,11 @@ xpStreamFeatures = xpWrap
) )
where where
pickleTlsFeature :: PU [Node] Bool pickleTlsFeature :: PU [Node] Bool
pickleTlsFeature = xpElemNodes "{urn:ietf:params:xml:ns:xmpp-tls}starttls" pickleTlsFeature = ("pickleTlsFeature", "") <?>
(xpElemExists "required") xpElemNodes "{urn:ietf:params:xml:ns:xmpp-tls}starttls"
(xpElemExists "{urn:ietf:params:xml:ns:xmpp-tls}required")
pickleSaslFeature :: PU [Node] [Text] pickleSaslFeature :: PU [Node] [Text]
pickleSaslFeature = xpElemNodes pickleSaslFeature = ("pickleSaslFeature", "") <?>
"{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))

52
source/Network/Xmpp/Stream.hs

@ -68,7 +68,8 @@ streamUnpickleElem :: PU [Node] a
-> StreamSink a -> StreamSink a
streamUnpickleElem p x = do streamUnpickleElem p x = do
case unpickleElem p x of case unpickleElem p x of
Left l -> throwError $ XmppOtherFailure "Unpickle error" Left l -> throwError $ XmppOtherFailure ("Unpickle error"
++ ppUnpickleError l)
-- TODO: Log: StreamXmlError (show l) -- TODO: Log: StreamXmlError (show l)
Right r -> return r Right r -> return r
@ -102,7 +103,6 @@ startStream :: StateT Stream IO (Either XmppFailure ())
startStream = runErrorT $ do startStream = runErrorT $ do
liftIO $ debugM "Pontarius.Xmpp" "starting stream" liftIO $ debugM "Pontarius.Xmpp" "starting stream"
state <- lift $ get state <- lift $ get
stream <- liftIO $ mkStream state
-- Set the `from' (which is also the expected to) attribute depending on the -- Set the `from' (which is also the expected to) attribute depending on the
-- state of the stream. -- state of the stream.
let expectedTo = case (streamState state, toJid $ streamConfiguration state) of let expectedTo = case (streamState state, toJid $ streamConfiguration state) of
@ -128,17 +128,17 @@ startStream = runErrorT $ do
-- Successful unpickling of stream element. -- Successful unpickling of stream element.
Right (Right (ver, from, to, id, lt, features)) Right (Right (ver, from, to, id, lt, features))
| (Text.unpack ver) /= "1.0" -> | (Text.unpack ver) /= "1.0" ->
closeStreamWithError stream StreamUnsupportedVersion Nothing closeStreamWithError StreamUnsupportedVersion Nothing
"Unknown stream version" "Unknown version"
| lt == Nothing -> | lt == Nothing ->
closeStreamWithError stream StreamInvalidXml Nothing closeStreamWithError StreamInvalidXml Nothing
"stream has no language tag" "stream has no language tag"
-- If `from' is set, we verify that it's the correct one. TODO: Should we check against the realm instead? -- If `from' is set, we verify that it's the correct one. TODO: Should we check against the realm instead?
| isJust from && (from /= Just (Jid Nothing (fromJust $ streamHostname state) Nothing)) -> | isJust from && (from /= Just (Jid Nothing (fromJust $ streamHostname state) Nothing)) ->
closeStreamWithError stream StreamInvalidFrom Nothing closeStreamWithError StreamInvalidFrom Nothing
"stream from is invalid" "stream from is invalid"
| to /= expectedTo -> | to /= expectedTo ->
closeStreamWithError stream StreamUndefinedCondition (Just $ Element "invalid-to" [] []) closeStreamWithError StreamUndefinedCondition (Just $ Element "invalid-to" [] [])
"stream to invalid"-- TODO: Suitable? "stream to invalid"-- TODO: Suitable?
| otherwise -> do | otherwise -> do
modify (\s -> s{ streamFeatures = features modify (\s -> s{ streamFeatures = features
@ -150,42 +150,43 @@ startStream = runErrorT $ do
-- Unpickling failed - we investigate the element. -- Unpickling failed - we investigate the element.
Right (Left (Element name attrs children)) Right (Left (Element name attrs children))
| (nameLocalName name /= "stream") -> | (nameLocalName name /= "stream") ->
closeStreamWithError stream StreamInvalidXml Nothing closeStreamWithError StreamInvalidXml Nothing
"Root element is not stream" "Root element is not stream"
| (nameNamespace name /= Just "http://etherx.jabber.org/streams") -> | (nameNamespace name /= Just "http://etherx.jabber.org/streams") ->
closeStreamWithError stream StreamInvalidNamespace Nothing closeStreamWithError StreamInvalidNamespace Nothing
"Wrong root element name space" "Wrong root element name space"
| (isJust $ namePrefix name) && (fromJust (namePrefix name) /= "stream") -> | (isJust $ namePrefix name) && (fromJust (namePrefix name) /= "stream") ->
closeStreamWithError stream StreamBadNamespacePrefix Nothing closeStreamWithError StreamBadNamespacePrefix Nothing
"Root name prefix set and not stream" "Root name prefix set and not stream"
| otherwise -> ErrorT $ checkchildren stream (flattenAttrs attrs) | otherwise -> ErrorT $ checkchildren (flattenAttrs attrs)
where where
-- closeStreamWithError :: MonadIO m => TMVar Stream -> StreamErrorCondition -> -- closeStreamWithError :: MonadIO m => TMVar Stream -> StreamErrorCondition ->
-- Maybe Element -> ErrorT XmppFailure m () -- Maybe Element -> ErrorT XmppFailure m ()
closeStreamWithError stream sec el msg = do closeStreamWithError :: StreamErrorCondition -> Maybe Element -> String
liftIO $ do -> ErrorT XmppFailure (StateT Stream IO) ()
withStream (pushElement . pickleElem xpStreamError $ closeStreamWithError sec el msg = do
StreamErrorInfo sec Nothing el) stream lift . pushElement . pickleElem xpStreamError
closeStreams stream $ StreamErrorInfo sec Nothing el
lift $ closeStreams'
throwError $ XmppOtherFailure msg throwError $ XmppOtherFailure msg
checkchildren stream children = checkchildren children =
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 :: Maybe Jid) == (safeRead <$> to') ->
runErrorT $ closeStreamWithError stream runErrorT $ closeStreamWithError
StreamBadNamespacePrefix Nothing StreamBadNamespacePrefix Nothing
"stream to not a valid JID" "stream to not a valid JID"
| Nothing == ver' -> | Nothing == ver' ->
runErrorT $ closeStreamWithError stream runErrorT $ closeStreamWithError
StreamUnsupportedVersion Nothing StreamUnsupportedVersion Nothing
"stream no version" "stream no version"
| Just (Nothing :: Maybe LangTag) == (safeRead <$> xl) -> | Just (Nothing :: Maybe LangTag) == (safeRead <$> xl) ->
runErrorT $ closeStreamWithError stream runErrorT $ closeStreamWithError
StreamInvalidXml Nothing StreamInvalidXml Nothing
"stream no language tag" "stream no language tag"
| otherwise -> | otherwise ->
runErrorT $ closeStreamWithError stream runErrorT $ closeStreamWithError
StreamBadFormat Nothing StreamBadFormat Nothing
"" ""
safeRead x = case reads $ Text.unpack x of safeRead x = case reads $ Text.unpack x of
@ -267,7 +268,9 @@ openStream realm config = runErrorT $ do
-- close the connection. Any remaining elements from the server are returned. -- close the connection. Any remaining elements from the server are returned.
-- Surpresses StreamEndFailure exceptions, but may throw a StreamCloseError. -- Surpresses StreamEndFailure exceptions, but may throw a StreamCloseError.
closeStreams :: TMVar Stream -> IO (Either XmppFailure [Element]) closeStreams :: TMVar Stream -> IO (Either XmppFailure [Element])
closeStreams = withStream $ do closeStreams = withStream closeStreams'
closeStreams' = do
send <- gets (streamSend . streamHandle) send <- gets (streamSend . streamHandle)
cc <- gets (streamClose . streamHandle) cc <- gets (streamClose . streamHandle)
liftIO $ send "</stream:stream>" liftIO $ send "</stream:stream>"
@ -357,8 +360,9 @@ pullUnpickle p = do
Right elem' -> do Right elem' -> do
let res = unpickleElem p elem' let res = unpickleElem p elem'
case res of case res of
Left e -> return . Left $ XmppOtherFailure Left e -> return . Left . XmppOtherFailure $
"pullUnpickle: unpickle failed" -- TODO: Log "pullUnpickle: unpickle failed" ++ ppUnpickleError e
-- TODO: Log
Right r -> return $ Right r Right r -> return $ Right r
-- | Pulls a stanza (or stream error) from the stream. -- | Pulls a stanza (or stream error) from the stream.

Loading…
Cancel
Save