]> gitweb @ CieloNegro.org - Rakka.git/blob - tests/WikiParserTest.hs
Resurrection from bitrot
[Rakka.git] / tests / WikiParserTest.hs
1 {-# LANGUAGE
2     OverloadedStrings
3   , UnicodeSyntax
4   #-}
5 module WikiParserTest
6     ( testData
7     )
8     where
9 import Control.Applicative
10 import           Data.Maybe
11 import Data.Text (Text)
12 import           Network.URI
13 import           Rakka.Wiki
14 import           Rakka.Wiki.Parser
15 import           Test.HUnit
16 import           Text.ParserCombinators.Parsec
17
18 cmdTypeOf ∷ Alternative f ⇒ Text → f CommandType
19 cmdTypeOf "br"   = pure InlineCommandType
20 cmdTypeOf "i"    = pure InlineCommandType
21 cmdTypeOf "b"    = pure InlineCommandType
22 cmdTypeOf "span" = pure InlineCommandType
23 cmdTypeOf "div"  = pure BlockCommandType
24 cmdTypeOf _      = empty
25
26 parseWiki ∷ String → Either String WikiPage
27 parseWiki src = case parse (wikiPage cmdTypeOf) "" src of
28                   Left  err  → Left (show err)
29                   Right page → Right page
30
31 testData :: [Test]
32 testData = [ (parseWiki ""
33               ~?=
34               Right [])
35
36            , (parseWiki "\n"
37               ~?=
38               Right [])
39
40            , (parseWiki "=heading="
41               ~?=
42               Right [ Heading 1 "heading" ])
43
44            , (parseWiki "==      heading  ==  \n"
45               ~?=
46               Right [ Heading 2 "heading" ])
47
48            , (parseWiki "===== hello world =====\n"
49               ~?=
50               Right [ Heading 5 "hello world" ])
51
52            , (parseWiki "a =not a heading="
53               ~?=
54               Right [ Paragraph [ Text "a =not a heading=" ]
55                     ])
56
57            , (parseWiki "=h=\n\n=h="
58               ~?=
59               Right [ Heading 1 "h"
60                     , Heading 1 "h"
61                     ])
62            , (parseWiki "foo\nbar"
63               ~?=
64               Right [ Paragraph [ Text "foo"
65                                 , Text "\n"
66                                 , Text "bar"
67                                 ]
68                     ])
69            , (parseWiki "foo\nbar\n\nbaz\n"
70               ~?=
71               Right [ Paragraph [ Text "foo"
72                                 , Text "\n"
73                                 , Text "bar"
74                                 ]
75                     , Paragraph [ Text "baz"
76                                 ]
77                     ])
78
79            , (parseWiki "foo\n\n\nbar"
80               ~?=
81               Right [ Paragraph [ Text "foo" ]
82                     , Paragraph [ Text "bar" ]
83                     ])
84
85            , (parseWiki "foo\n=h="
86               ~?=
87               Right [ Paragraph [ Text "foo" ]
88                     , Heading 1 "h"
89                     ])
90
91            , (parseWiki "<!-- comment -->"
92               ~?=
93               Right [])
94
95            , (parseWiki "<!-- comment -->foo"
96               ~?=
97               Right [ Paragraph [ Text "foo" ]
98                     ])
99
100            , (parseWiki "bar<!-- comment -->"
101               ~?=
102               Right [ Paragraph [ Text "bar" ]
103                     ])
104
105            , (parseWiki "foo<!-- comment -->bar"
106               ~?=
107               Right [ Paragraph [ Text "foo"
108                                 , Text "bar"
109                                 ]
110                     ])
111
112            , (parseWiki "<!-- comment -->=h="
113               ~?=
114               Right [ Heading 1 "h" ])
115
116            , (parseWiki "=h= <!---->"
117               ~?=
118               Right [ Heading 1 "h" ])
119
120            , (parseWiki "<!-- <!-- nested --> comment -->"
121               ~?=
122               Right [])
123
124            , (parseWiki "[[[Page]]]"
125               ~?=
126               Right [ Paragraph [ ObjectLink "Page" Nothing ] ])
127
128            , (parseWiki "[[[Page|foo]]]"
129               ~?=
130               Right [ Paragraph [ ObjectLink "Page" (Just "foo") ] ])
131
132            , (parseWiki "[[Page]]"
133               ~?= 
134               Right [ Paragraph [ PageLink (Just "Page") Nothing Nothing ]
135                     ])
136
137            , (parseWiki "[[Page|Link to \"Page\"]]"
138               ~?=
139               Right [ Paragraph [ PageLink (Just "Page") Nothing (Just "Link to \"Page\"") ]
140                     ])
141
142            , (parseWiki "[[Page#foo]]"
143               ~?= 
144               Right [ Paragraph [ PageLink (Just "Page") (Just "foo") Nothing ]
145                     ])
146
147            , (parseWiki "[[#foo]]"
148               ~?= 
149               Right [ Paragraph [ PageLink Nothing (Just "foo") Nothing ]
150                     ])
151
152            , (parseWiki "[[Page#foo|Link to \"Page#foo\"]]"
153               ~?=
154               Right [ Paragraph [ PageLink (Just "Page") (Just "foo") (Just "Link to \"Page#foo\"") ]
155                     ])
156
157            , (parseWiki "foo [[Bar]] baz"
158               ~?=
159               Right [ Paragraph [ Text "foo "
160                                 , PageLink (Just "Bar") Nothing Nothing
161                                 , Text " baz"
162                                 ]
163                     ])
164
165            , (parseWiki "[[Foo]]\n[[Bar]]"
166               ~?= 
167               Right [ Paragraph [ PageLink (Just "Foo") Nothing Nothing
168                                 , Text "\n"
169                                 , PageLink (Just "Bar") Nothing Nothing
170                                 ]
171                     ])
172
173            , (parseWiki " foo"
174               ~?=
175               Right [ Preformatted [ Text "foo" ] ])
176
177            , (parseWiki " foo\n  bar\n"
178               ~?=
179               Right [ Preformatted [ Text "foo"
180                                    , Text "\n"
181                                    , Text " bar"
182                                    ]
183                     ])
184
185            , (parseWiki "foo\n bar\nbaz"
186               ~?=
187               Right [ Paragraph    [ Text "foo" ]
188                     , Preformatted [ Text "bar" ]
189                     , Paragraph    [ Text "baz" ]
190                     ])
191
192            , (parseWiki "----"
193               ~?=
194               Right [ HorizontalLine ])
195
196            , (parseWiki "\nfoo\nbar\n----\n"
197               ~?=
198               Right [ Paragraph [ Text "foo"
199                                 , Text "\n"
200                                 , Text "bar"
201                                 ]
202                     , HorizontalLine
203                     ])
204
205            , (parseWiki "a----b"
206               ~?=
207               Right [ Paragraph [ Text "a----b" ] ])
208
209            , (parseWiki "* a"
210               ~?=
211               Right [ List Bullet [[Inline (Text "a")]] ])
212
213            , (parseWiki "* a*"
214               ~?=
215               Right [ List Bullet [[Inline (Text "a*")]] ])
216
217            , (parseWiki "* a\n* b\n"
218               ~?=
219               Right [ List Bullet [ [Inline (Text "a")]
220                                   , [Inline (Text "b")]
221                                   ]
222                     ])
223
224            , (parseWiki "*a\n*#b\n*#c\n"
225               ~?=
226               Right [ List Bullet [ [ Inline (Text "a")
227                                     , Block  (List Numbered [ [Inline (Text "b")]
228                                                             , [Inline (Text "c")]
229                                                             ])
230                                     ]
231                                   ]
232                     ])
233
234            , (parseWiki "*a\n#b"
235               ~?=
236               Right [ List Bullet   [ [Inline (Text "a")] ]
237                     , List Numbered [ [Inline (Text "b")] ]
238                     ])
239
240            , (parseWiki "*a<!-- comment -->"
241               ~?=
242               Right [ List Bullet [ [Inline (Text "a")] ] ])
243
244            , (parseWiki "*a<!-- comment -->\n*b"
245               ~?=
246               Right [ List Bullet [ [Inline (Text "a")]
247                                   , [Inline (Text "b")]
248                                   ]
249                     ])
250
251            , (parseWiki "foo:bar"
252               ~?=
253               Right [ Paragraph [ Text "foo"
254                                 , Text ":bar"
255                                 ]
256                     ])
257
258            , (parseWiki "; foo: bar"
259               ~?=
260               Right [ DefinitionList [Definition [Text "foo"] [Text "bar"]] ])
261
262            , (parseWiki "; foo: bar\n"
263               ~?=
264               Right [ DefinitionList [Definition [Text "foo"] [Text "bar"]] ])
265
266            , (parseWiki "; foo\n: bar\n; bar\n: baz\n: baz"
267               ~?=
268               Right [ DefinitionList [ Definition [Text "foo"] [ Text "bar" ]
269                                      , Definition [Text "bar"] [ Text "baz"
270                                                                , Text "\n"
271                                                                , Text "baz" ]
272                                      ]
273                     ])
274
275            , (parseWiki "<!nowiki[foo [[bar]] baz]>"
276               ~?=
277               Right [ Paragraph [ Text "foo [[bar]] baz" ] ])
278
279            , (parseWiki "<!verbatim[foo [[bar]] baz]>"
280               ~?=
281               Right [ Preformatted [ Text "foo [[bar]] baz" ] ])
282
283            , (parseWiki "<!verbatim[\nfoo [[bar]] baz\n]>"
284               ~?=
285               Right [ Preformatted [ Text "foo [[bar]] baz" ] ])
286
287            , (parseWiki "foo' bar"
288               ~?=
289               Right [ Paragraph [ Text "foo"
290                                 , Text "'"
291                                 , Text " bar" ]
292                     ])
293
294            , (parseWiki "''foo''"
295               ~?=
296               Right [ Paragraph [ Italic [Text "foo"] ] ])
297
298            , (parseWiki "'''foo'''"
299               ~?=
300               Right [ Paragraph [ Bold [Text "foo"] ] ])
301
302            , (parseWiki "foo''''"
303               ~?=
304               Right [ Paragraph [ Text "foo"
305                                 , Text "'"
306                                 ]
307                     ])
308
309            , (parseWiki "'''''foo'''''"
310               ~?=
311               Right [ Paragraph [ Italic [Bold [Text "foo"]] ] ])
312
313            , (parseWiki "<br />"
314               ~?=
315               Right [ Paragraph [ InlineCmd (InlineCommand "br" [] []) ] ])
316
317            , (parseWiki "<br style=\"clear: both\"/>"
318               ~?=
319               Right [ Paragraph [ InlineCmd (InlineCommand "br" [("style", "clear: both")] []) ] ])
320
321            , (parseWiki "<i><b>foo</b></i>"
322               ~?=
323               Right [ Paragraph [ InlineCmd (InlineCommand "i" []
324                                              [ InlineCmd (InlineCommand "b" [] [ Text "foo" ]) ]) ] ])
325
326            , (parseWiki "<i>\nfoo\n<!-- comment -->\nbar</i>"
327               ~?=
328               Right [ Paragraph [ InlineCmd (InlineCommand "i" []
329                                              [ Text "\n"
330                                              , Text "foo"
331                                              , Text "\n"
332                                              , Text "\n"
333                                              , Text "bar"
334                                              ]) ] ])
335
336            , (parseWiki "<div>foo</div>"
337               ~?=
338               Right [ BlockCmd (BlockCommand "div" []
339                                 [ Paragraph [Text "foo"] ]) ])
340
341            , (parseWiki "<div>\nbar\n</div>"
342               ~?=
343               Right [ BlockCmd (BlockCommand "div" []
344                                 [ Paragraph [Text "bar"] ]) ])
345
346            , (parseWiki "<div><!-- comment --></div>"
347               ~?=
348               Right [ BlockCmd (BlockCommand "div" [] []) ])
349
350            , (parseWiki "foo<div id=\"bar\"/>"
351               ~?=
352               Right [ Paragraph [Text "foo"]
353                     , BlockCmd (BlockCommand "div" [("id", "bar")] [])
354                     ])
355
356            , (parseWiki "[http://example.org/]"
357               ~?=
358               Right [ Paragraph [ExternalLink (fromJust $ parseURI "http://example.org/") Nothing] ])
359
360            , (parseWiki "[http://example.org/ example.org]"
361               ~?=
362               Right [ Paragraph [ExternalLink
363                                  (fromJust $ parseURI "http://example.org/")
364                                  (Just "example.org")
365                                 ]
366                     ])
367            ]