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.
165 lines
6.7 KiB
165 lines
6.7 KiB
|
14 years ago
|
{-# LANGUAGE PatternGuards #-}
|
||
|
|
{-# LANGUAGE FlexibleContexts #-}
|
||
|
|
{-# LANGUAGE OverloadedStrings #-}
|
||
|
|
|
||
|
14 years ago
|
module Network.Xmpp.Sasl.Mechanisms.Scram where
|
||
|
14 years ago
|
|
||
|
14 years ago
|
import Control.Applicative ((<$>))
|
||
|
14 years ago
|
import Control.Monad.Error
|
||
|
|
import Control.Monad.Trans (liftIO)
|
||
|
|
import qualified Crypto.Classes as Crypto
|
||
|
|
import qualified Crypto.HMAC as Crypto
|
||
|
|
import qualified Crypto.Hash.SHA1 as Crypto
|
||
|
|
import Data.Binary(Binary,encode)
|
||
|
|
import qualified Data.ByteString as BS
|
||
|
|
import qualified Data.ByteString.Base64 as B64
|
||
|
|
import Data.ByteString.Char8 as BS8 (unpack)
|
||
|
|
import qualified Data.ByteString.Lazy as LBS
|
||
|
14 years ago
|
import Data.List (foldl1', genericTake)
|
||
|
14 years ago
|
|
||
|
|
import qualified Data.Binary.Builder as Build
|
||
|
|
|
||
|
|
import Data.Maybe (maybeToList)
|
||
|
|
import qualified Data.Text as Text
|
||
|
|
import qualified Data.Text.Encoding as Text
|
||
|
|
import Data.Word(Word8)
|
||
|
|
|
||
|
|
import Network.Xmpp.Sasl.Common
|
||
|
14 years ago
|
import Network.Xmpp.Sasl.StringPrep
|
||
|
14 years ago
|
import Network.Xmpp.Sasl.Types
|
||
|
|
|
||
|
14 years ago
|
-- | A nicer name for undefined, for use as a dummy token to determin
|
||
|
|
-- the hash function to use
|
||
|
14 years ago
|
hashToken :: (Crypto.Hash ctx hash) => hash
|
||
|
|
hashToken = undefined
|
||
|
|
|
||
|
14 years ago
|
-- | Salted Challenge Response Authentication Mechanism (SCRAM) SASL
|
||
|
|
-- mechanism according to RFC 5802.
|
||
|
|
--
|
||
|
|
-- This implementation is independent and polymorphic in the used hash function.
|
||
|
14 years ago
|
scram :: (Crypto.Hash ctx hash)
|
||
|
14 years ago
|
=> hash -- ^ Dummy argument to determine the hash to use; you
|
||
|
14 years ago
|
-- can safely pass undefined or a 'hashToken' to it
|
||
|
14 years ago
|
-> Text.Text -- ^ Authentication ID (user name)
|
||
|
|
-> Maybe Text.Text -- ^ Authorization ID
|
||
|
|
-> Text.Text -- ^ Password
|
||
|
14 years ago
|
-> SaslM ()
|
||
|
14 years ago
|
scram hashToken authcid authzid password = do
|
||
|
|
(ac, az, pw) <- prepCredentials authcid authzid password
|
||
|
|
scramhelper hashToken ac az pw
|
||
|
14 years ago
|
where
|
||
|
14 years ago
|
scramhelper hashToken authcid authzid' password = do
|
||
|
|
cnonce <- liftIO $ makeNonce
|
||
|
|
saslInit "SCRAM-SHA-1" (Just $ cFirstMessage cnonce)
|
||
|
|
sFirstMessage <- saslFromJust =<< pullChallenge
|
||
|
|
pairs <- toPairs sFirstMessage
|
||
|
|
(nonce, salt, ic) <- fromPairs pairs cnonce
|
||
|
|
let (cfm, v) = cFinalMessageAndVerifier nonce salt ic sFirstMessage cnonce
|
||
|
|
respond $ Just cfm
|
||
|
|
finalPairs <- toPairs =<< saslFromJust =<< pullFinalMessage
|
||
|
|
unless (lookup "v" finalPairs == Just v) $ throwError AuthServerAuthError
|
||
|
|
return ()
|
||
|
14 years ago
|
where
|
||
|
14 years ago
|
-- We need to jump through some hoops to get a polymorphic solution
|
||
|
|
encode :: Crypto.Hash ctx hash => hash -> hash -> BS.ByteString
|
||
|
|
encode _hashtoken = Crypto.encode
|
||
|
14 years ago
|
|
||
|
|
hash :: BS.ByteString -> BS.ByteString
|
||
|
14 years ago
|
hash str = encode hashToken $ Crypto.hash' str
|
||
|
14 years ago
|
|
||
|
|
hmac :: BS.ByteString -> BS.ByteString -> BS.ByteString
|
||
|
14 years ago
|
hmac key str = encode hashToken $ Crypto.hmac' (Crypto.MacKey key) str
|
||
|
|
|
||
|
14 years ago
|
authzid :: Maybe BS.ByteString
|
||
|
14 years ago
|
authzid = (\z -> "a=" +++ Text.encodeUtf8 z) <$> authzid'
|
||
|
14 years ago
|
|
||
|
|
gs2CbindFlag :: BS.ByteString
|
||
|
14 years ago
|
gs2CbindFlag = "n" -- we don't support channel binding yet
|
||
|
14 years ago
|
|
||
|
|
gs2Header :: BS.ByteString
|
||
|
14 years ago
|
gs2Header = merge $ [ gs2CbindFlag
|
||
|
|
, maybe "" id authzid
|
||
|
|
, ""
|
||
|
|
]
|
||
|
14 years ago
|
cbindData :: BS.ByteString
|
||
|
14 years ago
|
cbindData = "" -- we don't support channel binding yet
|
||
|
14 years ago
|
|
||
|
|
cFirstMessageBare :: BS.ByteString -> BS.ByteString
|
||
|
14 years ago
|
cFirstMessageBare cnonce = merge [ "n=" +++ Text.encodeUtf8 authcid
|
||
|
|
, "r=" +++ cnonce]
|
||
|
14 years ago
|
cFirstMessage :: BS.ByteString -> BS.ByteString
|
||
|
14 years ago
|
cFirstMessage cnonce = gs2Header +++ cFirstMessageBare cnonce
|
||
|
|
|
||
|
|
fromPairs :: Pairs
|
||
|
|
-> BS.ByteString
|
||
|
14 years ago
|
-> SaslM (BS.ByteString, BS.ByteString, Integer)
|
||
|
14 years ago
|
fromPairs pairs cnonce | Just nonce <- lookup "r" pairs
|
||
|
|
, cnonce `BS.isPrefixOf` nonce
|
||
|
|
, Just salt' <- lookup "s" pairs
|
||
|
|
, Right salt <- B64.decode salt'
|
||
|
|
, Just ic <- lookup "i" pairs
|
||
|
|
, [(i,"")] <- reads $ BS8.unpack ic
|
||
|
14 years ago
|
= return (nonce, salt, i)
|
||
|
14 years ago
|
fromPairs _ _ = throwError $ AuthChallengeError
|
||
|
|
|
||
|
14 years ago
|
cFinalMessageAndVerifier :: BS.ByteString
|
||
|
|
-> BS.ByteString
|
||
|
|
-> Integer
|
||
|
|
-> BS.ByteString
|
||
|
|
-> BS.ByteString
|
||
|
|
-> (BS.ByteString, BS.ByteString)
|
||
|
14 years ago
|
cFinalMessageAndVerifier nonce salt ic sfm cnonce
|
||
|
|
= (merge [ cFinalMessageWOProof
|
||
|
|
, "p=" +++ B64.encode clientProof
|
||
|
|
]
|
||
|
|
, B64.encode serverSignature
|
||
|
|
)
|
||
|
14 years ago
|
where
|
||
|
14 years ago
|
cFinalMessageWOProof :: BS.ByteString
|
||
|
14 years ago
|
cFinalMessageWOProof = merge [ "c=" +++ B64.encode gs2Header
|
||
|
|
, "r=" +++ nonce]
|
||
|
14 years ago
|
|
||
|
|
saltedPassword :: BS.ByteString
|
||
|
14 years ago
|
saltedPassword = hi (Text.encodeUtf8 password) salt ic
|
||
|
14 years ago
|
|
||
|
|
clientKey :: BS.ByteString
|
||
|
14 years ago
|
clientKey = hmac saltedPassword "Client Key"
|
||
|
14 years ago
|
|
||
|
|
storedKey :: BS.ByteString
|
||
|
14 years ago
|
storedKey = hash clientKey
|
||
|
14 years ago
|
|
||
|
|
authMessage :: BS.ByteString
|
||
|
14 years ago
|
authMessage = merge [ cFirstMessageBare cnonce
|
||
|
|
, sfm
|
||
|
|
, cFinalMessageWOProof
|
||
|
|
]
|
||
|
14 years ago
|
|
||
|
|
clientSignature :: BS.ByteString
|
||
|
14 years ago
|
clientSignature = hmac storedKey authMessage
|
||
|
14 years ago
|
|
||
|
|
clientProof :: BS.ByteString
|
||
|
14 years ago
|
clientProof = clientKey `xorBS` clientSignature
|
||
|
14 years ago
|
|
||
|
|
serverKey :: BS.ByteString
|
||
|
14 years ago
|
serverKey = hmac saltedPassword "Server Key"
|
||
|
14 years ago
|
|
||
|
|
serverSignature :: BS.ByteString
|
||
|
14 years ago
|
serverSignature = hmac serverKey authMessage
|
||
|
|
|
||
|
|
-- helper
|
||
|
14 years ago
|
hi :: BS.ByteString -> BS.ByteString -> Integer -> BS.ByteString
|
||
|
|
hi str salt ic = foldl1' xorBS (genericTake ic us)
|
||
|
14 years ago
|
where
|
||
|
|
u1 = hmac str (salt +++ (BS.pack [0,0,0,1]))
|
||
|
|
us = iterate (hmac str) u1
|
||
|
14 years ago
|
|
||
|
14 years ago
|
-- | 'scram' spezialised to the SHA-1 hash function, packaged as a SaslHandler
|
||
|
14 years ago
|
scramSha1 :: Text.Text -- ^ username
|
||
|
|
-> Maybe Text.Text -- ^ authorization ID
|
||
|
|
-> Text.Text -- ^ password
|
||
|
|
-> SaslHandler
|
||
|
|
scramSha1 authcid authzid passwd =
|
||
|
|
("SCRAM-SHA-1"
|
||
|
|
, scram (hashToken :: Crypto.SHA1) authcid authzid passwd
|
||
|
|
)
|