You can not select more than 25 topics Topics must start with a letter or number, can include dashes ('-') and can be up to 35 characters long.

48 lines
1.5 KiB

12 years ago
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE TemplateHaskell #-}
module Tests.Stream where
import Control.Monad.Trans
12 years ago
import Data.Conduit
import qualified Data.Conduit.List as CL
import Data.XML.Types
import Test.Hspec
import Test.Tasty
import Test.Tasty.HUnit
12 years ago
import Test.Tasty.Hspec
import Test.Tasty.TH
12 years ago
import Network.Xmpp.Stream
junk = [ EventBeginDocument
, EventEndDocument
, EventBeginDoctype "" Nothing
, EventEndDoctype
, EventInstruction $ Instruction "" ""
-- , EventBeginElement Name [(Name, [Content])]
, EventEndElement "foo"
, EventContent $ ContentText ""
, EventComment ""
, EventCDATA ""
]
beginElem = EventBeginElement "foo" []
case_ThrowOutJunk = hspec . describe "throwOutJunk" $ do
12 years ago
it "drops everything but EvenBeginElement" $ do
res <- CL.sourceList junk $$ throwOutJunk >> await
res `shouldBe` Nothing
it "keeps everything after (and including) EvenBeginElement" $ do
res <- CL.sourceList (junk ++ [beginElem] ++ junk)
$$ throwOutJunk >> CL.consume
res `shouldBe` (beginElem : junk)
case_LogInput = hspec . describe "logInput" $ do
it "Can handle split UTF8 codepoints" $ do
res <- CL.sourceList ["\209","\136"] $= logInput $$ CL.consume
res `shouldBe` ["\209","\136"]
streamTests :: TestTree
streamTests = $testGroupGenerator