Added HTML writer tests for inline code.

This commit is contained in:
John MacFarlane 2011-01-29 16:26:00 -08:00
parent 22969c1b9c
commit 3b5dbe6fdb
3 changed files with 44 additions and 0 deletions

View file

@ -361,3 +361,4 @@ Executable test-pandoc
Tests.Readers.RST
Tests.Writers.Native
Tests.Writers.ConTeXt
Tests.Writers.HTML

41
src/Tests/Writers/HTML.hs Normal file
View file

@ -0,0 +1,41 @@
{-# LANGUAGE OverloadedStrings, QuasiQuotes #-}
module Tests.Writers.HTML (tests) where
import Test.Framework
import Text.Pandoc.Builder
import Text.Pandoc
import Tests.Helpers
import Tests.Arbitrary()
import Text.Pandoc.Highlighting (languages) -- null if no hl support
html :: (ToString a, ToPandoc a) => a -> String
html = writeHtmlString defaultWriterOptions{ writerWrapText = False } . 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 5 =:
(=:) :: (ToString a, ToPandoc a)
=> String -> (a, String) -> Test
(=:) = test html
tests :: [Test]
tests = [ testGroup "inline code"
[ "basic" =: code "@&" =?> "<code>@&amp;</code>"
, "haskell" =: codeWith ("",["haskell"],[]) ">>="
=?> if null languages
then "<code class=\"haskell\">&gt;&gt;=</code>"
else "<code class=\"sourceCode haskell\"><span class=\"fu\">&gt;&gt;=</span></code>"
, "nolanguage" =: codeWith ("",["nolanguage"],[]) ">>="
=?> "<code class=\"nolanguage\">&gt;&gt;=</code>"
]
]

View file

@ -9,6 +9,7 @@ import qualified Tests.Readers.LaTeX
import qualified Tests.Readers.Markdown
import qualified Tests.Readers.RST
import qualified Tests.Writers.ConTeXt
import qualified Tests.Writers.HTML
import qualified Tests.Writers.Native
import qualified Tests.Shared
@ -18,6 +19,7 @@ tests = [ testGroup "Old" Tests.Old.tests
, testGroup "Writers"
[ testGroup "Native" Tests.Writers.Native.tests
, testGroup "ConTeXt" Tests.Writers.ConTeXt.tests
, testGroup "HTML" Tests.Writers.HTML.tests
]
, testGroup "Readers"
[ testGroup "LaTeX" Tests.Readers.LaTeX.tests