summaryrefslogtreecommitdiff
diff options
context:
space:
mode:
-rw-r--r--Presence/NestingXML.hs36
-rw-r--r--Presence/XMPP.hs19
2 files changed, 22 insertions, 33 deletions
diff --git a/Presence/NestingXML.hs b/Presence/NestingXML.hs
index b90d0caa..5956b34d 100644
--- a/Presence/NestingXML.hs
+++ b/Presence/NestingXML.hs
@@ -2,28 +2,29 @@ module NestingXML where
2 2
3import Data.Conduit 3import Data.Conduit
4import Data.XML.Types 4import Data.XML.Types
5import Control.Monad.Reader 5import Control.Monad.State
6-- import qualified Text.XML.Stream.Parse as Parse (content) 6-- import qualified Text.XML.Stream.Parse as Parse (content)
7 7
8type NestingXML o m a = ReaderT Int (ConduitM Event o m) a 8type NestingXML o m a = StateT Int (ConduitM Event o m) a
9 9
10runNestingXML :: NestingXML o m a -> Int -> ConduitM Event o m a 10runNestingXML :: NestingXML o m a -> Int -> ConduitM Event o m (a,Int)
11runNestingXML = runReaderT 11runNestingXML = runStateT
12 12
13doNestingXML :: NestingXML o m a -> ConduitM Event o m a 13doNestingXML :: Monad m => NestingXML o m a -> ConduitM Event o m a
14doNestingXML = flip runNestingXML 0 14doNestingXML = fmap fst . flip runNestingXML 0
15 15
16nesting :: Monad m => NestingXML o m Int 16nesting :: Monad m => NestingXML o m Int
17nesting = ask 17nesting = get
18 18
19awaitXML :: Monad m => NestingXML o m (Maybe Event) 19awaitXML :: Monad m => NestingXML o m (Maybe Event)
20awaitXML = do 20awaitXML = do
21 lvl <- get
21 xml <- lift await 22 xml <- lift await
22 let f = case xml of 23 put $case xml of
23 Just (EventBeginElement _ _) -> (+1) 24 Just (EventBeginElement _ _) -> lvl+1
24 Just (EventEndElement _) -> (subtract 1) 25 Just (EventEndElement _) -> lvl-1
25 _ -> id 26 _ -> lvl
26 local f (return xml) 27 return xml
27 28
28withXML 29withXML
29 :: Monad m => (Event -> NestingXML o m ()) -> NestingXML o m () 30 :: Monad m => (Event -> NestingXML o m ()) -> NestingXML o m ()
@@ -31,30 +32,31 @@ withXML f = do
31 xml <- awaitXML 32 xml <- awaitXML
32 maybe (return ()) f xml 33 maybe (return ()) f xml
33 34
35
34maybeXML 36maybeXML
35 :: Monad m => NestingXML o m a -> (Event -> NestingXML o m a) -> NestingXML o m a 37 :: Monad m => NestingXML o m a -> (Event -> NestingXML o m a) -> NestingXML o m a
36maybeXML whenNothing withJust = do 38maybeXML whenNothing withJust = do
37 xml <- awaitXML 39 xml <- awaitXML
38 maybe whenNothing withJust xml 40 maybe whenNothing withJust xml
39 41
40awaitCloser :: MonadIO m => Int -> NestingXML o m () 42
43awaitCloser :: Monad m => Int -> NestingXML o m ()
41awaitCloser lvl = do 44awaitCloser lvl = do
42 fix $ \loop -> do 45 fix $ \loop -> do
43 lvl' <- nesting 46 lvl' <- nesting
44 when (lvl' >= lvl) $ do 47 when (lvl' >= lvl) $ do
45 withXML $ \xml -> do 48 withXML $ \xml -> do
46 liftIO $ putStrLn $ "awaitCloser: "++show (lvl',lvl,xml)
47 loop 49 loop
48 50
49nextElement :: MonadIO m => NestingXML o m (Maybe Event) 51nextElement :: Monad m => NestingXML o m (Maybe Event)
50nextElement = do 52nextElement = do
51 lvl <- nesting 53 lvl <- nesting
52 fix $ \loop -> do 54 fix $ \loop -> do
53 xml <- awaitXML 55 xml <- awaitXML
54 liftIO $ putStrLn $ "nextElement: "++show xml
55 case xml of 56 case xml of
56 Nothing -> return Nothing 57 Nothing -> return Nothing
57 Just (EventBeginElement _ _) -> return xml 58 Just (EventBeginElement _ _) -> do
59 return xml
58 Just _ -> do 60 Just _ -> do
59 lvl' <- nesting 61 lvl' <- nesting
60 if (lvl'>=lvl) then loop 62 if (lvl'>=lvl) then loop
diff --git a/Presence/XMPP.hs b/Presence/XMPP.hs
index 5c5cbaef..e15b10cc 100644
--- a/Presence/XMPP.hs
+++ b/Presence/XMPP.hs
@@ -321,35 +321,22 @@ fromClient session cmdChan = doNestingXML $ do
321 log "begin-doc" 321 log "begin-doc"
322 withXML $ \xml -> do 322 withXML $ \xml -> do
323 withJust (elementAttrs "stream" xml) $ \stream_attrs -> do 323 withJust (elementAttrs "stream" xml) $ \stream_attrs -> do
324 log $ "stream " <++> bshow stream_attrs 324 log $ "stream atributes: " <++> bshow stream_attrs
325 host <- liftIO $ do 325 host <- liftIO $ do
326 jid <- getJID session 326 jid <- getJID session
327 names <- getNamesForPeer (peer jid) 327 names <- getNamesForPeer (peer jid)
328 return (S.decodeUtf8 . head $ names) 328 return (S.decodeUtf8 . head $ names)
329 send $ greet host 329 send $ greet host
330 330
331{-
332 fix $ \loop -> do
333 xml <- mawait
334 log $ bshow xml
335 let isIQ n = n=="{jabber:client}iq"
336 case xml of
337 _ | eventIsEndElement xml -> return ()
338 tag@(EventBeginElement name attrs) | isIQ name -> doIQ session cmdChan tag >> loop
339
340 tag@(EventBeginElement _ _) -> do
341 xs <- gatherElement tag Seq.empty
342 prettyPrint "client-in: ignoring..." (toList xs)
343 loop
344 _ -> loop
345-}
346 fix $ \loop -> do 331 fix $ \loop -> do
347 whenJust nextElement $ \stanza -> do 332 whenJust nextElement $ \stanza -> do
348 stanza_lvl <- nesting 333 stanza_lvl <- nesting
334
349 let unhandledStanza = liftIO $ putStrLn ("ignoring stanza: "++show stanza) 335 let unhandledStanza = liftIO $ putStrLn ("ignoring stanza: "++show stanza)
350 case () of 336 case () of
351 _ | stanza `isIQOf` iqTypeSet -> handleIQSet session cmdChan stanza 337 _ | stanza `isIQOf` iqTypeSet -> handleIQSet session cmdChan stanza
352 _ | otherwise -> unhandledStanza 338 _ | otherwise -> unhandledStanza
339
353 awaitCloser stanza_lvl 340 awaitCloser stanza_lvl
354 loop 341 loop
355 342