Browse Source

removed sConPush, session now starts without connection, added inline connection method

xml-types-pickle updated
master
Philipp Balzarek 14 years ago
parent
commit
e0b97dacf8
  1. 39
      src/Network/XMPP.hs
  2. 1
      src/Network/XMPP/Concurrent/Monad.hs
  3. 4
      src/Network/XMPP/Concurrent/Threads.hs
  4. 44
      src/Network/XMPP/Monad.hs
  5. 6
      src/Network/XMPP/Pickle.hs
  6. 31
      src/Network/XMPP/SASL.hs
  7. 2
      src/Network/XMPP/Stream.hs
  8. 8
      src/Network/XMPP/TLS.hs
  9. 5
      src/Network/XMPP/Types.hs
  10. 25
      src/Tests.hs
  11. 40
      src/Text/XML/Stream/Elements.hs
  12. 2
      xml-types-pickle

39
src/Network/XMPP.hs

@ -40,8 +40,8 @@ module Network.XMPP
, module Network.XMPP.Types , module Network.XMPP.Types
, module Network.XMPP.Presence , module Network.XMPP.Presence
, module Network.XMPP.Message , module Network.XMPP.Message
-- , connectXMPP , xmppConnect
, sessionConnect , xmppNewSession
) where ) where
import Data.Text as Text import Data.Text as Text
@ -58,35 +58,8 @@ import Network.XMPP.Stream
import Network.XMPP.TLS import Network.XMPP.TLS
import Network.XMPP.Types import Network.XMPP.Types
import System.IO xmppConnect :: HostName -> Text -> XMPPConMonad ()
xmppConnect address hostname = xmppRawConnect address hostname >> xmppStartStream
--fromHandle :: Handle -> Text -> Text -> Maybe Text -> Text -> IO ((), XMPPState)
-- fromHandle :: Handle -> Text -> Text -> Maybe Text -> Text -> XMPPThread a
-- -> IO ((), XMPPState)
-- fromHandle handle hostname username rsrc password a =
-- xmppFromHandle handle hostname username rsrc $ do
-- xmppStartStream
-- -- this will check whether the server supports tls
-- -- on it's own
-- xmppStartTLS exampleParams
-- xmppSASL password
-- xmppBind rsrc
-- xmppSession
-- _ <- runThreaded a
-- return ()
-- connectXMPP :: HostName -> Text -> Text -> Maybe Text
-- -> Text -> XMPPThread a -> IO ((), XMPPState)
-- connectXMPP host hostname username rsrc passwd a = do
-- con <- connectTo host (PortNumber 5222)
-- hSetBuffering con NoBuffering
-- fromHandle con hostname username rsrc passwd a
sessionConnect :: HostName -> Text -> Text
-> Maybe Text -> XMPPThread a -> IO (a, XMPPConState)
sessionConnect host hostname username rsrc a = do
con <- connectTo host (PortNumber 5222)
hSetBuffering con NoBuffering
xmppFromHandle con hostname username rsrc $
xmppStartStream >> runThreaded a
xmppNewSession :: XMPPThread a -> IO (a, XMPPConState)
xmppNewSession = withNewSession . runThreaded

1
src/Network/XMPP/Concurrent/Monad.hs

@ -162,7 +162,6 @@ withConnection a = do
putTMVar stateRef s' putTMVar stateRef s'
return res return res
sendPresence :: Presence -> XMPPThread () sendPresence :: Presence -> XMPPThread ()
sendPresence = sendS . PresenceS sendPresence = sendS . PresenceS

4
src/Network/XMPP/Concurrent/Threads.hs

@ -109,9 +109,7 @@ writeWorker stCh writeR = forever $ do
(write, next) <- atomically $ (,) <$> (write, next) <- atomically $ (,) <$>
takeTMVar writeR <*> takeTMVar writeR <*>
readTChan stCh readTChan stCh
outBS <- CL.sourceList (elementToEvents $ pickleElem stanzaP next) _ <- write $ renderElement (pickleElem stanzaP next)
$= XR.renderBytes def $$ CL.consume
_ <- forM outBS write
atomically $ putTMVar writeR write atomically $ putTMVar writeR write
-- Two streams: input and output. Threads read from input stream and write to output stream. -- Two streams: input and output. Threads read from input stream and write to output stream.

