]> gitweb @ CieloNegro.org - Rakka.git/blob - Rakka/Wiki/Parser.hs
Applied HLint
[Rakka.git] / Rakka / Wiki / Parser.hs
1 module Rakka.Wiki.Parser
2     ( CommandTypeOf
3     , wikiPage
4     )
5     where
6
7 import           Data.Maybe
8 import           Network.URI hiding (fragment)
9 import           Rakka.Wiki
10 import           Text.ParserCombinators.Parsec hiding (label)
11
12
13 type CommandTypeOf = String -> Maybe CommandType
14
15
16 wikiPage :: CommandTypeOf -> Parser WikiPage
17 wikiPage cmdTypeOf
18     = do xs <- many (blockElement cmdTypeOf)
19          skipMany ( comment
20                     <|>
21                     (newline >> return ())
22                   )
23          eof
24          return xs
25
26
27 blockElement :: CommandTypeOf -> Parser BlockElement
28 blockElement cmdTypeOf
29     = try $ do skipMany ( comment
30                           <|>
31                           (newline >> return ())
32                         )
33                foldr (<|>) pzero [ heading
34                                  , horizontalLine
35                                  , listElement cmdTypeOf
36                                  , definitionList cmdTypeOf
37                                  , verbatim
38                                  , leadingSpaced cmdTypeOf
39                                  , paragraph cmdTypeOf
40                                  , blockCmd cmdTypeOf
41                                  ]
42
43
44 heading :: Parser BlockElement
45 heading = foldr (<|>) pzero (map heading' [1..5])
46           <?>
47           "heading"
48     where
49       heading' :: Int -> Parser BlockElement
50       heading' n = do try $ do count n (char '=')
51                                notFollowedBy (char '=')
52                       ws
53                       x  <- notFollowedBy (char '=') >> anyChar
54                       xs <- manyTill anyChar (try $ ws >> ( count n (char '=')
55                                                             <?>
56                                                             ("trailing " ++ replicate n '=')
57                                                           )
58                                              )
59                       ws
60                       eol
61                       return (Heading n (x:xs))
62
63
64 horizontalLine :: Parser BlockElement
65 horizontalLine = try ( do count 4 (char '-')
66                           many (char '-')
67                           ws
68                           eol
69                           return HorizontalLine
70                      )
71                  <?>
72                  "horizontal line"
73
74
75 listElement :: CommandTypeOf -> Parser BlockElement
76 listElement cmdTypeOf = listElement' []
77     where
78       listElement' :: [Char] -> Parser BlockElement
79       listElement' stack
80           = do t  <- oneOf "*#"
81                ws
82                xs <- items (stack ++ [t])
83                return (List (toType t) xs)
84
85       items :: [Char] -> Parser [ListItem]
86       items stack = do xs     <- many1 $ inlineElement cmdTypeOf
87                        nested <- option Nothing
88                                  $ try $ do skipMany comment
89                                             newline
90                                             string stack
91                                             liftM Just (listElement' stack)
92                        rest <- items stack
93                        return $ (map Inline xs ++ map Block (catMaybes [nested])) : rest
94                     <|>
95                     (try $ do skipMany comment
96                               newline
97                               string stack
98                               ws
99                               items stack
100                     )
101                     <|>
102                     return []
103
104       toType :: Char -> ListType
105       toType '*' = Bullet
106       toType '#' = Numbered
107       toType _   = undefined
108
109
110 definitionList :: CommandTypeOf -> Parser BlockElement
111 definitionList cmdTypeOf = liftM DefinitionList (many1 definition)
112     where
113       definition :: Parser Definition
114       definition = do char ';'
115                       ws
116                       tHead <- inlineElement cmdTypeOf
117                       tRest <- term
118                       d     <- description
119                       return (Definition (tHead:tRest) d)
120                    <?>
121                    "definition list"
122
123       term :: Parser [InlineElement]
124       term = (char ':' >> ws >> return [])
125              <|>
126              (newline >> char ':' >> ws >> return [])
127              <|>
128              do x  <- inlineElement cmdTypeOf
129                 xs <- term
130                 return (x:xs)
131              <?>
132              "term to be defined"
133
134       description :: Parser [InlineElement]
135       description = do x  <- inlineElement cmdTypeOf
136                        xs <- description
137                        return (x:xs)
138                     <|>
139                     try ( do newline
140                              char ':'
141                              ws
142                              xs <- description
143                              return (Text "\n" : xs)
144                         )
145                     <|>
146                     (newline >> return [])
147                     <|>
148                     (eof >> return [])
149                     <?>
150                     "description of term"
151
152
153 verbatim :: Parser BlockElement
154 verbatim = do try (string "<!verbatim[")
155               many (oneOf " \t\n")
156               x <- verbatim'
157               return (Preformatted [Text x])
158     where
159       verbatim' :: Parser String
160       verbatim' = do try (many (oneOf " \t\n") >> string "]>")
161                      return []
162                   <|>
163                   do x  <- anyChar
164                      xs <- verbatim'
165                      return (x:xs)
166
167
168 leadingSpaced :: CommandTypeOf -> Parser BlockElement
169 leadingSpaced cmdTypeOf = liftM Preformatted (char ' ' >> leadingSpaced')
170                           <?>
171                           "leading space"
172     where
173       leadingSpaced' :: Parser [InlineElement]
174       leadingSpaced' = do x  <- inlineElement cmdTypeOf
175                           xs <- leadingSpaced'
176                           return (x:xs)
177                        <|>
178                        try ( liftM (Text "\n" :) ( newline
179                                                    >>
180                                                    char ' '
181                                                    >>
182                                                    leadingSpaced'
183                                                  )
184                            )
185                        <|>
186                        return []
187
188
189 paragraph :: CommandTypeOf -> Parser BlockElement
190 paragraph cmdTypeOf = liftM Paragraph paragraph'
191     where
192       paragraph' :: Parser [InlineElement]
193       paragraph' = do x  <- inlineElement cmdTypeOf
194                       xs <- try ( do newline
195                                      eof
196                                      return []
197                                   -- \n で文字列が終はってゐたら、ここ
198                                   -- で終了。
199                                 )
200                             <|>
201                             try ( do newline
202                                      ((oneOf ('\n':blockSymbols) >> pzero) <|> return ())
203                                      ys <- (paragraph' <|> return [])
204                                      return (Text "\n" : ys)
205                                   -- \n があり、その次に \n または
206                                   -- blockSymbols があれば、fail して
207                                   -- 最初の newline を讀んだ所まで卷き
208                                   -- 戻す。
209                                 )
210                             <|>
211                             paragraph'
212                             -- それ以外の場合は次の inlineElement から
213                             -- を讀んで見る。但し一つも無くても良い。
214                             <|>
215                             return [] -- 全部失敗したらここで終了。
216                       return (x:xs)
217
218
219 blockCmd :: CommandTypeOf -> Parser BlockElement
220 blockCmd cmdTypeOf
221     = (try $ do (tagName, tagAttrs) <- openTag
222                 case cmdTypeOf tagName of
223                   Just BlockCommandType
224                       -> do xs <- contents
225                             closeTag tagName
226                             return $ BlockCmd BlockCommand {
227                                          bCmdName       = tagName
228                                        , bCmdAttributes = tagAttrs
229                                        , bCmdContents   = xs
230                                        }
231
232                   Just InlineCommandType
233                       -> pzero
234
235                   _   -> return $ undefinedCmdErr tagName
236       )
237       <|>
238       (try $ do (tagName, tagAttrs) <- emptyTag
239                 case cmdTypeOf tagName of
240                   Just BlockCommandType
241                       -> return $ BlockCmd BlockCommand {
242                                          bCmdName       = tagName
243                                        , bCmdAttributes = tagAttrs
244                                        , bCmdContents   = []
245                                        }
246
247                   Just InlineCommandType
248                       -> pzero
249
250                   _   -> return $ undefinedCmdErr tagName
251       )
252       <?>
253       "block command"
254     where
255       contents :: Parser [BlockElement]
256       contents = do x  <- blockElement cmdTypeOf
257                     xs <- contents
258                     return (x:xs)
259                  <|>
260                  (newline >> contents)
261                  <|>
262                  (comment >> contents)
263                  <|>
264                  return []
265
266       undefinedCmdErr :: String -> BlockElement
267       undefinedCmdErr name
268           = Div [("class", "error")]
269             [ Block (Paragraph [Text ("The command `" ++ name ++ "' is not defined. " ++
270                                       "Make sure you haven't mistyped.")
271                                ])
272             ]
273
274
275 inlineElement :: CommandTypeOf -> Parser InlineElement
276 inlineElement cmdTypeOf
277     = try $ do skipMany comment
278                foldr (<|>) pzero [ nowiki
279                                  , apostrophes cmdTypeOf
280                                  , text
281                                  , objLink
282                                  , pageLink
283                                  , extLink
284                                  , inlineCmd cmdTypeOf
285                                  ]
286
287
288 nowiki :: Parser InlineElement
289 nowiki = liftM Text (try (string "<!nowiki[") >> nowiki')
290     where
291       nowiki' :: Parser String
292       nowiki' = do try (string "]>")
293                    return []
294                 <|>
295                 do x  <- anyChar
296                    xs <- nowiki'
297                    return (x:xs)
298
299
300 text :: Parser InlineElement
301 text = liftM (Text . (':' :)) ( char ':'
302                                 >>
303                                 many (noneOf ('\n':inlineSymbols))
304                               )
305        -- 定義リストとの關係上、コロンは先頭にしか來られない。
306        <|>
307        liftM Text (many1 (noneOf ('\n':inlineSymbols)))
308        <?>
309        "text"
310
311
312 apostrophes :: CommandTypeOf -> Parser InlineElement
313 apostrophes cmdTypeOf = foldr (<|>) pzero (map try [apos1, apos2, apos3, apos4, apos5])
314     where
315       apos1 = apos 1 >> return (Text "'")
316
317       apos2 = do apos 2
318                  xs <- many1 $ inlineElement cmdTypeOf
319                  apos 2
320                  return (Italic xs)
321
322       apos3 = do apos 3
323                  xs <- many1 $ inlineElement cmdTypeOf
324                  apos 3
325                  return (Bold xs)
326
327       apos4 = apos 4 >> return (Text "'")
328
329       apos5 = do apos 5
330                  xs <- many1 $ inlineElement cmdTypeOf
331                  apos 5
332                  return (Italic [Bold xs])
333
334       apos :: Int -> Parser ()
335       apos n = count n (char '\'') >> notFollowedBy (char '\'')
336
337
338 objLink :: Parser InlineElement
339 objLink = do try (string "[[[")
340              page  <- many1 (noneOf "|]")
341              label <- option Nothing
342                       (liftM Just (char '|' >> many1 (satisfy (/= ']'))))
343              string "]]]"
344              return $ ObjectLink page label
345           <?>
346           "object link"
347
348
349 pageLink :: Parser InlineElement
350 pageLink = do try (string "[[")
351               page     <- option Nothing 
352                           (liftM Just (many1 (noneOf "#|]")))
353               fragment <- option Nothing
354                           (liftM Just (char '#' >> many1 (noneOf "|]")))
355               label    <- option Nothing
356                           (liftM Just (char '|' >> many1 (satisfy (/= ']'))))
357
358               case (page, fragment) of
359                 (Nothing, Nothing) -> pzero
360                 (_, _)             -> return ()
361
362               string "]]"
363               return $ PageLink page fragment label
364            <?>
365            "page link"
366
367
368 extLink :: Parser InlineElement
369 extLink = do char '['
370              uriStr <- many1 (noneOf " \t]")
371              skipMany (oneOf " \t")
372              label  <- option Nothing
373                        (liftM Just (many1 (noneOf "]")))
374              
375              case parseURI uriStr of
376                Just uri -> char ']' >> return (ExternalLink uri label)
377                Nothing  -> pzero <?> "absolute URI"
378           <?>
379           "external link"
380
381
382 inlineCmd :: CommandTypeOf -> Parser InlineElement
383 inlineCmd cmdTypeOf
384     = (try $ do (tagName, tagAttrs) <- openTag
385                 case cmdTypeOf tagName of
386                   Just InlineCommandType
387                       -> do xs <- contents
388                             closeTag tagName
389                             return $ InlineCmd InlineCommand {
390                                          iCmdName       = tagName
391                                        , iCmdAttributes = tagAttrs
392                                        , iCmdContents   = xs
393                                        }
394                   _   -> pzero
395       )
396       <|>
397       (try $ do (tagName, tagAttrs) <- emptyTag
398                 case cmdTypeOf tagName of
399                   Just InlineCommandType
400                       -> return $ InlineCmd InlineCommand {
401                                          iCmdName       = tagName
402                                        , iCmdAttributes = tagAttrs
403                                        , iCmdContents   = []
404                                        }
405                   _   -> pzero
406       )
407       <?>
408       "inline command"
409     where
410       contents :: Parser [InlineElement]
411       contents = do x  <- inlineElement cmdTypeOf
412                     xs <- contents
413                     return (x:xs)
414                  <|>
415                  (comment >> contents)
416                  <|>
417                  liftM (Text "\n" :) (newline >> contents)
418                  <|>
419                  return []
420
421
422 openTag :: Parser (String, [Attribute])
423 openTag = try $ do char '<'
424                    many space
425                    name  <- many1 letter
426                    many space
427                    attrs <- many $ do attr <- tagAttr
428                                       many space
429                                       return attr
430                    char '>'
431                    return (name, attrs)
432
433
434 emptyTag :: Parser (String, [Attribute])
435 emptyTag = try $ do char '<'
436                     many space
437                     name  <- many1 letter
438                     many space
439                     attrs <- many $ do attr <- tagAttr
440                                        many space
441                                        return attr
442                     char '/'
443                     many space
444                     char '>'
445                     return (name, attrs)
446
447
448 closeTag :: String -> Parser ()
449 closeTag name = try $ do char '<'
450                          many space
451                          char '/'
452                          many space
453                          string name
454                          many space
455                          char '>'
456                          return ()
457
458
459 tagAttr :: Parser (String, String)
460 tagAttr = do name  <- many1 letter
461              char '='
462              char '"'
463              value <- many (satisfy (/= '"'))
464              char '"'
465              return (name, value)
466
467
468 comment :: Parser ()
469 comment = (try (string "<!--") >> skipTillEnd 1)
470           <?>
471           "comment"
472     where
473       skipTillEnd :: Int -> Parser ()
474       skipTillEnd level = (try (string "<!--") >> skipTillEnd (level + 1))
475                           <|>
476                           (try (string "-->") >> case level of
477                                                    1 -> return ()
478                                                    n -> skipTillEnd (n - 1))
479                           <|>
480                           (anyChar >> skipTillEnd level)
481
482
483 blockSymbols :: [Char]
484 blockSymbols = " =-*#;<"
485
486
487 inlineSymbols :: [Char]
488 inlineSymbols = "<[:'"
489
490 -- white space
491 ws :: Parser ()
492 ws = skipMany ( (oneOf " \t" >> return ())
493                 <|>
494                 comment
495               )
496
497 -- end of line
498 eol :: Parser ()
499 eol = (newline >> return ())
500       <|>
501       eof