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.
76 lines
2.6 KiB
76 lines
2.6 KiB
|
14 years ago
|
-- Implementation of the PLAIN Simple Authentication and Security Layer (SASL)
|
||
|
|
-- Mechanism, http://tools.ietf.org/html/rfc4616.
|
||
|
|
|
||
|
|
{-# LANGUAGE OverloadedStrings #-}
|
||
|
|
|
||
|
14 years ago
|
module Network.Xmpp.Sasl.Mechanisms.Plain 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 Data.Word (Word8)
|
||
|
|
|
||
|
|
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
|
|
||
|
|
import qualified System.Random as Random
|
||
|
|
|
||
|
|
import Data.Maybe (fromMaybe)
|
||
|
14 years ago
|
import qualified Data.Text as Text
|
||
|
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
|
-- TODO: stringprep
|
||
|
14 years ago
|
xmppPlain :: Text.Text -- ^ Password
|
||
|
|
-> Maybe Text.Text -- ^ Authorization identity (authzid)
|
||
|
|
-> Text.Text -- ^ Authentication identity (authcid)
|
||
|
14 years ago
|
-> SaslM ()
|
||
|
14 years ago
|
xmppPlain authcid authzid password = do
|
||
|
|
(ac, az, pw) <- prepCredentials authcid authzid password
|
||
|
|
_ <- saslInit "PLAIN" ( Just $ plainMessage ac az pw)
|
||
|
14 years ago
|
_ <- pullSuccess
|
||
|
14 years ago
|
return ()
|
||
|
|
where
|
||
|
|
-- Converts an optional authorization identity, an authentication identity,
|
||
|
|
-- and a password to a \NUL-separated PLAIN message.
|
||
|
14 years ago
|
plainMessage :: Text.Text -- Authorization identity (authzid)
|
||
|
|
-> Maybe Text.Text -- Authentication identity (authcid)
|
||
|
14 years ago
|
-> Text.Text -- Password
|
||
|
|
-> BS.ByteString -- The PLAIN message
|
||
|
14 years ago
|
plainMessage authcid authzid passwd = BS.concat $
|
||
|
14 years ago
|
[ authzid'
|
||
|
|
, "\NUL"
|
||
|
|
, Text.encodeUtf8 $ authcid
|
||
|
|
, "\NUL"
|
||
|
|
, Text.encodeUtf8 $ passwd
|
||
|
|
]
|
||
|
|
where
|
||
|
|
authzid' = maybe "" Text.encodeUtf8 authzid
|
||
|
|
|
||
|
14 years ago
|
plain :: Text.Text -> Maybe Text.Text -> Text.Text -> SaslHandler
|
||
|
|
plain authcid authzid passwd = ("PLAIN", xmppPlain authcid authzid passwd)
|