Browse Source

Eq instance for JID, PLAIN now base64-encoded, EchoClient compiles,

isBare/Full functions exposed
master
Jon Kristensen 14 years ago
parent
commit
188cc252d3
  1. 68
      examples/EchoClient.hs
  2. 3
      pontarius.cabal
  3. 2
      source/Network/XMPP.hs
  4. 2
      source/Network/XMPP/JID.hs
  5. 1
      source/Network/XMPP/SASL.hs
  6. 2
      source/Network/XMPP/SASL/PLAIN.hs

68
examples/EchoClient.hs

@ -2,62 +2,62 @@
Copyright © 2010-2012 Jon Kristensen. Copyright © 2010-2012 Jon Kristensen.
This file (EchoClient.hs) illustrates how to connect, authenticate, This file (EchoClient.hs) illustrates how to connect, authenticate, set a simple
set a simple presence, receive message stanzas, and echo them back to presence, receive message stanzas, and echo them back to whoever is sending
whoever is sending them, using Pontarius. The contents of this file them, using Pontarius. The contents of this file may be used freely, as if it is
may be used freely, as if it is in the public domain. in the public domain.
-} -}
module Examples.EchoClient () where {-# LANGUAGE OverloadedStrings #-}
module Main (main) where
import Control.Monad (forever)
import Control.Monad.IO.Class (liftIO)
import Data.Maybe (fromJust, isJust)
import Network.XMPP import Network.XMPP
import Network.XMPP.IM
-- Server and authentication details. -- Server and authentication details.
hostName = "nejla.com" hostName = "nejla.com"
portNumber = 5222 portNumber = 5222
userName = "test" userName = "jon"
password = "" password = "G2D9%b4S3" -- TODO
-- Start an XMPP session with the default settings, open the streams
-- to the XMPP server, authenticate, send a simple presence, and start
-- the `echo' XMPP thread.
-- TODO: Incomplete code, needs documentation, etc.
main :: IO () main :: IO ()
main = do
main = session default $ do withNewSession $ do
liftIO $ putStrLn "Welcome to the Pontarius EchoClient example!" withConnection $ do
openStreamsResult <- openStreams "nejla.com" connect "xmpp.nejla.com" "nejla.com"
case openStreamsResult of -- startTLS exampleParams
Nothing -> do saslResponse <- auth userName password (Just "echo-client")
liftIO $ putStrLn "Streams opened, now authenticating!" case saslResponse of
authenticateResult <- authenticate userName password Nothing Right _ -> return ()
case authenticateResult of Left e -> error $ show e
Right _ -> do -- Ignore XMPP address sendPresence presenceOnline
liftIO $ putStrLn "Authenticating, now sending presence!"
sendPresence Nothing Nothing [] Nothing -- Simple presence
liftIO $ putStrLn "Echoing..."
fork echo fork echo
Left error -> liftIO $ putStrLn "Error: " ++ $ show exception return ()
Just error -> liftIO $ putStrLn "Error: " ++ $ show exception return ()
-- Pull message stanzas, verify that they originate from a `full' XMPP -- Pull message stanzas, verify that they originate from a `full' XMPP
-- address, and, if so, `echo' the message back. -- address, and, if so, `echo' the message back.
echo :: XMPP ()
echo :: XMPPThread () -- TODO: XMPP ()? XMPP?
echo = forever $ do echo = forever $ do
result <- pullMessage result <- pullMessage
case result of case result of
Right message -> Right message ->
if messageFrom message /= Nothing && isFull $ messageFrom message if (isJust $ messageFrom message) &&
then do (isFull $ fromJust $ messageFrom message) then do
sendMessage (messageFrom message) (messageType message) Nothing [] -- TODO: May not set from.
sendMessage $ Message Nothing (messageTo message) (messageFrom message) Nothing (messageType message) (messagePayload message)
liftIO $ putStrLn "Message echoed!" liftIO $ putStrLn "Message echoed!"
else liftIO $ putStrLn "Message sender is not set or is bare!" else liftIO $ putStrLn "Message sender is not set or is bare!"
Left exception -> liftIO $ putStrLn "Error: " ++ $ show exception Left exception -> liftIO $ putStrLn "Error: "

3
pontarius.cabal

@ -75,6 +75,9 @@ Library
, Data.Conduit.TLS , Data.Conduit.TLS
GHC-Options: -Wall GHC-Options: -Wall
Executable pontarius-echoclient
hs-source-dirs: source
Main-Is: ../examples/EchoClient.hs
Source-Repository head Source-Repository head
Type: git Type: git

2
source/Network/XMPP.hs

@ -38,6 +38,8 @@ module Network.XMPP
-- for addressing entities in the network. It is somewhat similar to an e-mail -- for addressing entities in the network. It is somewhat similar to an e-mail
-- address but contains three parts instead of two: -- address but contains three parts instead of two:
, JID(..) , JID(..)
, isBare
, isFull
-- * Stanzas -- * Stanzas
-- | @Stanzas@ are the the smallest unit of communication in @XMPP@. They come -- | @Stanzas@ are the the smallest unit of communication in @XMPP@. They come
-- in 3 flavors: -- in 3 flavors:

2
source/Network/XMPP/JID.hs

@ -54,7 +54,7 @@ data JID = JID { -- | The @localpart@ of a JID is an optional identifier placed
-- the entity associated with an XMPP localpart at a domain -- the entity associated with an XMPP localpart at a domain
-- (i.e., @localpart\@domainpart/resourcepart@). -- (i.e., @localpart\@domainpart/resourcepart@).
, resourcepart :: !(Maybe Text) , resourcepart :: !(Maybe Text)
} } deriving Eq
instance Show JID where instance Show JID where
show (JID nd dmn res) = show (JID nd dmn res) =

1
source/Network/XMPP/SASL.hs

@ -63,4 +63,5 @@ xmppSASL creds = runErrorT $ do
-- the XMPP mechanism attribute. -- the XMPP mechanism attribute.
credsToName :: SASLCredentials -> Text credsToName :: SASLCredentials -> Text
credsToName (DIGEST_MD5Credentials _ _ _) = "DIGEST-MD5" credsToName (DIGEST_MD5Credentials _ _ _) = "DIGEST-MD5"
credsToName (PLAINCredentials _ _ _) = "PLAIN"
credsToName c = error $ "credsToName failed for " ++ (show c) credsToName c = error $ "credsToName failed for " ++ (show c)

2
source/Network/XMPP/SASL/PLAIN.hs

@ -51,7 +51,7 @@ xmppPLAIN :: Maybe 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 $ plainMessage authzid authcid passwd Just $ Text.decodeUtf8 $ B64.encode $ Text.encodeUtf8 $ plainMessage authzid authcid passwd
lift $ pushElement saslResponse2E lift $ pushElement saslResponse2E
e <- lift pullElement e <- lift pullElement
case e of case e of

Loading…
Cancel
Save