{-# LANGUAGE OverloadedStrings #-} module Tests.Writers.HTML (tests) where import Data.Text (unpack) import qualified Data.Text as T import Test.Tasty import Test.Tasty.HUnit (HasCallStack) import Tests.Helpers import Text.Pandoc import Text.Pandoc.Arbitrary () import Text.Pandoc.Builder htmlWithOpts :: (ToPandoc a) => WriterOptions -> a -> String htmlWithOpts opts = unpack . purely (writeHtml4String opts{ writerWrapText = WrapNone }) . toPandoc html :: (ToPandoc a) => a -> String html = htmlWithOpts def htmlQTags :: (ToPandoc a) => a -> String htmlQTags = unpack . purely (writeHtml4String def{ writerWrapText = WrapNone, writerHtmlQTags = True }) . toPandoc {- "my test" =: X =?> Y is shorthand for test html "my test" $ X =?> Y which is in turn shorthand for test html "my test" (X,Y) -} infix 4 =: (=:) :: (ToString a, ToPandoc a, HasCallStack) => String -> (a, String) -> TestTree (=:) = test html noteTestDoc :: Blocks noteTestDoc = header 1 "Page title" <> header 2 "First section" <> para ("This is a footnote." <> note (para "Down here.") <> " And this is a " <> link "https://www.google.com" "" "link" <> ".") <> blockQuote (para ("A note inside a block quote." <> note (para "The second note.")) <> para "A second paragraph.") <> header 2 "Second section" <> para "Some more text." tests :: [TestTree] tests = [ testGroup "inline code" [ "basic" =: code "@&" =?> "@&" , "haskell" =: codeWith ("",["haskell"],[]) ">>=" =?> ">>=" , "nolanguage" =: codeWith ("",["nolanguage"],[]) ">>=" =?> ">>=" ] , testGroup "images" [ "alt with formatting" =: image "/url" "title" ("my " <> emph "image") =?> "\"my" ] , testGroup "blocks" [ "definition list with empty
" =: definitionList [(mempty, [para $ text "foo bar"])] =?> "
\n
\n
\n

foo bar

\n
\n
" , "heading with disallowed attributes" =: headerWith ("", [], [("invalid","1"), ("lang", "en")]) 1 "test" =?> "

test

" ] , testGroup "quotes" [ "quote with cite attribute (without q-tags)" =: doubleQuoted (spanWith ("", [], [("cite", "http://example.org")]) (str "examples")) =?> "“examples”" , tQ "quote with cite attribute (with q-tags)" $ doubleQuoted (spanWith ("", [], [("cite", "http://example.org")]) (str "examples")) =?> "examples" ] , testGroup "sample" [ "sample should be rendered correctly" =: plain (codeWith ("",["sample"],[]) "Answer is 42") =?> "Answer is 42" ] , testGroup "variable" [ "variable should be rendered correctly" =: plain (codeWith ("",["variable"],[]) "result") =?> "result" ] , testGroup "sample with style" [ "samp should wrap highlighted code" =: codeWith ("",["sample","haskell"],[]) ">>=" =?> ("" ++ ">>=") ] , testGroup "variable with style" [ "var should wrap highlighted code" =: codeWith ("",["haskell","variable"],[]) ">>=" =?> ("" ++ ">>=") ] , testGroup "footnotes" [ test (htmlWithOpts def{writerReferenceLocation=EndOfDocument}) "at the end of a document" $ noteTestDoc =?> T.unlines [ "

Page title

" , "

First section

" , "

This is a footnote.1 And this is a link.

" , "
" , "

A note inside a block quote.2

" , "

A second paragraph.

" , "
" , "

Second section

" , "

Some more text.

" , "
" , "
" , "
    " , "
  1. Down here.↩︎

  2. " , "
  3. The second note.↩︎

  4. " , "
" , "
" ] , test (htmlWithOpts def{writerReferenceLocation=EndOfBlock}) "at the end of a block" $ noteTestDoc =?> T.unlines [ "

Page title

" , "

First section

" , "

This is a footnote.1 And this is a link.

" , "
" , "
    " , "
  1. Down here.↩︎

  2. " , "
" , "
" , "
" , "

A note inside a block quote.2

" , "

A second paragraph.

" , "
" , "
" , "
    " , "
  1. The second note.↩︎

  2. " , "
" , "
" , "

Second section

" , "

Some more text.

" ] , test (htmlWithOpts def{writerReferenceLocation=EndOfSection}) "at the end of a section" $ noteTestDoc =?> T.unlines [ "

Page title

" , "

First section

" , "

This is a footnote.1 And this is a link.

" , "
" , "

A note inside a block quote.2

" , "

A second paragraph.

" , "
" , "
" , "
" , "
    " , "
  1. Down here.↩︎

  2. " , "
  3. The second note.↩︎

  4. " , "
" , "
" , "

Second section

" , "

Some more text.

" ] , test (htmlWithOpts def{writerReferenceLocation=EndOfSection, writerSectionDivs=True}) "at the end of a section, with section divs" $ noteTestDoc =?> -- Footnotes are rendered _after_ their section (in this case after the level2 section -- that contains it). T.unlines [ "
" , "

Page title

" , "
" , "

First section

" , "

This is a footnote.1 And this is a link.

" , "
" , "

A note inside a block quote.2

" , "

A second paragraph.

" , "
" , "
" , "
" , "
" , "
    " , "
  1. Down here.↩︎

  2. " , "
  3. The second note.↩︎

  4. " , "
" , "
" , "
" , "

Second section

" , "

Some more text.

" , "
" , "
" ] ] ] where tQ :: (ToString a, ToPandoc a) => String -> (a, String) -> TestTree tQ = test htmlQTags