Browse Source

Added some SASL failure handling

master
Philipp Balzarek 14 years ago
parent
commit
b9774d297a
  1. 1
      src/Network/XMPP/JID.hs
  2. 84
      src/Network/XMPP/SASL.hs

1
src/Network/XMPP/JID.hs

@ -120,7 +120,6 @@ isFull jid = not $ isBare jid
-- Parses an JID string and returns its three parts. It performs no -- Parses an JID string and returns its three parts. It performs no
-- validation or transformations. We are using Parsec to parse the -- validation or transformations. We are using Parsec to parse the
-- JIDs. There is no input for which 'jidParts' fails. -- JIDs. There is no input for which 'jidParts' fails.
jidParts = do jidParts = do
-- Read until we reach an '@', a '/', or EOF. -- Read until we reach an '@', a '/', or EOF.
a <- AP.takeWhile1 (AP.notInClass ['@', '/']) a <- AP.takeWhile1 (AP.notInClass ['@', '/'])

84
src/Network/XMPP/SASL.hs

@ -2,7 +2,9 @@
module Network.XMPP.SASL where module Network.XMPP.SASL where
import Control.Applicative import Control.Applicative
import Control.Arrow (left)
import Control.Monad import Control.Monad
import Control.Monad.Error
import Control.Monad.IO.Class import Control.Monad.IO.Class
import Control.Monad.State.Strict import Control.Monad.State.Strict
@ -50,35 +52,53 @@ saslResponse2E =
[] []
[] []
xmppSASL:: Text -> Text -> XMPPConMonad (Either String Text) data SaslError = SaslXmlError
xmppSASL uname passwd = do | SaslMechanismError [Text]
| SaslChallengeError
| SaslStreamError StreamError
| SaslConnectionError
instance Error SaslError where
noMsg = SaslXmlError
xmppSASL:: Text -> Text -> XMPPConMonad (Either SaslError Text)
xmppSASL uname passwd = runErrorT $ do
realm <- gets sHostname realm <- gets sHostname
case realm of case realm of
Just realm' -> do Just realm' -> do
xmppStartSASL realm' uname passwd ErrorT $ xmppStartSASL realm' uname passwd
modify (\s -> s{sUsername = Just uname}) modify (\s -> s{sUsername = Just uname})
return $ Right uname return uname
Nothing -> return $ Left "No connection found" Nothing -> throwError SaslConnectionError
xmppStartSASL :: Text xmppStartSASL :: Text
-> Text -> Text
-> Text -> Text
-> XMPPConMonad () -> XMPPConMonad (Either SaslError ())
xmppStartSASL realm username passwd = do xmppStartSASL realm username passwd = runErrorT $ do
mechanisms <- gets $ saslMechanisms . sFeatures mechanisms <- gets $ saslMechanisms . sFeatures
unless ("DIGEST-MD5" `elem` mechanisms) . error $ "No usable auth mechanism: " ++ show mechanisms unless ("DIGEST-MD5" `elem` mechanisms)
pushN $ saslInitE "DIGEST-MD5" . throwError $ SaslMechanismError mechanisms
Right challenge <- B64.decode . Text.encodeUtf8<$> pullPickle challengePickle lift . pushN $ saslInitE "DIGEST-MD5"
let Right pairs = toPairs challenge challenge' <- lift $ B64.decode . Text.encodeUtf8<$> pullPickle challengePickle
challenge <- case challenge' of
Left _e -> throwError SaslChallengeError
Right r -> return r
pairs <- case toPairs challenge of
Left _ -> throwError SaslChallengeError
Right p -> return p
g <- liftIO $ Random.newStdGen g <- liftIO $ Random.newStdGen
pushN . saslResponseE $ createResponse g realm username passwd pairs lift . pushN . saslResponseE $ createResponse g realm username passwd pairs
challenge2 <- pullPickle (xpEither failurePickle challengePickle) challenge2 <- lift $ pullPickle (xpEither failurePickle challengePickle)
case challenge2 of case challenge2 of
Left x -> error $ show x Left _x -> throwError $ SaslXmlError
Right _ -> return () Right _ -> return ()
pushN saslResponse2E lift $ pushN saslResponse2E
Element "{urn:ietf:params:xml:ns:xmpp-sasl}success" [] [] <- pullE e <- lift pullE
_ <- xmppRestartStream case e of
Element "{urn:ietf:params:xml:ns:xmpp-sasl}success" [] [] -> return ()
_ -> throwError SaslXmlError -- TODO: investigate
_ <- ErrorT $ left SaslStreamError <$> xmppRestartStream
return () return ()
createResponse :: Random.RandomGen g createResponse :: Random.RandomGen g
@ -93,16 +113,15 @@ createResponse g hostname username passwd' pairs = let
Just nonce = L.lookup "nonce" pairs Just nonce = L.lookup "nonce" pairs
uname = Text.encodeUtf8 username uname = Text.encodeUtf8 username
passwd = Text.encodeUtf8 passwd' passwd = Text.encodeUtf8 passwd'
realm = Text.encodeUtf8 hostname
-- Using Int instead of Word8 for random 1.0.0.0 (GHC 7) -- Using Int instead of Word8 for random 1.0.0.0 (GHC 7)
-- compatibility. -- compatibility.
cnonce = BS.tail . BS.init . cnonce = BS.tail . BS.init .
B64.encode . BS.pack . map toWord8 . take 8 $ Random.randoms g B64.encode . BS.pack . map toWord8 . take 8 $ Random.randoms g
nc = "00000001" nc = "00000001"
digestURI = ("xmpp/" `BS.append` realm) digestURI = ("xmpp/" `BS.append` (Text.encodeUtf8 hostname))
digest = md5Digest digest = md5Digest
uname uname
realm (lookup "realm" pairs)
passwd passwd
digestURI digestURI
nc nc
@ -110,15 +129,18 @@ createResponse g hostname username passwd' pairs = let
nonce nonce
cnonce cnonce
response = BS.intercalate"," . map (BS.intercalate "=") $ response = BS.intercalate"," . map (BS.intercalate "=") $
[["username" , quote uname ] [ ["username" , quote uname ]]
,["realm" , quote realm ] ++ case L.lookup "realm" pairs of
,["nonce" , quote nonce ] Just realm -> [["realm" , quote realm ]]
,["cnonce" , quote cnonce ] Nothing -> []
,["nc" , nc ] ++
,["qop" , qop ] [ ["nonce" , quote nonce ]
,["digest-uri", quote digestURI ] , ["cnonce" , quote cnonce ]
,["response" , digest ] , ["nc" , nc ]
,["charset" , "utf-8" ] , ["qop" , qop ]
, ["digest-uri", quote digestURI ]
, ["response" , digest ]
, ["charset" , "utf-8" ]
] ]
in Text.decodeUtf8 $ B64.encode response in Text.decodeUtf8 $ B64.encode response
where where
@ -150,7 +172,7 @@ toStrict = BS.concat . BL.toChunks
-- TODO: this only handles MD5-sess -- TODO: this only handles MD5-sess
md5Digest :: BS8.ByteString md5Digest :: BS8.ByteString
-> BS8.ByteString -> Maybe BS8.ByteString
-> BS8.ByteString -> BS8.ByteString
-> BS8.ByteString -> BS8.ByteString
-> BS8.ByteString -> BS8.ByteString
@ -159,7 +181,7 @@ md5Digest :: BS8.ByteString
-> BS8.ByteString -> BS8.ByteString
-> BS8.ByteString -> BS8.ByteString
md5Digest uname realm password digestURI nc qop nonce cnonce= md5Digest uname realm password digestURI nc qop nonce cnonce=
let ha1 = hash [hashRaw [uname,realm,password], nonce, cnonce] let ha1 = hash [hashRaw [uname, maybe "" id realm, password], nonce, cnonce]
ha2 = hash ["AUTHENTICATE", digestURI] ha2 = hash ["AUTHENTICATE", digestURI]
in hash [ha1,nonce, nc, cnonce,qop,ha2] in hash [ha1,nonce, nc, cnonce,qop,ha2]

Loading…
Cancel
Save