aboutsummaryrefslogtreecommitdiff
path: root/src
diff options
context:
space:
mode:
authorJohn MacFarlane <jgm@berkeley.edu>2011-01-29 16:26:00 -0800
committerJohn MacFarlane <jgm@berkeley.edu>2011-01-29 16:26:00 -0800
commit3b5dbe6fdb3888b263a52e001918b0e97789a38c (patch)
treefacb4bbdaa7f402ad9ebefebdb7587417fa458e1 /src
parent22969c1b9cc88225c8bc60ac4e98636051ca7b4c (diff)
downloadpandoc-3b5dbe6fdb3888b263a52e001918b0e97789a38c.tar.gz
Added HTML writer tests for inline code.
Diffstat (limited to 'src')
-rw-r--r--src/Tests/Writers/HTML.hs41
-rw-r--r--src/test-pandoc.hs2
2 files changed, 43 insertions, 0 deletions
diff --git a/src/Tests/Writers/HTML.hs b/src/Tests/Writers/HTML.hs
new file mode 100644
index 000000000..e13d0dc87
--- /dev/null
+++ b/src/Tests/Writers/HTML.hs
@@ -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>"
+ ]
+ ]
diff --git a/src/test-pandoc.hs b/src/test-pandoc.hs
index b7e4f7bd5..2b6c2bb49 100644
--- a/src/test-pandoc.hs
+++ b/src/test-pandoc.hs
@@ -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