aboutsummaryrefslogtreecommitdiff
path: root/test/Tests/Writers/RST.hs
blob: e6377c02f4cfcd700dda2c6e01328d27b4fa7972 (plain)
1
2
3
4
5
6
7
8
9
10
11
12
13
14
15
16
17
18
19
20
21
22
23
24
25
26
27
28
29
30
31
32
33
34
35
36
37
38
39
40
41
42
43
44
45
46
47
48
49
50
51
52
53
54
55
56
57
58
59
60
61
62
63
64
65
66
67
68
69
70
71
72
73
74
75
76
77
78
79
80
81
82
83
84
85
86
87
88
89
90
91
92
93
94
95
96
97
98
99
100
101
102
103
104
105
106
107
108
109
110
111
112
113
114
115
116
117
118
119
120
121
122
123
124
125
126
127
128
129
130
131
132
133
134
135
136
137
138
139
140
141
142
143
144
145
146
147
148
149
150
151
152
153
154
155
156
157
158
159
160
161
162
163
164
165
166
167
168
169
170
171
172
173
174
175
176
177
178
179
180
{-# LANGUAGE NoImplicitPrelude #-}
{-# LANGUAGE OverloadedStrings #-}
module Tests.Writers.RST (tests) where

import Prelude
import Control.Monad.Identity
import Test.Tasty
import Test.Tasty.HUnit
import Tests.Helpers
import Text.Pandoc
import Text.Pandoc.Arbitrary ()
import Text.Pandoc.Builder
import Text.Pandoc.Writers.RST
import qualified Data.Text as T

infix 4 =:
(=:) :: (ToString a, ToPandoc a)
     => String -> (a, String) -> TestTree
(=:) = test (purely (writeRST def . toPandoc))

testTemplate :: (ToString a, ToString c, ToPandoc a) =>
                String -> String -> (a, c) -> TestTree
testTemplate t = case runIdentity (compileTemplate [] (T.pack t)) of
    Left e -> error $ "Could not compile RST template: " ++ e
    Right templ -> test (purely (writeRST def{ writerTemplate = Just templ }) . toPandoc)

bodyTemplate :: Template T.Text
bodyTemplate = case runIdentity (compileTemplate [] "$body$\n") of
                    Left e      -> error $
                      "Could not compile RST bodyTemplate" ++ e
                    Right templ -> templ

tests :: [TestTree]
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 "ligatures" -- handling specific sequences of blocks
          [ "a list is closed by a comment before a quote" =: -- issue 4248
            bulletList [plain "bulleted"] <> blockQuote (plain "quoted") =?>
              unlines
              [ "-  bulleted"
              , ""
              , ".."
              , ""
              , "   quoted"]
          ]
        , testGroup "flatten"
          [ testCase "emerges nested styles as expected" $
            flatten (Emph [Str "1", Strong [Str "2"], Str "3"]) @?=
            [Emph [Str "1"], Strong [Str "2"], Emph [Str "3"]]
          , testCase "could introduce trailing spaces" $
            flatten (Emph [Str "f", Space, Strong [Str "2"]]) @?=
            [Emph [Str "f", Space], Strong [Str "2"]]
            -- the test above is the reason why we call
            -- stripLeadingTrailingSpace through transformNested after
            -- flatten
          , testCase "preserves empty parents" $
            flatten (Image ("",[],[]) [] ("loc","title")) @?=
            [Image ("",[],[]) [] ("loc","title")]
          ]
        , testGroup "inlines"
          [ "are removed when empty" =: -- #4434
            plain (strong (str "")) =?> ""
          , "do not cause the introduction of extra spaces when removed" =:
            plain (strong (str "") <> emph (str "text")) =?> "*text*"
          , "spaces are stripped at beginning and end" =:
            -- pandoc issue 4327 "The text within inline markup may not
            -- begin or end with whitespace"
            -- http://docutils.sourceforge.net/docs/ref/rst/restructuredtext.html#inline-markup
            strong (space <> str "text" <> space <> space) =?> "**text**"
          , "single space stripped" =:
            strong space =?> ""
          , "give priority to strong style over emphasis" =:
            strong (emph (strong (str "s"))) =?> "**s**"
          , "links are not elided by outer style" =:
            strong (emph (link "loc" "" (str "text"))) =?>
            "`text <loc>`__"
          , "RST inlines cannot start nor end with spaces" =:
            emph (str "f" <> space <> strong (str "d") <> space <> str "l") =?>
            "*f*\\ **d**\\ *l*"
          , "keeps quotes" =:
            strong (str "f" <> doubleQuoted (str "d") <> str "l") =?>
            "**f“d”l**"
          , "backslash inserted between str and code" =:
            str "/api?query=" <> code "foo" =?>
            "/api?query=\\ ``foo``"
          ]
        , testGroup "headings"
          [ "normal heading" =:
              header 1 (text "foo") =?>
              unlines
              [ "foo"
              , "==="]
          -- note: heading normalization is only done in standalone mode
          , test (purely (writeRST def{ writerTemplate = Just bodyTemplate })
                       . toPandoc)
            "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"
              , "--------"]
          , test (purely (writeRST def{ writerTemplate = Just bodyTemplate }) . toPandoc)
            "minimal heading levels" $
              header 2 (text "Header 1") <>
              header 3 (text "Header 2") <>
              header 2 (text "Header 1") <>
              header 4 (text "Header 2") <>
              header 5 (text "Header 3") <>
              header 3 (text "Header 2") =?>
              unlines
              [ "Header 1"
              , "========"
              , ""
              , "Header 2"
              , "--------"
              , ""
              , "Header 1"
              , "========"
              , ""
              , "Header 2"
              , "--------"
              , ""
              , "Header 3"
              , "~~~~~~~~"
              , ""
              , "Header 2"
              , "--------"]
          ]
        , testTemplate "$subtitle$\n" "subtitle" $
          (setMeta "subtitle" ("subtitle" :: Inlines) $ doc $ plain "") =?>
          ("subtitle" :: String)
        ]