Browse Source

cleaned up imports and comments

master
Jon Kristensen 15 years ago
parent
commit
cf453923c1
  1. 54
      Network/XMPP/Utilities.hs

54
Network/XMPP/Utilities.hs

@ -1,50 +1,34 @@
-- Copyright © 2010-2011 Jon Kristensen. See the LICENSE file in the Pontarius -- Copyright © 2010-2011 Jon Kristensen. See the LICENSE file in the Pontarius
-- XMPP distribution for more details. -- XMPP distribution for more details.
{-# OPTIONS_HADDOCK hide #-} -- This module currently converts XML elements to strings.
{-# LANGUAGE OverloadedStrings #-}
-- TODO: Use -fno-cse? http://cvs.haskell.org/Hugs/pages/libraries/base/System-IO-Unsafe.html -- TODO: Use -fno-cse? http://cvs.haskell.org/Hugs/pages/libraries/base/System-IO-Unsafe.html
-- TODO: Remove elementsToString?
{-# OPTIONS_HADDOCK hide #-}
-- TODO: Document this module {-# LANGUAGE OverloadedStrings #-}
-- TODO: Make is possible to customize characters
-- TODO: Make it possible to customize length
module Network.XMPP.Utilities ( elementToString module Network.XMPP.Utilities ( elementToString
, elementsToString, testElement ) where , elementsToString, testElement ) where
import Prelude hiding (concat) import Prelude hiding (concat)
import Data.Word
import Data.XML.Types import Data.ByteString (ByteString, concat)
import System.Crypto.Random import Data.ByteString.Char8 (unpack)
import System.Random import Data.Enumerator (($$), Stream (Chunks), Enumerator, Step (Continue), joinI, run_, returnI)
import qualified Data.ByteString as DB
import qualified Data.Map as DM
import qualified Data.Text as DT
import qualified Data.ByteString.Char8 as DBC
import Data.Enumerator (($$), Stream (Chunks), Enumerator, Iteratee, Step (Continue), continue, joinI,
run, run_, yield, returnI)
import Data.Enumerator.List (consume) import Data.Enumerator.List (consume)
import Text.XML.Enumerator.Document (toEvents) import Data.XML.Types (Document (..), Element (..), Event (..), Name (..), Prologue (..))
import Text.XML.Enumerator.Render (renderBytes) import Text.XML.Enumerator.Render (renderBytes)
import Data.Maybe (fromJust) import Text.XML.Enumerator.Document (toEvents)
import Data.ByteString (concat, unpack)
import Data.List (tail)
import System.IO.Unsafe (unsafePerformIO)
{-# NOINLINE elementToString #-}
-- ============================================================================= import System.IO.Unsafe (unsafePerformIO)
-- XML Utilities
-- =============================================================================
-- TODO: Remove? -- Converts the Element objects to a document, converts it into Events, strips
-- the DocumentBegin event, generates a ByteString, and converts it into a
-- String, aggregates the results and returns a string.
elementsToString :: [Element] -> String elementsToString :: [Element] -> String
@ -56,22 +40,20 @@ elementsToString (e:es) = (elementToString (Just e)) ++ (elementsToString es)
-- the DocumentBegin event, generates a ByteString, and converts it into a -- the DocumentBegin event, generates a ByteString, and converts it into a
-- String. -- String.
{-# NOINLINE elementToString #-}
elementToString :: Maybe Element -> String elementToString :: Maybe Element -> String
elementToString Nothing = "" elementToString Nothing = ""
elementToString (Just elem) = DBC.unpack $ concat $ unsafePerformIO $ do elementToString (Just elem) = unpack $ concat $ unsafePerformIO $ do
r <- run_ $ events $$ (joinI $ renderBytes $$ consume) r <- run_ $ events $$ (joinI $ renderBytes $$ consume)
return r return r
where where
-- Enumerator that "produces" the events to convert to the document -- Enumerator that "produces" the events to convert to the document
events :: Enumerator Event IO [DB.ByteString] events :: Enumerator Event IO [ByteString]
events (Continue more) = more $ Chunks (tail $ toEvents $ dummyDoc elem) events (Continue more) = more $ Chunks (tail $ toEvents $ dummyDoc elem)
events step = returnI step events step = returnI step
dummyDoc :: Element -> Document dummyDoc :: Element -> Document
dummyDoc e = Document (Prologue [] Nothing []) elem [] dummyDoc e = Document (Prologue [] Nothing []) elem []
testElement :: Element
testElement = Element ("{http://example.com/ns/my-namespace}my-name" :: Name) [] []

Loading…
Cancel
Save