{-# LANGUAGE OverloadedStrings #-} {-# LANGUAGE StandaloneDeriving #-} module Spec.Wordpress (tests) where import qualified Data.Text as T import qualified Data.XML.Types as XML import Hakyll.Convert.Common (DistilledPost (..)) import Hakyll.Convert.Wordpress import Spec.SpecHelpers import Test.Tasty (TestTree, testGroup) import Test.Tasty.HUnit import qualified Text.RSS.Syntax as RSS deriving instance Eq DistilledPost deriving instance Show DistilledPost tests :: TestTree tests = testGroup "Wordpress.distill" [ extractsPostUri, extractsPostBody, combinesMultipleContentTags, extractsPostTitle, canSkipComments, canExtractComments, usesTheFirstCommentAuthorTag, turnsIncorrectDatesIntoEpochStart, parsesDates, extractsPostTags, extractsPostCategories ] extractsPostUri :: TestTree extractsPostUri = testGroup "extracts post's item link" [ testCase (T.unpack uri) (dpUri (distill False (createInput uri)) @?= uri) | uri <- [ "https://example.com/testing-post-uris", "http://www.example.com/~joe/posts.atom" ] ] where createInput uri = (RSS.nullItem "First post") { RSS.rssItemLink = Just uri } contentTag :: XML.Name contentTag = XML.Name { XML.nameLocalName = "encoded", XML.nameNamespace = Just "http://purl.org/rss/1.0/modules/content/", XML.namePrefix = Just "content" } namedElement :: XML.Name -> [XML.Node] -> XML.Element namedElement name nodes = XML.Element { XML.elementName = name, XML.elementAttributes = [], XML.elementNodes = nodes } extractsPostBody :: TestTree extractsPostBody = testGroup "extracts post's body" [ testCase (T.unpack body) (dpBody (distill False (createInput body)) @?= T.append body "\n") | body <- [ "
Today was a snowy day, and I decided to...
", "So you see, I...
" ] ] where createInput body = (RSS.nullItem "Test post") { RSS.rssItemOther = [ namedElement contentTag [XML.NodeContent $ XML.ContentText body] ] } combinesMultipleContentTags :: TestTree combinesMultipleContentTags = testCase "combines multiple content:encoded tags into the post body" (dpBody (distill False input) @?= T.unlines [body1, body2]) where body1 = "Hope you like my blog
" input = (RSS.nullItem "Just testing") { RSS.rssItemOther = [ createElement body1, createElement body2 ] } createElement body = namedElement contentTag [XML.NodeContent $ XML.ContentText body] extractsPostTitle :: TestTree extractsPostTitle = testGroup "extracts post's title" [ testCase (T.unpack title) (dpTitle (distill False (RSS.nullItem title)) @?= Just title) | title <- [ "First post", "You won't believe what happened to me today", "Trying out things…" ] ] commentTag :: XML.Name commentTag = XML.Name { XML.nameLocalName = "comment", XML.nameNamespace = Just "http://wordpress.org/export/1.2/", XML.namePrefix = Just "wp" } commentContentTag :: XML.Name commentContentTag = XML.Name { XML.nameLocalName = "comment_content", XML.nameNamespace = Just "http://wordpress.org/export/1.2/", XML.namePrefix = Just "wp" } commentDateTag :: XML.Name commentDateTag = XML.Name { XML.nameLocalName = "comment_date", XML.nameNamespace = Just "http://wordpress.org/export/1.2/", XML.namePrefix = Just "wp" } commentAuthorTag :: XML.Name commentAuthorTag = XML.Name { XML.nameLocalName = "comment_author", XML.nameNamespace = Just "http://wordpress.org/export/1.2/", XML.namePrefix = Just "wp" } canSkipComments :: TestTree canSkipComments = testCase "does not extract comments if first argument is False" (dpBody (distill False input) @?= "Hello, world!
\n") where input = (RSS.nullItem "Testing...") { RSS.rssItemOther = [ namedElement contentTag [XML.NodeContent $ XML.ContentText "Hello, world!
"], namedElement commentTag [ XML.NodeContent $ XML.ContentText "I'd like to point out that...
" ] ] } canExtractComments :: TestTree canExtractComments = testGroup "extracts comments if first argument is True" [ noDateNoAuthor, dateNoAuthor, noDateAuthor, dateAuthor ] where createInput comment = (RSS.nullItem "Testing...") { RSS.rssItemOther = [ namedElement contentTag [XML.NodeContent $ XML.ContentText "Is this thing on?
"], comment ] } noDateNoAuthor = testCase "comments with no \"published\" date and no author" (dpBody (distill True (createInput noDateNoAuthorComment)) @?= expectedNoDateNoAuthor) noDateNoAuthorComment = namedElement commentTag [ XML.NodeElement $ namedElement commentContentTag [XML.NodeContent $ XML.ContentText "hi
"] ] expectedNoDateNoAuthor = "Is this thing on?
\n\n\n\ \hi
"], XML.NodeElement $ namedElement commentDateTag [XML.NodeContent $ XML.ContentText "2017-09-02 21:28:46"] ] expectedDateNoAuthor = "Is this thing on?
\n\n\n\ \On 2017-09-02 21:28:46, unknown author wrote:
\n\ \hi
\n\ \Here's the thing: …
"], XML.NodeElement $ namedElement commentAuthorTag [XML.NodeContent $ XML.ContentText "Terry Jones"] ] expectedNoDateAuthor = "Is this thing on?
\n\n\n\ \On unknown date, Terry Jones wrote:
\n\ \Here's the thing: …
\n\ \It sure is!
"], XML.NodeElement $ namedElement commentDateTag [XML.NodeContent $ XML.ContentText "2017-09-02 21:28:46"], XML.NodeElement $ namedElement commentAuthorTag [XML.NodeContent $ XML.ContentText "Elizabeth Keyes"] ] expectedDateAuthor = "Is this thing on?
\n\n\n\ \On 2017-09-02 21:28:46, Elizabeth Keyes wrote:
\n\ \It sure is!
\n\ \Check this out!
"], namedElement commentTag [ XML.NodeElement $ namedElement commentContentTag [XML.NodeContent $ XML.ContentText "Cool!
"], XML.NodeElement $ namedElement commentAuthorTag [XML.NodeContent $ XML.ContentText "Alexander Batischev"], XML.NodeElement $ namedElement commentAuthorTag [XML.NodeContent $ XML.ContentText "John Doe"] ] ] } expected = "Check this out!
\n\n\n\ \On unknown date, Alexander Batischev wrote:
\n\ \Cool!
\n\ \
On unknown date, unknown author wrote:
\n\ \hi
\n\ \