You can not select more than 25 topics
Topics must start with a letter or number, can include dashes ('-') and can be up to 35 characters long.
134 lines
4.8 KiB
134 lines
4.8 KiB
|
14 years ago
|
{-# LANGUAGE OverloadedStrings #-}
|
||
|
|
|
||
|
14 years ago
|
module Network.Xmpp.Sasl.DigestMd5 where
|
||
|
14 years ago
|
|
||
|
|
import Control.Applicative
|
||
|
|
import Control.Arrow (left)
|
||
|
|
import Control.Monad
|
||
|
|
import Control.Monad.Error
|
||
|
|
import Control.Monad.State.Strict
|
||
|
|
import Data.Maybe (fromJust, isJust)
|
||
|
|
|
||
|
|
import qualified Crypto.Classes as CC
|
||
|
|
|
||
|
|
import qualified Data.Binary as Binary
|
||
|
|
import qualified Data.ByteString.Base64 as B64
|
||
|
|
import qualified Data.ByteString.Char8 as BS8
|
||
|
|
import qualified Data.ByteString.Lazy as BL
|
||
|
|
import qualified Data.Digest.Pure.MD5 as MD5
|
||
|
|
import qualified Data.List as L
|
||
|
|
|
||
|
|
import qualified Data.Text as Text
|
||
|
|
import Data.Text (Text)
|
||
|
|
import qualified Data.Text.Encoding as Text
|
||
|
|
|
||
|
|
import Data.XML.Pickle
|
||
|
|
|
||
|
|
import qualified Data.ByteString as BS
|
||
|
|
|
||
|
|
import Data.XML.Types
|
||
|
|
|
||
|
14 years ago
|
import Network.Xmpp.Monad
|
||
|
|
import Network.Xmpp.Stream
|
||
|
|
import Network.Xmpp.Types
|
||
|
|
import Network.Xmpp.Pickle
|
||
|
14 years ago
|
|
||
|
|
|
||
|
14 years ago
|
import Network.Xmpp.Sasl.Common
|
||
|
14 years ago
|
import Network.Xmpp.Sasl.Types
|
||
|
14 years ago
|
|
||
|
14 years ago
|
|
||
|
|
|
||
|
14 years ago
|
xmppDigestMd5 :: Maybe Text -- Authorization identity (authzid)
|
||
|
14 years ago
|
-> Text -- Authentication identity (authzid)
|
||
|
|
-> Text -- Password (authzid)
|
||
|
14 years ago
|
-> SaslM ()
|
||
|
|
xmppDigestMd5 authzid authcid passwd = do
|
||
|
14 years ago
|
hn <- gets sHostname
|
||
|
|
case hn of
|
||
|
|
Just hn' -> do
|
||
|
|
xmppDigestMD5' hn'
|
||
|
14 years ago
|
-- TODO: Save authzid
|
||
|
|
modify (\s -> s{sUsername = Just authcid})
|
||
|
|
Nothing -> throwError AuthConnectionError
|
||
|
|
where
|
||
|
14 years ago
|
xmppDigestMD5' :: Text -> SaslM ()
|
||
|
|
xmppDigestMD5' hostname = do
|
||
|
14 years ago
|
-- Push element and receive the challenge (in SaslM).
|
||
|
|
_ <- saslInit "DIGEST-MD5" Nothing -- TODO: Check boolean?
|
||
|
|
pairs <- toPairs =<< saslFromJust =<< pullChallenge
|
||
|
14 years ago
|
cnonce <- liftIO $ makeNonce
|
||
|
|
_b <- respond . Just $ createResponse hostname pairs cnonce
|
||
|
|
challenge2 <- pullFinalMessage
|
||
|
14 years ago
|
_ <- ErrorT $ left AuthStreamError <$> xmppRestartStream
|
||
|
|
return ()
|
||
|
|
-- Produce the response to the challenge.
|
||
|
14 years ago
|
createResponse :: Text
|
||
|
|
-> Pairs
|
||
|
|
-> BS.ByteString -- nonce
|
||
|
|
-> BS.ByteString
|
||
|
|
createResponse hostname pairs cnonce = let
|
||
|
14 years ago
|
Just qop = L.lookup "qop" pairs -- TODO: proper handling
|
||
|
14 years ago
|
Just nonce = L.lookup "nonce" pairs
|
||
|
|
uname_ = Text.encodeUtf8 authcid
|
||
|
|
passwd_ = Text.encodeUtf8 passwd
|
||
|
|
-- Using Int instead of Word8 for random 1.0.0.0 (GHC 7) compatibility.
|
||
|
14 years ago
|
|
||
|
14 years ago
|
nc = "00000001"
|
||
|
|
digestURI = "xmpp/" `BS.append` Text.encodeUtf8 hostname
|
||
|
|
digest = md5Digest
|
||
|
|
uname_
|
||
|
|
(lookup "realm" pairs)
|
||
|
|
passwd_
|
||
|
|
digestURI
|
||
|
|
nc
|
||
|
|
qop
|
||
|
|
nonce
|
||
|
|
cnonce
|
||
|
|
response = BS.intercalate "," . map (BS.intercalate "=") $
|
||
|
|
[["username", quote uname_]] ++
|
||
|
|
case L.lookup "realm" pairs of
|
||
|
|
Just realm -> [["realm" , quote realm ]]
|
||
|
|
Nothing -> [] ++
|
||
|
|
[ ["nonce" , quote nonce ]
|
||
|
|
, ["cnonce" , quote cnonce ]
|
||
|
|
, ["nc" , nc ]
|
||
|
|
, ["qop" , qop ]
|
||
|
|
, ["digest-uri", quote digestURI]
|
||
|
|
, ["response" , digest ]
|
||
|
|
, ["charset" , "utf-8" ]
|
||
|
|
]
|
||
|
14 years ago
|
in B64.encode response
|
||
|
14 years ago
|
hash :: [BS8.ByteString] -> BS8.ByteString
|
||
|
|
hash = BS8.pack . show
|
||
|
|
. (CC.hash' :: BS.ByteString -> MD5.MD5Digest) . BS.intercalate (":")
|
||
|
|
hashRaw :: [BS8.ByteString] -> BS8.ByteString
|
||
|
|
hashRaw = toStrict . Binary.encode .
|
||
|
|
(CC.hash' :: BS.ByteString -> MD5.MD5Digest) . BS.intercalate (":")
|
||
|
|
toStrict :: BL.ByteString -> BS8.ByteString
|
||
|
|
toStrict = BS.concat . BL.toChunks
|
||
|
|
-- TODO: this only handles MD5-sess
|
||
|
|
md5Digest :: BS8.ByteString
|
||
|
|
-> Maybe BS8.ByteString
|
||
|
|
-> BS8.ByteString
|
||
|
|
-> BS8.ByteString
|
||
|
|
-> BS8.ByteString
|
||
|
|
-> BS8.ByteString
|
||
|
|
-> BS8.ByteString
|
||
|
|
-> BS8.ByteString
|
||
|
|
-> BS8.ByteString
|
||
|
|
md5Digest uname realm password digestURI nc qop nonce cnonce =
|
||
|
|
let ha1 = hash [ hashRaw [uname, maybe "" id realm, password]
|
||
|
|
, nonce
|
||
|
|
, cnonce
|
||
|
|
]
|
||
|
|
ha2 = hash ["AUTHENTICATE", digestURI]
|
||
|
14 years ago
|
in hash [ha1, nonce, nc, cnonce, qop, ha2]
|
||
|
|
|
||
|
|
digestMd5 :: Maybe Text -- Authorization identity (authzid)
|
||
|
|
-> Text -- Authentication identity (authzid)
|
||
|
|
-> Text -- Password (authzid)
|
||
|
|
-> SaslHandler
|
||
|
|
digestMd5 authzid authcid password = ( "DIGEST-MD5"
|
||
|
|
, xmppDigestMd5 authzid authcid password
|
||
|
|
)
|