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