From 4b7ddeb63fb754cbe3f4f6ea809532b2b92ca513 Mon Sep 17 00:00:00 2001
From: Nikolay Yakimov <root@livid.pp.ru>
Date: Thu, 16 Apr 2015 19:27:33 +0300
Subject: [PATCH] RST Writer: Tests for rubrics and heading normalization

---
 pandoc.cabal               |  1 +
 tests/Tests/Writers/RST.hs | 79 ++++++++++++++++++++++++++++++++++++++
 tests/test-pandoc.hs       |  2 +
 3 files changed, 82 insertions(+)
 create mode 100644 tests/Tests/Writers/RST.hs

diff --git a/pandoc.cabal b/pandoc.cabal
index 9b1001ace..7328a07db 100644
--- a/pandoc.cabal
+++ b/pandoc.cabal
@@ -495,6 +495,7 @@ Test-Suite test-pandoc
                   Tests.Writers.AsciiDoc
                   Tests.Writers.LaTeX
                   Tests.Writers.Docx
+                  Tests.Writers.RST
   Ghc-Options:  -rtsopts -Wall -fno-warn-unused-do-bind -threaded
   Default-Language: Haskell98
 
diff --git a/tests/Tests/Writers/RST.hs b/tests/Tests/Writers/RST.hs
new file mode 100644
index 000000000..2a511782f
--- /dev/null
+++ b/tests/Tests/Writers/RST.hs
@@ -0,0 +1,79 @@
+{-# LANGUAGE OverloadedStrings #-}
+module Tests.Writers.RST (tests) where
+
+import Test.Framework
+import Text.Pandoc.Builder
+import Text.Pandoc
+import Tests.Helpers
+import Tests.Arbitrary()
+
+infix 4 =:
+(=:) :: (ToString a, ToPandoc a)
+     => String -> (a, String) -> Test
+(=:) = test (writeRST def{ writerHighlight = True } . toPandoc)
+
+tests :: [Test]
+tests = [ testGroup "rubrics"
+          [ "in list item" =:
+              bulletList [header 2 (text "foo")] =?>
+              "-  .. rubric:: foo"
+          , "in definition list item" =:
+              definitionList [(text "foo", [header 2 (text "bar"),
+                                            para $ text "baz"])] =?>
+              unlines
+              [ "foo"
+              , "    .. rubric:: bar"
+              , ""
+              , "    baz"]
+          , "in block quote" =:
+              blockQuote (header 1 (text "bar")) =?>
+              "    .. rubric:: bar"
+          , "with id" =:
+              blockQuote (headerWith ("foo",[],[]) 1 (text "bar")) =?>
+              unlines
+              [ "    .. rubric:: bar"
+              , "       :name: foo"]
+          , "with id class" =:
+              blockQuote (headerWith ("foo",["baz"],[]) 1 (text "bar")) =?>
+              unlines
+              [ "    .. rubric:: bar"
+              , "       :name: foo"
+              , "       :class: baz"]
+          ]
+        , testGroup "headings"
+          [ "normal heading" =:
+              header 1 (text "foo") =?>
+              unlines
+              [ "foo"
+              , "==="]
+          , "heading levels" =:
+              header 1 (text "Header 1") <>
+              header 3 (text "Header 2") <>
+              header 2 (text "Header 2") <>
+              header 1 (text "Header 1") <>
+              header 4 (text "Header 2") <>
+              header 5 (text "Header 3") <>
+              header 3 (text "Header 2") =?>
+              unlines
+              [ "Header 1"
+              , "========"
+              , ""
+              , "Header 2"
+              , "--------"
+              , ""
+              , "Header 2"
+              , "--------"
+              , ""
+              , "Header 1"
+              , "========"
+              , ""
+              , "Header 2"
+              , "--------"
+              , ""
+              , "Header 3"
+              , "~~~~~~~~"
+              , ""
+              , "Header 2"
+              , "--------"]
+          ]
+        ]
diff --git a/tests/test-pandoc.hs b/tests/test-pandoc.hs
index dd92a271a..805bad414 100644
--- a/tests/test-pandoc.hs
+++ b/tests/test-pandoc.hs
@@ -21,6 +21,7 @@ import qualified Tests.Writers.Markdown
 import qualified Tests.Writers.Plain
 import qualified Tests.Writers.AsciiDoc
 import qualified Tests.Writers.Docx
+import qualified Tests.Writers.RST
 import qualified Tests.Shared
 import qualified Tests.Walk
 import Text.Pandoc.Shared (inDirectory)
@@ -40,6 +41,7 @@ tests = [ testGroup "Old" Tests.Old.tests
           , testGroup "Plain" Tests.Writers.Plain.tests
           , testGroup "AsciiDoc" Tests.Writers.AsciiDoc.tests
           , testGroup "Docx" Tests.Writers.Docx.tests
+          , testGroup "RST" Tests.Writers.RST.tests
           ]
         , testGroup "Readers"
           [ testGroup "LaTeX" Tests.Readers.LaTeX.tests