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