44
src/Network/XMPP/Monad.hs

@ -3,9 +3,11 @@
module Network.XMPP.Monad where module Network.XMPP.Monad where
import Control.Applicative((<$>)) import Control.Applicative((<$>))
import Control.Monad
import Control.Monad.IO.Class import Control.Monad.IO.Class
import Control.Monad.Trans.Class import Control.Monad.Trans.Class
--import Control.Monad.Trans.Resource --import Control.Monad.Trans.Resource
import Control.Concurrent
import Control.Monad.Trans.State import Control.Monad.Trans.State
import Data.ByteString as BS import Data.ByteString as BS
@ -30,16 +32,16 @@ import Text.XML.Stream.Render as XR
pushN :: Element -> XMPPConMonad () pushN :: Element -> XMPPConMonad ()
pushN x = do pushN x = do
sink <- gets sConPush sink <- gets sConPushBS
lift . sink $ elementToEvents x liftIO . sink $ renderElement x
push :: Stanza -> XMPPConMonad () push :: Stanza -> XMPPConMonad ()
push = pushN . pickleElem stanzaP push = pushN . pickleElem stanzaP
pushOpen :: Element -> XMPPConMonad () pushOpen :: Element -> XMPPConMonad ()
pushOpen e = do pushOpen e = do
sink <- gets sConPush sink <- gets sConPushBS
lift . sink $ openElementToEvents e liftIO . sink $ renderOpenElement e
return () return ()
pulls :: Sink Event IO b -> XMPPConMonad b pulls :: Sink Event IO b -> XMPPConMonad b
@ -71,14 +73,12 @@ xmppFromHandle handle hostname username res f = do
let st = XMPPConState let st = XMPPConState
src src
(raw) (raw)
(\xs -> CL.sourceList xs
$$ XR.renderBytes def =$ sinkHandle' handle)
(BS.hPut handle) (BS.hPut handle)
(Just handle) (Just handle)
(SF Nothing [] []) (SF Nothing [] [])
False False
hostname (Just hostname)
username (Just username)
res res
runStateT f st runStateT f st
@ -108,8 +108,24 @@ sinkHandle' h =
(return ()) (return ())
close = return () close = return ()
xmppConnect :: HostName -> Text -> XMPPConMonad () zeroSource :: Source IO output
xmppConnect host hostname = do zeroSource = sourceState () (\_ -> forever $ threadDelay 10000000)
xmppZeroConState :: XMPPConState
xmppZeroConState = XMPPConState
{ sConSrc = zeroSource
, sRawSrc = zeroSource
, sConPushBS = (\_ -> return ())
, sConHandle = Nothing
, sFeatures = SF Nothing [] []
, sHaveTLS = False
, sHostname = Nothing
, sUsername = Nothing
, sResource = Nothing
}
xmppRawConnect :: HostName -> Text -> XMPPConMonad ()
xmppRawConnect host hostname = do
uname <- gets sUsername uname <- gets sUsername
con <- liftIO $ do con <- liftIO $ do
con <- connectTo host (PortNumber 5222) con <- connectTo host (PortNumber 5222)
@ -120,15 +136,15 @@ xmppConnect host hostname = do
let st = XMPPConState let st = XMPPConState
src src
(raw) (raw)
(\xs -> CL.sourceList xs
$$ XR.renderBytes def =$ sinkHandle' con)
(BS.hPut con) (BS.hPut con)
(Just con) (Just con)
(SF Nothing [] []) (SF Nothing [] [])
False False
hostname (Just hostname)
uname uname
Nothing Nothing
put st put st
return ()
withNewSession :: XMPPConMonad a -> IO (a, XMPPConState)
withNewSession action = do
runStateT action xmppZeroConState

6
src/Network/XMPP/Pickle.hs

@ -10,6 +10,7 @@ module Network.XMPP.Pickle where
import Data.XML.Types import Data.XML.Types
import Data.XML.Pickle import Data.XML.Pickle
import Text.XML.Stream.Elements
mbToBool :: Maybe t -> Bool mbToBool :: Maybe t -> Bool
mbToBool (Just _) = True mbToBool (Just _) = True
@ -51,14 +52,11 @@ right :: Either [Char] t -> t
right (Left l) = error l right (Left l) = error l
right (Right r) = r right (Right r) = r
unpickleElem :: PU [Node] c -> Element -> c unpickleElem :: PU [Node] c -> Element -> c
unpickleElem p x = case unpickle (xpNodeElem p) x of unpickleElem p x = case unpickle (xpNodeElem p) x of
Left l -> error $ l ++ "\n saw: " ++ show x Left l -> error $ l ++ "\n saw: " ++ ppElement x
Right r -> r Right r -> r
pickleElem :: PU [Node] a -> a -> Element pickleElem :: PU [Node] a -> a -> Element
pickleElem p = pickle $ xpNodeElem p pickleElem p = pickle $ xpNodeElem p

31
src/Network/XMPP/SASL.hs

@ -48,14 +48,27 @@ saslResponse2E =
[] []
[] []
xmppSASL :: Text -> XMPPConMonad () xmppSASL:: Text -> Text -> XMPPConMonad (Either String Text)
xmppSASL passwd = do xmppSASL uname passwd = do
realm <- gets sHostname
case realm of
Just realm' -> do
xmppStartSASL realm' uname passwd
modify (\s -> s{sUsername = Just uname})
return $ Right uname
Nothing -> return $ Left "No connection found"
xmppStartSASL :: Text
-> Text
-> Text
-> XMPPConMonad ()
xmppStartSASL realm username passwd = do
mechanisms <- gets $ saslMechanisms . sFeatures mechanisms <- gets $ saslMechanisms . sFeatures
unless ("DIGEST-MD5" `elem` mechanisms) . error $ "No usable auth mechanism: " ++ show mechanisms unless ("DIGEST-MD5" `elem` mechanisms) . error $ "No usable auth mechanism: " ++ show mechanisms
pushN $ saslInitE "DIGEST-MD5" pushN $ saslInitE "DIGEST-MD5"
Right challenge <- B64.decode . Text.encodeUtf8<$> pullPickle challengePickle Right challenge <- B64.decode . Text.encodeUtf8<$> pullPickle challengePickle
let Right pairs = toPairs challenge let Right pairs = toPairs challenge
pushN . saslResponseE =<< createResponse passwd pairs pushN . saslResponseE =<< createResponse realm username passwd pairs
challenge2 <- pullPickle (xpEither failurePickle challengePickle) challenge2 <- pullPickle (xpEither failurePickle challengePickle)
case challenge2 of case challenge2 of
Left x -> error $ show x Left x -> error $ show x
@ -65,13 +78,17 @@ xmppSASL passwd = do
xmppRestartStream xmppRestartStream
return () return ()
createResponse :: Text -> [(BS8.ByteString, BS8.ByteString)] -> XMPPConMonad Text createResponse :: Text
createResponse passwd' pairs = do -> Text
-> Text
-> [(BS8.ByteString, BS8.ByteString)]
-> XMPPConMonad Text
createResponse hostname username passwd' pairs = do
let Just qop = L.lookup "qop" pairs let Just qop = L.lookup "qop" pairs
let Just nonce = L.lookup "nonce" pairs let Just nonce = L.lookup "nonce" pairs
uname <- Text.encodeUtf8 <$> gets sUsername let uname = Text.encodeUtf8 username
let passwd = Text.encodeUtf8 passwd' let passwd = Text.encodeUtf8 passwd'
realm <- Text.encodeUtf8 <$> gets sHostname let realm = Text.encodeUtf8 hostname
g <- liftIO $ Random.newStdGen g <- liftIO $ Random.newStdGen
let cnonce = BS.tail . BS.init . let cnonce = BS.tail . BS.init .
B64.encode . BS.pack . take 8 $ Random.randoms g B64.encode . BS.pack . take 8 $ Random.randoms g

2
src/Network/XMPP/Stream.hs

@ -40,7 +40,7 @@ openElementFromEvents = do
xmppStartStream :: XMPPConMonad () xmppStartStream :: XMPPConMonad ()
xmppStartStream = do xmppStartStream = do
hostname <- gets sHostname hostname <- gets sHostname
pushOpen $ pickleElem pickleStream ("1.0",Nothing, Just hostname) pushOpen $ pickleElem pickleStream ("1.0",Nothing, hostname)
features <- pulls xmppStream features <- pulls xmppStream
modify (\s -> s {sFeatures = features}) modify (\s -> s {sFeatures = features})
return () return ()

8
src/Network/XMPP/TLS.hs

@ -26,7 +26,8 @@ starttlsE =
Element "{urn:ietf:params:xml:ns:xmpp-tls}starttls" [] [] Element "{urn:ietf:params:xml:ns:xmpp-tls}starttls" [] []
exampleParams :: TLS.TLSParams exampleParams :: TLS.TLSParams
exampleParams = TLS.TLSParams { pConnectVersion = TLS.TLS10 exampleParams = TLS.defaultParams
{pConnectVersion = TLS.TLS10
, pAllowedVersions = [TLS.SSL3, TLS.TLS10, TLS.TLS11] , pAllowedVersions = [TLS.SSL3, TLS.TLS10, TLS.TLS11]
, pCiphers = [TLS.cipher_AES128_SHA1] , pCiphers = [TLS.cipher_AES128_SHA1]
, pCompressions = [TLS.nullCompression] , pCompressions = [TLS.nullCompression]
@ -35,7 +36,8 @@ exampleParams = TLS.TLSParams { pConnectVersion = TLS.TLS10
, pCertificates = [] -- TODO , pCertificates = [] -- TODO
, pLogging = TLS.defaultLogging -- TODO , pLogging = TLS.defaultLogging -- TODO
, onCertificatesRecv = \ certificate -> , onCertificatesRecv = \ certificate ->
return TLS.CertificateUsageAccept } return TLS.CertificateUsageAccept
}
xmppStartTLS :: TLS.TLSParams -> XMPPConMonad () xmppStartTLS :: TLS.TLSParams -> XMPPConMonad ()
xmppStartTLS params = do xmppStartTLS params = do
@ -49,8 +51,6 @@ xmppStartTLS params = do
{ sRawSrc = raw { sRawSrc = raw
-- , sConSrc = -- Note: this momentarily leaves us in an -- , sConSrc = -- Note: this momentarily leaves us in an
-- inconsistent state -- inconsistent state
, sConPush = \xs -> CL.sourceList xs
$$ XR.renderBytes def =$ snk
, sConPushBS = psh , sConPushBS = psh
}) })
xmppRestartStream xmppRestartStream

5
src/Network/XMPP/Types.hs

@ -610,13 +610,12 @@ data ServerFeatures = SF
data XMPPConState = XMPPConState data XMPPConState = XMPPConState
{ sConSrc :: Source IO Event { sConSrc :: Source IO Event
, sRawSrc :: Source IO BS.ByteString , sRawSrc :: Source IO BS.ByteString
, sConPush :: [Event] -> IO ()
, sConPushBS :: BS.ByteString -> IO () , sConPushBS :: BS.ByteString -> IO ()
, sConHandle :: Maybe Handle , sConHandle :: Maybe Handle
, sFeatures :: ServerFeatures , sFeatures :: ServerFeatures
, sHaveTLS :: Bool , sHaveTLS :: Bool
, sHostname :: Text , sHostname :: Maybe Text
, sUsername :: Text , sUsername :: Maybe Text
, sResource :: Maybe Text , sResource :: Maybe Text
} }

25
src/Tests.hs

@ -1,7 +1,6 @@
{-# LANGUAGE PackageImports, OverloadedStrings #-} {-# LANGUAGE PackageImports, OverloadedStrings, NoMonomorphismRestriction #-}
module Example where module Example where
import Network.XMPP
import Control.Concurrent import Control.Concurrent
import Control.Concurrent.STM import Control.Concurrent.STM
import Control.Monad import Control.Monad
@ -13,9 +12,11 @@ import qualified Data.Text as Text
import Data.XML.Pickle import Data.XML.Pickle
import Data.XML.Types import Data.XML.Types
import Network.XMPP
import Network.XMPP.Pickle import Network.XMPP.Pickle
import System.Environment import System.Environment
import Text.XML.Stream.Elements
testUser1 :: JID testUser1 :: JID
testUser1 = read "testuser1@species64739.dyndns.org/bot1" testUser1 = read "testuser1@species64739.dyndns.org/bot1"
@ -72,6 +73,9 @@ expect debug x y | x == y = debug "Ok."
sendUser failMSG sendUser failMSG
wait3 :: MonadIO m => m ()
wait3 = liftIO $ threadDelay 1000000
runMain :: (String -> STM ()) -> Int -> IO () runMain :: (String -> STM ()) -> Int -> IO ()
runMain debug number = do runMain debug number = do
let (we, them, active) = case number of let (we, them, active) = case number of
@ -80,16 +84,21 @@ runMain debug number = do
_ -> error "Need either 1 or 2" _ -> error "Need either 1 or 2"
let debug' = liftIO . atomically . let debug' = liftIO . atomically .
debug . (("Thread " ++ show number ++ ":") ++) debug . (("Thread " ++ show number ++ ":") ++)
sessionConnect "localhost" xmppNewSession $ do
"species64739.dyndns.org" debug' "running"
(fromJust $ node we) (resource we) $ do withConnection $ do
withConnection $ xmppSASL "pwd" xmppConnect "localhost" "species64739.dyndns.org"
xmppStartTLS exampleParams
saslResponse <- xmppSASL (fromJust $ node we) "pwd"
case saslResponse of
Right _ -> return ()
Left e -> error e
xmppThreadedBind (resource we) xmppThreadedBind (resource we)
withConnection $ xmppSession withConnection $ xmppSession
debug' "session standing"
sendPresence presenceOnline sendPresence presenceOnline
forkXMPP autoAccept forkXMPP autoAccept
forkXMPP iqResponder forkXMPP iqResponder
-- sendS . SPresence $ Presence Nothing (Just them) Nothing (Just Subscribe) Nothing Nothing Nothing []
when active . void . forkXMPP $ do when active . void . forkXMPP $ do
forM [1..10] $ \count -> do forM [1..10] $ \count -> do
let message = Text.pack . show $ node we let message = Text.pack . show $ node we
@ -99,7 +108,7 @@ runMain debug number = do
let answerPayload = unpickleElem payloadP let answerPayload = unpickleElem payloadP
(fromJust $ iqResultPayload answer) (fromJust $ iqResultPayload answer)
expect debug' (invertPayload payload) answerPayload expect debug' (invertPayload payload) answerPayload
liftIO $ threadDelay 500000 liftIO $ threadDelay 100000
sendUser "All tests done" sendUser "All tests done"
liftIO . forever $ threadDelay 10000000 liftIO . forever $ threadDelay 10000000
return () return ()

40
src/Text/XML/Stream/Elements.hs

@ -4,20 +4,23 @@ import Control.Applicative ((<$>))
import Control.Monad.Trans.Class import Control.Monad.Trans.Class
import Control.Monad.Trans.Resource as R import Control.Monad.Trans.Resource as R
import Data.Text as T import qualified Data.ByteString as BS
import Text.XML.Unresolved import qualified Data.Text as Text
import qualified Data.Text.Encoding as Text
import Data.XML.Types import Data.XML.Types
import qualified Text.XML.Stream.Render as TXSR
import Text.XML.Unresolved as TXU
import Data.Conduit as C import Data.Conduit as C
import Data.Conduit.List as CL import Data.Conduit.List as CL
import Text.XML.Stream.Parse import System.IO.Unsafe(unsafePerformIO)
compressNodes :: [Node] -> [Node] compressNodes :: [Node] -> [Node]
compressNodes [] = [] compressNodes [] = []
compressNodes [x] = [x] compressNodes [x] = [x]
compressNodes (NodeContent (ContentText x) : NodeContent (ContentText y) : z) = compressNodes (NodeContent (ContentText x) : NodeContent (ContentText y) : z) =
compressNodes $ NodeContent (ContentText $ x `T.append` y) : z compressNodes $ NodeContent (ContentText $ x `Text.append` y) : z
compressNodes (x:xs) = x : compressNodes xs compressNodes (x:xs) = x : compressNodes xs
elementFromEvents :: R.MonadThrow m => C.Sink Event m Element elementFromEvents :: R.MonadThrow m => C.Sink Event m Element
@ -27,7 +30,7 @@ elementFromEvents = do
Just (EventBeginElement n as) -> goE n as Just (EventBeginElement n as) -> goE n as
_ -> lift $ R.monadThrow $ InvalidEventStream $ "not an element: " ++ show x _ -> lift $ R.monadThrow $ InvalidEventStream $ "not an element: " ++ show x
where where
many f = many' f =
go id go id
where where
go front = do go front = do
@ -38,7 +41,7 @@ elementFromEvents = do
dropReturn x = CL.drop 1 >> return x dropReturn x = CL.drop 1 >> return x
goE n as = do goE n as = do
CL.drop 1 CL.drop 1
ns <- many goN ns <- many' goN
y <- CL.head y <- CL.head
if y == Just (EventEndElement n) if y == Just (EventEndElement n)
then return $ Element n as $ compressNodes ns then return $ Element n as $ compressNodes ns
@ -57,15 +60,10 @@ elementFromEvents = do
openElementToEvents :: Element -> [Event] openElementToEvents :: Element -> [Event]
openElementToEvents (Element name as ns) = EventBeginElement name as : goN ns [] openElementToEvents (Element name as ns) = EventBeginElement name as : goN ns []
where where
goM [] = id goE (Element name' as' ns') =
goM [x] = (goM' x :) (EventBeginElement name' as' :)
goM (x:xs) = (goM' x :) . goM xs . goN ns'
goM' (MiscInstruction i) = EventInstruction i . (EventEndElement name' :)
goM' (MiscComment t) = EventComment t
goE (Element name as ns) =
(EventBeginElement name as :)
. goN ns
. (EventEndElement name :)
goN [] = id goN [] = id
goN [x] = goN' x goN [x] = goN' x
goN (x:xs) = goN' x . goN xs goN (x:xs) = goN' x . goN xs
@ -76,3 +74,15 @@ openElementToEvents (Element name as ns) = EventBeginElement name as : goN ns []
elementToEvents :: Element -> [Event] elementToEvents :: Element -> [Event]
elementToEvents e@(Element name _ _) = openElementToEvents e ++ [EventEndElement name] elementToEvents e@(Element name _ _) = openElementToEvents e ++ [EventEndElement name]
renderOpenElement :: Element -> BS.ByteString
renderOpenElement e = Text.encodeUtf8 . Text.concat . unsafePerformIO
$ CL.sourceList (openElementToEvents e) $$ TXSR.renderText def =$ CL.consume
renderElement :: Element -> BS.ByteString
renderElement e = Text.encodeUtf8 . Text.concat . unsafePerformIO
$ CL.sourceList (elementToEvents e) $$ TXSR.renderText def =$ CL.consume
ppElement :: Element -> String
ppElement = Text.unpack . Text.decodeUtf8 . renderElement

2
xml-types-pickle

@ -1 +1 @@
Subproject commit e417f9ddc6cc74dc06fabadad810da10b8e25d84 Subproject commit 73f8caedfe389646647354badc7700eccf40442f
Loading…
Cancel
Save