diff options
Diffstat (limited to 'Presence')
-rw-r--r-- | Presence/XMPPServer.hs | 45 |
1 files changed, 35 insertions, 10 deletions
diff --git a/Presence/XMPPServer.hs b/Presence/XMPPServer.hs index 5008213c..ba542909 100644 --- a/Presence/XMPPServer.hs +++ b/Presence/XMPPServer.hs | |||
@@ -2,7 +2,7 @@ | |||
2 | {-# LANGUAGE ScopedTypeVariables #-} | 2 | {-# LANGUAGE ScopedTypeVariables #-} |
3 | {-# LANGUAGE ViewPatterns #-} | 3 | {-# LANGUAGE ViewPatterns #-} |
4 | {-# LANGUAGE TupleSections #-} | 4 | {-# LANGUAGE TupleSections #-} |
5 | module XMPPServer ( listenForXmppClients ) where | 5 | module XMPPServer where -- ( listenForXmppClients ) where |
6 | 6 | ||
7 | import Data.HList.TypeEqGeneric1() | 7 | import Data.HList.TypeEqGeneric1() |
8 | import Data.HList.TypeCastGeneric1() | 8 | import Data.HList.TypeCastGeneric1() |
@@ -23,7 +23,10 @@ import Data.HList | |||
23 | import AdaptServer | 23 | import AdaptServer |
24 | import Text.XML.HaXml.Lex (xmlLex) | 24 | import Text.XML.HaXml.Lex (xmlLex) |
25 | import Text.XML.HaXml.Parse (xmlParseWith,element,{-doctypedecl,-}processinginstruction,elemOpenTag,elemCloseTag) | 25 | import Text.XML.HaXml.Parse (xmlParseWith,element,{-doctypedecl,-}processinginstruction,elemOpenTag,elemCloseTag) |
26 | import Text.XML.HaXml.Types as Hax (ElemTag,QName(..),Namespace(..),Element(..),Content(..),AttValue(..)) | 26 | import Text.XML.HaXml.Types as Hax hiding (Element) -- (ElemTag,QName(..),Namespace(..),Element(..),Content(..),AttValue(..)) |
27 | import qualified Text.XML.HaXml.Types as Hax (Element(..)) | ||
28 | import Text.XML.HaXml.Posn (Posn) | ||
29 | import Text.XML.HaXml.Lex (TokenT) | ||
27 | import qualified Text.XML.HaXml.Pretty as PP | 30 | import qualified Text.XML.HaXml.Pretty as PP |
28 | import Text.PrettyPrint | 31 | import Text.PrettyPrint |
29 | import Data.Maybe | 32 | import Data.Maybe |
@@ -199,11 +202,11 @@ doCon st elem cont = do | |||
199 | instance Show Hax.ElemTag where | 202 | instance Show Hax.ElemTag where |
200 | show _ = "elemtag" | 203 | show _ = "elemtag" |
201 | 204 | ||
202 | data XmppObject e i t c | 205 | data XmppObject |
203 | = Element e | 206 | = Element (Hax.Element Posn) |
204 | | ProcessingInstruction i | 207 | | ProcessingInstruction Hax.ProcessingInstruction |
205 | | OpenTag t | 208 | | OpenTag ElemTag |
206 | | CloseTag c | 209 | | CloseTag () |
207 | deriving Show | 210 | deriving Show |
208 | 211 | ||
209 | pp (Element e) = PP.element e | 212 | pp (Element e) = PP.element e |
@@ -211,7 +214,28 @@ pp o = fromString (show o) | |||
211 | 214 | ||
212 | streamName = QN (Namespace {nsPrefix= "stream" , nsURI="http://etherx.jabber.org/streams" }) "stream" | 215 | streamName = QN (Namespace {nsPrefix= "stream" , nsURI="http://etherx.jabber.org/streams" }) "stream" |
213 | 216 | ||
214 | xmppParse ls = | 217 | newtype TryParse p x e = Try (Either e p,[x]) |
218 | |||
219 | instance Monad (TryParse p x) where | ||
220 | return v = Try (Left v,[]) | ||
221 | Try (Left m,xs) >>= k = k m | ||
222 | Try (Right e,xs) >>= _ = Try (Right e,xs) | ||
223 | |||
224 | runTryParse (Try p) = p | ||
225 | mapRight f (Right x,ls) = (Right (f x),ls) | ||
226 | mapRight f (Left y,ls) = (Left y ,ls) | ||
227 | |||
228 | xmppParse :: [(Posn, TokenT)] -> (Either String XmppObject, [(Posn, TokenT)]) | ||
229 | xmppParse ls = runTryParse $ do | ||
230 | let xml tag = mapRight tag . flip xmlParseWith ls | ||
231 | Try . xml Element $ element | ||
232 | Try . xml OpenTag $ elemOpenTag | ||
233 | Try . xml CloseTag $ elemCloseTag streamName | ||
234 | Try . xml ProcessingInstruction $ processinginstruction | ||
235 | |||
236 | {- | ||
237 | xmppParseOld :: [(Posn, TokenT)] -> (Either String XmppObject, [(Posn, TokenT)]) | ||
238 | xmppParseOld ls = | ||
215 | case xmlParseWith element ls of | 239 | case xmlParseWith element ls of |
216 | (Right e,rs) -> (Right (Element e), rs) | 240 | (Right e,rs) -> (Right (Element e), rs) |
217 | (Left _,_) -> | 241 | (Left _,_) -> |
@@ -219,11 +243,12 @@ xmppParse ls = | |||
219 | (Right e,rs) -> (Right (OpenTag e),rs) | 243 | (Right e,rs) -> (Right (OpenTag e),rs) |
220 | (Left _,_) -> | 244 | (Left _,_) -> |
221 | case xmlParseWith (elemCloseTag streamName) ls of | 245 | case xmlParseWith (elemCloseTag streamName) ls of |
222 | (Right e,rs) -> (Right (CloseTag e),rs) | 246 | (Right (),rs) -> (Right (CloseTag ()),rs) |
223 | (Left _,_) -> | 247 | (Left _,_) -> |
224 | case xmlParseWith processinginstruction ls of | 248 | case xmlParseWith processinginstruction ls of |
225 | (Right e,rs) -> (Right (ProcessingInstruction e),rs) | 249 | (Right e,rs) -> (Right (ProcessingInstruction e),rs) |
226 | (Left err,rs) -> (Left err,rs) | 250 | (Left err,rs) -> (Left err,rs) |
251 | -} | ||
227 | 252 | ||
228 | 253 | ||
229 | 254 | ||