{-# LANGUAGE OverloadedStrings #-} {-# LANGUAGE StandaloneDeriving #-} module Spec.Blogger (tests) where import Data.DateTime (fromGregorian) import qualified Data.Text as T import Hakyll.Convert.Blogger import Hakyll.Convert.Common (DistilledPost (..)) import Test.Tasty (TestTree, testGroup) import Test.Tasty.ExpectedFailure (expectFail) import Test.Tasty.HUnit import qualified Text.Atom.Feed as Atom deriving instance Eq DistilledPost deriving instance Show DistilledPost tests :: TestTree tests = testGroup "Blogger.distill" [ extractsPostUri, extractsPostBody, extractsPostTitle, canSkipComments, canExtractComments, enumeratesAllCommentAuthors, errorsOnNonHtmlPost, errorsOnNonHtmlComment, turnsIncorrectDatesIntoEpochStart, parsesDates, extractsPostTags ] extractsPostUri :: TestTree extractsPostUri = testGroup "extracts post's URI" [ 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 = FullPost { fpPost = entry, fpComments = [], fpUri = uri } entry = Atom.nullEntry "https://example.com/entry" (Atom.TextString "Test post") "2003-12-13T18:30:02Z" extractsPostBody :: TestTree extractsPostBody = testGroup "extracts post's body" [ testCase (T.unpack body) (dpBody (distill False (createInput body)) @?= body) | body <- [ "
Today was a snowy day, and I decided to...
", "So you see, I...
" ] ] where createInput body = FullPost { fpPost = createEntry body, fpComments = [], fpUri = "https://example.com" } createEntry body = ( Atom.nullEntry "https://example.com/entry" (Atom.TextString "Test post") "2003-12-13T18:30:02Z" ) { Atom.entryContent = Just (Atom.HTMLContent body) } extractsPostTitle :: TestTree extractsPostTitle = testGroup "extracts post's title" [ testCase (T.unpack title) (dpTitle (distill False (createInput title)) @?= Just (title)) | title <- [ "First post", "You won't believe what happened to me today", "Trying out things…" ] ] where createInput title = FullPost { fpPost = createEntry title, fpComments = [], fpUri = "https://example.com/titles.atom" } createEntry title = Atom.nullEntry "https://example.com/entry" (Atom.TextString title) "2003-12-13T18:30:02Z" canSkipComments :: TestTree canSkipComments = testCase "does not extract comments if first argument is False" (dpBody (distill False input) @?= expected) where input = FullPost { fpPost = entry, fpComments = [comment], fpUri = "https://example.com/feed" } entry = ( Atom.nullEntry "https://example.com/entry" (Atom.TextString "First post") "2003-12-13T18:30:02Z" ) { Atom.entryContent = Just (Atom.HTMLContent "Hello, world!
"), Atom.entryPublished = Just "2003-12-13T18:30:02Z" } comment = ( Atom.nullEntry "https://example.com/entry#comment1" (Atom.TextString "Nice") "2003-12-13T20:00:03Z" ) { Atom.entryContent = Just (Atom.HTMLContent "Nice post.
") } expected = "Hello, world!
" canExtractComments :: TestTree canExtractComments = testGroup "extracts comments if first argument is True" [ noDateNoAuthor, dateNoAuthor, noDateAuthor, dateAuthor ] where createInput comment = FullPost { fpPost = entry, fpComments = [comment], fpUri = "https://example.com/feed" } entry = ( Atom.nullEntry "https://example.com/entry" (Atom.TextString "First post") "2003-12-13T18:30:02Z" ) { Atom.entryContent = Just (Atom.HTMLContent "Hello, world!
"), Atom.entryPublished = Just "2003-12-13T18:30:02Z" } noDateNoAuthor = testCase "comments with no \"published\" date and no author" (dpBody (distill True (createInput commentNoDateNoAuthor)) @?= expectedNoDateNoAuthor) commentNoDateNoAuthor = ( Atom.nullEntry "https://example.com/entry#comment1" (Atom.TextString "Nice") "2003-12-13T20:00:03Z" ) { Atom.entryContent = Just (Atom.HTMLContent "Nice post.
") } expectedNoDateNoAuthor = "Hello, world!
\n\n\ \Hello, world!
\n\n\ \On 2019-01-02T03:04:05Z, wrote:
\n\ \Nice post.
\n\ \Hello, world!
\n\n\ \On unknown date, John Doe wrote:
\n\ \Nice post.
\n\ \Hello, world!
\n\n\ \On 2019-01-02T03:04:05Z, John Doe wrote:
\n\ \Nice post.
\n\ \Hello, world!
"), Atom.entryPublished = Just "2003-12-13T18:30:02Z" } comment = ( Atom.nullEntry "https://example.com/entry#comment1" (Atom.TextString "Nice") "2103-05-11T18:37:49Z" ) { Atom.entryContent = Just (Atom.HTMLContent "Nice post.
"), Atom.entryAuthors = [ Atom.nullPerson {Atom.personName = "First Author"}, Atom.nullPerson {Atom.personName = "Second Author"} ] } expected = "Hello, world!
\n\n\ \On unknown date, First Author Second Author wrote:
\n\ \Nice post.
\n\ \
On unknown date, wrote:
\n\ \Nice post.
\n\ \