]> gitweb @ CieloNegro.org - Rakka.git/blob - tests/WikiParserTest.hs
wrote many
[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 [ PageLink (Just "Page") Nothing Nothing ]
125                      ]))
126
127            , (parseWiki "[[Page|Link to \"Page\"]]"
128               ~?=
129               (Right [ Paragraph [ PageLink (Just "Page") Nothing (Just "Link to \"Page\"") ]
130                      ]))
131
132            , (parseWiki "[[Page#foo]]"
133               ~?= 
134               (Right [ Paragraph [ PageLink (Just "Page") (Just "foo") Nothing ]
135                      ]))
136
137            , (parseWiki "[[#foo]]"
138               ~?= 
139               (Right [ Paragraph [ PageLink Nothing (Just "foo") Nothing ]
140                      ]))
141
142            , (parseWiki "[[Page#foo|Link to \"Page#foo\"]]"
143               ~?=
144               (Right [ Paragraph [ PageLink (Just "Page") (Just "foo") (Just "Link to \"Page#foo\"") ]
145                      ]))
146
147            , (parseWiki "foo [[Bar]] baz"
148               ~?=
149               (Right [ Paragraph [ Text "foo "
150                                  , PageLink (Just "Bar") Nothing Nothing
151                                  , Text " baz"
152                                  ]
153                      ]))
154
155            , (parseWiki "[[Foo]]\n[[Bar]]"
156               ~?= 
157               (Right [ Paragraph [ PageLink (Just "Foo") Nothing Nothing
158                                  , Text "\n"
159                                  , PageLink (Just "Bar") Nothing Nothing
160                                  ]
161                      ]))
162
163            , (parseWiki " foo"
164               ~?=
165               (Right [ Preformatted [ Text "foo" ] ]))
166
167            , (parseWiki " foo\n  bar\n"
168               ~?=
169               (Right [ Preformatted [ Text "foo"
170                                     , Text "\n"
171                                     , Text " bar"
172                                     ]
173                      ]))
174
175            , (parseWiki "foo\n bar\nbaz"
176               ~?=
177               (Right [ Paragraph    [ Text "foo" ]
178                      , Preformatted [ Text "bar" ]
179                      , Paragraph    [ Text "baz" ]
180                      ]))
181
182            , (parseWiki "----"
183               ~?=
184               (Right [ HorizontalLine ]))
185
186            , (parseWiki "\nfoo\nbar\n----\n"
187               ~?=
188               (Right [ Paragraph [ Text "foo"
189                                  , Text "\n"
190                                  , Text "bar"
191                                  ]
192                      , HorizontalLine
193                      ]))
194
195            , (parseWiki "a----b"
196               ~?=
197               (Right [ Paragraph [ Text "a----b" ] ]))
198
199            , (parseWiki "* a"
200               ~?=
201               (Right [ List (ListElement Bullet [[Right (Text "a")]]) ]))
202
203            , (parseWiki "* a*"
204               ~?=
205               (Right [ List (ListElement Bullet [[Right (Text "a*")]]) ]))
206
207            , (parseWiki "* a\n* b\n"
208               ~?=
209               (Right [ List (ListElement Bullet [ [Right (Text "a")]
210                                                 , [Right (Text "b")]
211                                                 ])
212                      ]))
213
214            , (parseWiki "*a\n*#b\n*#c\n"
215               ~?=
216               (Right [ List (ListElement Bullet [ [ Right (Text "a")
217                                                   , Left (ListElement Numbered [ [Right (Text "b")]
218                                                                                , [Right (Text "c")]
219                                                                                ])
220                                                   ]
221                                                 ])
222                      ]))
223
224            , (parseWiki "*a\n#b"
225               ~?=
226               (Right [ List (ListElement Bullet   [ [Right (Text "a")] ])
227                      , List (ListElement Numbered [ [Right (Text "b")] ])
228                      ]))
229
230            , (parseWiki "*a<!-- comment -->"
231               ~?=
232               (Right [ List (ListElement Bullet [ [Right (Text "a")] ]) ]))
233
234            , (parseWiki "*a<!-- comment -->\n*b"
235               ~?=
236               (Right [ List (ListElement Bullet [ [Right (Text "a")]
237                                                 , [Right (Text "b")]
238                                                 ])
239                      ]))
240
241            , (parseWiki "foo:bar"
242               ~?=
243               (Right [ Paragraph [ Text "foo"
244                                  , Text ":bar"
245                                  ]
246                      ]))
247
248            , (parseWiki "; foo: bar"
249               ~?=
250               (Right [ DefinitionList [Definition [Text "foo"] [Text "bar"]] ]))
251
252            , (parseWiki "; foo: bar\n"
253               ~?=
254               (Right [ DefinitionList [Definition [Text "foo"] [Text "bar"]] ]))
255
256            , (parseWiki "; foo\n: bar\n; bar\n: baz\n: baz"
257               ~?=
258               (Right [ DefinitionList [ Definition [Text "foo"] [ Text "bar" ]
259                                       , Definition [Text "bar"] [ Text "baz"
260                                                                 , Text "\n"
261                                                                 , Text "baz" ]
262                                       ]
263                      ]))
264
265            , (parseWiki "<![CDATA[foo [[bar]] baz]]>"
266               ~?=
267               (Right [ Paragraph [ Text "foo [[bar]] baz" ] ]))
268
269            , (parseWiki "<![PDATA[foo [[bar]] baz]]>"
270               ~?=
271               (Right [ Preformatted [ Text "foo [[bar]] baz" ] ]))
272
273            , (parseWiki "<![PDATA[\nfoo [[bar]] baz\n]]>"
274               ~?=
275               (Right [ Preformatted [ Text "foo [[bar]] baz" ] ]))
276
277            , (parseWiki "foo' bar"
278               ~?=
279               (Right [ Paragraph [ Text "foo"
280                                  , Text "'"
281                                  , Text " bar" ]
282                      ]))
283
284            , (parseWiki "''foo''"
285               ~?=
286               (Right [ Paragraph [ Italic [Text "foo"] ] ]))
287
288            , (parseWiki "'''foo'''"
289               ~?=
290               (Right [ Paragraph [ Bold [Text "foo"] ] ]))
291
292            , (parseWiki "foo''''"
293               ~?=
294               (Right [ Paragraph [ Text "foo"
295                                  , Text "'"
296                                  ]
297                      ]))
298
299            , (parseWiki "'''''foo'''''"
300               ~?=
301               (Right [ Paragraph [ Italic [Bold [Text "foo"]] ] ]))
302
303            , (parseWiki "<br />"
304               ~?=
305               (Right [ Paragraph [ InlineCmd (InlineCommand "br" [] []) ] ]))
306
307            , (parseWiki "<br style=\"clear: both\"/>"
308               ~?=
309               (Right [ Paragraph [ InlineCmd (InlineCommand "br" [("style", "clear: both")] []) ] ]))
310
311            , (parseWiki "<i><b>foo</b></i>"
312               ~?=
313               (Right [ Paragraph [ InlineCmd (InlineCommand "i" []
314                                               [ InlineCmd (InlineCommand "b" [] [ Text "foo" ]) ]) ] ]))
315
316            , (parseWiki "<i>\nfoo\n<!-- comment -->\nbar</i>"
317               ~?=
318               (Right [ Paragraph [ InlineCmd (InlineCommand "i" []
319                                               [ Text "\n"
320                                               , Text "foo"
321                                               , Text "\n"
322                                               , Text "\n"
323                                               , Text "bar"
324                                               ]) ] ]))
325
326            , (parseWiki "<div>foo</div>"
327               ~?=
328               (Right [ BlockCmd (BlockCommand "div" []
329                                  [ Paragraph [Text "foo"] ]) ]))
330
331            , (parseWiki "<div>\nbar\n</div>"
332               ~?=
333               (Right [ BlockCmd (BlockCommand "div" []
334                                  [ Paragraph [Text "bar"] ]) ]))
335
336            , (parseWiki "<div><!-- comment --></div>"
337               ~?=
338               (Right [ BlockCmd (BlockCommand "div" [] []) ]))
339
340            , (parseWiki "foo<div id=\"bar\"/>"
341               ~?=
342               (Right [ Paragraph [Text "foo"]
343                      , BlockCmd (BlockCommand "div" [("id", "bar")] [])
344                      ]))
345
346            , (parseWiki "[http://example.org/]"
347               ~?=
348               (Right [ Paragraph [ExternalLink (fromJust $ parseURI "http://example.org/") Nothing] ]))
349
350            , (parseWiki "[http://example.org/ example.org]"
351               ~?=
352               (Right [ Paragraph [ExternalLink
353                                   (fromJust $ parseURI "http://example.org/")
354                                   (Just "example.org")
355                                  ]
356                      ]))
357            ]