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