{-# LANGUAGE OverloadedStrings, QuasiQuotes #-} import Data.Time import Test.Tasty import Test.Tasty.HUnit hiding ( assert ) import Text.RawString.QQ ( r ) import Web.Sitemap.Gen import qualified Data.ByteString as BS main :: IO () main = defaultMain tests tests :: TestTree tests = testGroup "sitemap.org Examples" [ testCase "Single Url Sitemap" singleUrlSitemap , testCase "Multiple Url Sitemap" multipleUrlSitemap , testCase "Sitemap Index" sitemapIndex ] singleUrlSitemap :: Assertion singleUrlSitemap = let rendered = renderSitemap $ Sitemap [ SitemapUrl { sitemapLocation = "http://www.example.com/" , sitemapPriority = Just 0.8 , sitemapChangeFrequency = Just Monthly , sitemapLastModified = Just $ UTCTime (fromGregorian 2005 01 01) 0 } ] in singleUrlSitemapFixture @=? rendered singleUrlSitemapFixture :: BS.ByteString singleUrlSitemapFixture = [r| http://www.example.com/2005-01-01T00:00:00+00:00monthly0.8|] multipleUrlSitemap :: Assertion multipleUrlSitemap = let urls = [ SitemapUrl "http://www.example.com/" (Just $ UTCTime (fromGregorian 2005 01 01) 0) (Just Monthly) (Just 0.8) , SitemapUrl "http://www.example.com/catalog?item=12&desc=vacation_hawaii" Nothing (Just Weekly) Nothing , SitemapUrl "http://www.example.com/catalog?item=73&desc=vacation_new_zealand" (Just $ UTCTime (fromGregorian 2004 12 23) 0) (Just Weekly) Nothing , SitemapUrl "http://www.example.com/catalog?item=74&desc=vacation_newfoundland" (Just $ UTCTime (fromGregorian 2004 12 23) 64815) Nothing (Just 0.3) , SitemapUrl "http://www.example.com/catalog?item=83&desc=vacation_usa" (Just $ UTCTime (fromGregorian 2004 11 23) 0) Nothing Nothing ] in multipleUrlSitemapFixture @=? renderSitemap (Sitemap urls) multipleUrlSitemapFixture :: BS.ByteString multipleUrlSitemapFixture = [r| http://www.example.com/2005-01-01T00:00:00+00:00monthly0.8http://www.example.com/catalog?item=12&desc=vacation_hawaiiweeklyhttp://www.example.com/catalog?item=73&desc=vacation_new_zealand2004-12-23T00:00:00+00:00weeklyhttp://www.example.com/catalog?item=74&desc=vacation_newfoundland2004-12-23T18:00:15+00:000.3http://www.example.com/catalog?item=83&desc=vacation_usa2004-11-23T00:00:00+00:00|] sitemapIndex :: Assertion sitemapIndex = let sitemaps = [ IndexEntry "http://www.example.com/sitemap1.xml.gz" ( Just $ UTCTime (fromGregorian 2004 10 01) $ 18 * 60 * 60 + 23 * 60 + 17 ) , IndexEntry "http://www.example.com/sitemap2.xml.gz" (Just $ UTCTime (fromGregorian 2005 01 01) 0) ] in sitemapIndexFixture @=? renderSitemapIndex (SitemapIndex sitemaps) sitemapIndexFixture :: BS.ByteString sitemapIndexFixture = [r| http://www.example.com/sitemap1.xml.gz2004-10-01T18:23:17+00:00http://www.example.com/sitemap2.xml.gz2005-01-01T00:00:00+00:00|]