Browse Source

Change more all-caps names to camel case

rename Sasl.Sasl to Sasl.Common
master
Philipp Balzarek 14 years ago
parent
commit
5b536428a9
  1. 2
      source/Network/Xmpp/Sasl.hs
  2. 17
      source/Network/Xmpp/Sasl/Common.hs
  3. 6
      source/Network/Xmpp/Sasl/DigestMD5.hs
  4. 4
      source/Network/Xmpp/Sasl/Plain.hs

2
source/Network/Xmpp/Sasl.hs

@ -53,7 +53,7 @@ xmppSasl creds = runErrorT $ do
authzid authzid
authcid authcid
passwd passwd
PlainCredentials authzid authcid passwd -> ErrorT $ xmppPLAIN PlainCredentials authzid authcid passwd -> ErrorT $ xmppPlain
authzid authzid
authcid authcid
passwd passwd

17
source/Network/Xmpp/Sasl/Sasl.hs → source/Network/Xmpp/Sasl/Common.hs

@ -1,16 +1,19 @@
{-# LANGUAGE OverloadedStrings #-} {-# LANGUAGE OverloadedStrings #-}
module Network.Xmpp.Sasl.Sasl where module Network.Xmpp.Sasl.Common where
import Network.Xmpp.Types import Network.Xmpp.Types
import Control.Applicative ((<$>))
import Control.Monad.Error import Control.Monad.Error
import Data.Text
import qualified Data.Attoparsec.ByteString.Char8 as AP import qualified Data.Attoparsec.ByteString.Char8 as AP
import qualified Data.ByteString as BS
import Data.Maybe (fromMaybe)
import Data.Maybe (maybeToList)
import Data.Text
import Data.XML.Pickle import Data.XML.Pickle
import Data.XML.Types import Data.XML.Types
import qualified Data.ByteString as BS
import Data.Maybe (fromMaybe)
import Network.Xmpp.Pickle import Network.Xmpp.Pickle
@ -20,7 +23,7 @@ saslInitE :: Text -> Maybe Text -> Element
saslInitE mechanism rt = saslInitE mechanism rt =
Element "{urn:ietf:params:xml:ns:xmpp-sasl}auth" Element "{urn:ietf:params:xml:ns:xmpp-sasl}auth"
[("mechanism", [ContentText mechanism])] [("mechanism", [ContentText mechanism])]
[NodeContent $ ContentText $ fromMaybe "" rt] (maybeToList $ NodeContent . ContentText <$> rt)
-- SASL response with text payload. -- SASL response with text payload.
saslResponseE :: Text -> Element saslResponseE :: Text -> Element
@ -28,12 +31,14 @@ saslResponseE resp =
Element "{urn:ietf:params:xml:ns:xmpp-sasl}response" Element "{urn:ietf:params:xml:ns:xmpp-sasl}response"
[] []
[NodeContent $ ContentText resp] [NodeContent $ ContentText resp]
-- SASL response without payload. -- SASL response without payload.
saslResponse2E :: Element saslResponse2E :: Element
saslResponse2E = saslResponse2E =
Element "{urn:ietf:params:xml:ns:xmpp-sasl}response" Element "{urn:ietf:params:xml:ns:xmpp-sasl}response"
[] []
[] []
-- Parses the incoming SASL data to a mapped list of pairs. -- Parses the incoming SASL data to a mapped list of pairs.
toPairs :: BS.ByteString -> Either String [(BS.ByteString, BS.ByteString)] toPairs :: BS.ByteString -> Either String [(BS.ByteString, BS.ByteString)]
toPairs = AP.parseOnly . flip AP.sepBy1 (void $ AP.char ',') $ do toPairs = AP.parseOnly . flip AP.sepBy1 (void $ AP.char ',') $ do

6
source/Network/Xmpp/Sasl/DigestMD5.hs

@ -47,14 +47,14 @@ xmppDigestMD5 authzid authcid passwd = runErrorT $ do
realm <- gets sHostname realm <- gets sHostname
case realm of case realm of
Just realm' -> do Just realm' -> do
ErrorT $ xmppDIGEST_MD5' realm' ErrorT $ xmppDigestMD5' realm'
-- TODO: Save authzid -- TODO: Save authzid
modify (\s -> s{sUsername = Just authcid}) modify (\s -> s{sUsername = Just authcid})
Nothing -> throwError AuthConnectionError Nothing -> throwError AuthConnectionError
where where
xmppDIGEST_MD5' :: Text -- ^ SASL realm xmppDigestMD5' :: Text -- ^ SASL realm
-> XmppConMonad (Either AuthError ()) -> XmppConMonad (Either AuthError ())
xmppDIGEST_MD5' realm = runErrorT $ do xmppDigestMD5' realm = runErrorT $ do
-- Push element and receive the challenge (in XmppConMonad). -- Push element and receive the challenge (in XmppConMonad).
_ <- lift . pushElement $ saslInitE "DIGEST-MD5" Nothing -- TODO: Check boolean? _ <- lift . pushElement $ saslInitE "DIGEST-MD5" Nothing -- TODO: Check boolean?
challenge' <- lift $ B64.decode . Text.encodeUtf8 <$> challenge' <- lift $ B64.decode . Text.encodeUtf8 <$>

4
source/Network/Xmpp/Sasl/Plain.hs

@ -45,11 +45,11 @@ import qualified Data.Text as T
import Network.Xmpp.Sasl.Sasl import Network.Xmpp.Sasl.Sasl
import Network.Xmpp.Sasl.Types import Network.Xmpp.Sasl.Types
xmppPLAIN :: Maybe T.Text xmppPlain :: Maybe T.Text
-> T.Text -> T.Text
-> T.Text -> T.Text
-> XmppConMonad (Either AuthError ()) -> XmppConMonad (Either AuthError ())
xmppPLAIN authzid authcid passwd = runErrorT $ do xmppPlain authzid authcid passwd = runErrorT $ do
_ <- lift . pushElement $ saslInitE "PLAIN" $ -- TODO: Check boolean? _ <- lift . pushElement $ saslInitE "PLAIN" $ -- TODO: Check boolean?
Just $ Text.decodeUtf8 $ B64.encode $ Text.encodeUtf8 $ plainMessage authzid authcid passwd Just $ Text.decodeUtf8 $ B64.encode $ Text.encodeUtf8 $ plainMessage authzid authcid passwd
lift $ pushElement saslResponse2E lift $ pushElement saslResponse2E

Loading…
Cancel
Save