{-# LANGUAGE FlexibleInstances #-} {-# LANGUAGE OverloadedLists #-} {-# LANGUAGE OverloadedStrings #-} -- {{{ Imports import Arbitrary import Control.Monad.Catch.Pure import Control.Monad.Trans.Resource import Data.Char import Data.Conduit import Data.Conduit.Binary import Data.Conduit.List import Data.Conduit.Parser import Data.Conduit.Parser.XML as XML import Data.Default import Data.Version import qualified Language.Haskell.HLint as HLint (hlint) import Lens.Simple import Test.Tasty import Test.Tasty.HUnit import Test.Tasty.QuickCheck import Text.Parser.Combinators import Text.RSS.Conduit.Parse as Parser import Text.RSS.Conduit.Render as Renderer import Text.RSS.Lens import Text.RSS.Types import Text.XML.Stream.Render import URI.ByteString import System.IO -- }}} main :: IO () main = defaultMain $ testGroup "Tests" [ unitTests , properties , hlint ] unitTests :: TestTree unitTests = testGroup "Unit tests" [ skipHoursCase , skipDaysCase , textInputCase , imageCase , categoryCase , cloudCase , guidCase , enclosureCase , sourceCase , itemCase , documentCase ] properties :: TestTree properties = testGroup "Properties" [ roundtripTextInputProperty , roundtripImageProperty , roundtripCategoryProperty , roundtripEnclosureProperty , roundtripSourceProperty , roundtripGuidProperty , roundtripItemProperty ] skipHoursCase :: TestTree skipHoursCase = testCase " element" $ do result <- runResourceT . runConduit $ sourceList input =$= XML.parseText def =$= runConduitParser rssSkipHours result @?= [Hour 0, Hour 9, Hour 18, Hour 21] where input = [ "" , "21" , "9" , "0" , "18" , "9" , "" ] skipDaysCase :: TestTree skipDaysCase = testCase " element" $ do result <- runResourceT . runConduit $ sourceList input =$= XML.parseText def =$= runConduitParser rssSkipDays result @?= [Monday, Saturday, Friday] where input = [ "" , "Monday" , "Monday" , "Friday" , "Saturday" , "" ] textInputCase :: TestTree textInputCase = testCase " element" $ do result <- runResourceT . runConduit $ sourceList input =$= XML.parseText def =$= runConduitParser rssTextInput result^.textInputTitleL @?= "Title" result^.textInputDescriptionL @?= "Description" result^.textInputNameL @?= "Name" result^.textInputLinkL @=? RssURI (URI (Scheme "http") (Just (Authority Nothing (Host "link.ext") Nothing)) "" (Query []) Nothing) where input = [ "" , "Title" , "Description" , "Name" , "http://link.ext" , "" ] imageCase :: TestTree imageCase = testCase " element" $ do result <- runResourceT . runConduit $ sourceList input =$= XML.parseText def =$= runConduitParser rssImage result^.imageUriL @?= RssURI (URI (Scheme "http") (Just (Authority Nothing (Host "image.ext") Nothing)) "" (Query []) Nothing) result^.imageTitleL @?= "Title" result^.imageLinkL @?= RssURI (URI (Scheme "http") (Just (Authority Nothing (Host "link.ext") Nothing)) "" (Query []) Nothing) result^.imageWidthL @?= Just 100 result^.imageHeightL @?= Just 200 result^.imageDescriptionL @?= "Description" where input = [ "" , "http://image.ext" , "Title" , "http://link.ext" , "100" , "200" , "Description" , "" ] categoryCase :: TestTree categoryCase = testCase " element" $ do result <- runResourceT . runConduit $ sourceList input =$= XML.parseText def =$= runConduitParser rssCategory result @?= RssCategory "Domain" "Name" where input = [ "" , "Name" , "" ] cloudCase :: TestTree cloudCase = testCase " element" $ do (result1, result2) <- runResourceT . runConduit $ sourceList input =$= XML.parseText def =$= runConduitParser ((,) <$> rssCloud <*> rssCloud) result1 @?= RssCloud uri "pingMe" ProtocolSoap result2 @?= RssCloud uri "myCloud.rssPleaseNotify" ProtocolXmlRpc where input = [ "" , "" ] uri = RssURI (RelativeRef (Just (Authority Nothing (Host "rpc.sys.com") (Just $ Port 80))) "/RPC2" (Query []) Nothing) guidCase :: TestTree guidCase = testCase " element" $ do result <- runResourceT . runConduit $ sourceList input =$= XML.parseText def =$= runConduitParser (some rssGuid) result @?= [GuidUri uri, GuidText "1", GuidText "2"] where input = [ "//guid.ext" , "1" , "2" ] uri = RssURI (RelativeRef (Just (Authority Nothing (Host "guid.ext") Nothing)) "" (Query []) Nothing) enclosureCase :: TestTree enclosureCase = testCase " element" $ do result <- runResourceT . runConduit $ sourceList input =$= XML.parseText def =$= runConduitParser rssEnclosure result @?= RssEnclosure uri 12216320 "audio/mpeg" where input = [ "" ] uri = RssURI (URI (Scheme "http") (Just (Authority Nothing (Host "www.scripting.com") Nothing)) "/mp3s/weatherReportSuite.mp3" (Query []) Nothing) sourceCase :: TestTree sourceCase = testCase " element" $ do result <- runResourceT . runConduit $ sourceList input =$= XML.parseText def =$= runConduitParser rssSource result @?= RssSource uri "Tomalak's Realm" where input = [ "Tomalak's Realm" ] uri = RssURI (URI (Scheme "http") (Just (Authority Nothing (Host "www.tomalak.org") Nothing)) "/links2.xml" (Query []) Nothing) itemCase :: TestTree itemCase = testCase " element" $ do result <- runResourceT . runConduit $ sourceList input =$= XML.parseText def =$= runConduitParser rssItem result^.itemTitleL @?= "Example entry" result^.itemLinkL @?= Just link result^.itemDescriptionL @?= "Here is some text containing an interesting description." result^.itemGuidL @?= Just (GuidText "7bd204c6-1655-4c27-aeee-53f933c5395f") -- isJust (result^.itemPubDate_) @?= True where input = [ "" , "Example entry" , "Here is some text containing an interesting description." , "http://www.example.com/blog/post/1" , "7bd204c6-1655-4c27-aeee-53f933c5395f" , "Sun, 06 Sep 2009 16:20:00 +0000" , "Some content in unknown tag, should be ignored." , "" ] link = RssURI (URI (Scheme "http") (Just (Authority Nothing (Host "www.example.com") Nothing)) "/blog/post/1" (Query []) Nothing) documentCase :: TestTree documentCase = testCase " element" $ do result <- runResourceT . runConduit $ sourceList input =$= XML.parseText def =$= runConduitParser rssDocument result^.documentVersionL @?= Version [2] [] result^.channelTitleL @?= "RSS Title" result^.channelDescriptionL @?= "This is an example of an RSS feed" result^.channelLinkL @?= link result^.channelTtlL @?= Just 1800 length (result^..channelItemsL) @?= 1 where input = [ "" , "" , "" , "RSS Title" , "This is an example of an RSS feed" , "http://www.example.com/main.html" , "Mon, 06 Sep 2010 00:01:00 +0000 " , "Sun, 06 Sep 2009 16:20:00 +0000" , "1800" , "" , "Example entry" , "Here is some text containing an interesting description." , "http://www.example.com/blog/post/1" , "7bd204c6-1655-4c27-aeee-53f933c5395f" , "Sun, 06 Sep 2009 16:20:00 +0000" , "" , "" , "" ] link = RssURI (URI (Scheme "http") (Just (Authority Nothing (Host "www.example.com") Nothing)) "/main.html" (Query []) Nothing) hlint :: TestTree hlint = testCase "HLint check" $ do result <- HLint.hlint [ "test/", "Text/" ] Prelude.null result @?= True roundtripTextInputProperty :: TestTree roundtripTextInputProperty = testProperty "parse . render = id (RssTextInput)" $ \t -> either (const False) (t ==) (runIdentity . runCatchT . runConduit $ renderRssTextInput t =$= runConduitParser rssTextInput) roundtripImageProperty :: TestTree roundtripImageProperty = testProperty "parse . render = id (RssImage)" $ \t -> either (const False) (t ==) (runIdentity . runCatchT . runConduit $ renderRssImage t =$= runConduitParser rssImage) roundtripCategoryProperty :: TestTree roundtripCategoryProperty = testProperty "parse . render = id (RssCategory)" $ \t -> either (const False) (t ==) (runIdentity . runCatchT . runConduit $ renderRssCategory t =$= runConduitParser rssCategory) roundtripEnclosureProperty :: TestTree roundtripEnclosureProperty = testProperty "parse . render = id (RssEnclosure)" $ \t -> either (const False) (t ==) (runIdentity . runCatchT . runConduit $ renderRssEnclosure t =$= runConduitParser rssEnclosure) roundtripSourceProperty :: TestTree roundtripSourceProperty = testProperty "parse . render = id (RssSource)" $ \t -> either (const False) (t ==) (runIdentity . runCatchT . runConduit $ renderRssSource t =$= runConduitParser rssSource) roundtripGuidProperty :: TestTree roundtripGuidProperty = testProperty "parse . render = id (RssGuid)" $ \t -> either (const False) (t ==) (runIdentity . runCatchT . runConduit $ renderRssGuid t =$= runConduitParser rssGuid) roundtripItemProperty :: TestTree roundtripItemProperty = testProperty "parse . render = id (RssItem)" $ \t -> either (const False) (t ==) (runIdentity . runCatchT . runConduit $ renderRssItem t =$= runConduitParser rssItem) letter = choose ('a', 'z') digit = arbitrary `suchThat` isDigit alphaNum = oneof [letter, digit]