]> gitweb @ CieloNegro.org - Rakka.git/blob - Rakka/Wiki/Parser.hs
Implemented block commands
[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           Rakka.Wiki
9 import           Text.ParserCombinators.Parsec
10
11
12 type CommandTypeOf = String -> Maybe CommandType
13
14
15 wikiPage :: CommandTypeOf -> Parser WikiPage
16 wikiPage cmdTypeOf
17     = do xs <- many (blockElement cmdTypeOf)
18          skipMany ( comment
19                     <|>
20                     (newline >> return ())
21                   )
22          eof
23          return xs
24
25
26 blockElement :: CommandTypeOf -> Parser BlockElement
27 blockElement cmdTypeOf
28     = try $ do skipMany ( comment
29                           <|>
30                           (newline >> return ())
31                         )
32                foldr (<|>) pzero [ heading
33                                  , horizontalLine
34                                  , listElement cmdTypeOf
35                                  , definitionList cmdTypeOf
36                                  , pdata
37                                  , leadingSpaced cmdTypeOf
38                                  , paragraph cmdTypeOf
39                                  , blockCmd cmdTypeOf
40                                  ]
41
42
43 heading :: Parser BlockElement
44 heading = foldr (<|>) pzero (map heading' [1..5])
45           <?>
46           "heading"
47     where
48       heading' :: Int -> Parser BlockElement
49       heading' n = do try $ do count n (char '=')
50                                notFollowedBy (char '=')
51                       ws
52                       x  <- notFollowedBy (char '=') >> anyChar
53                       xs <- manyTill anyChar (try $ ws >> ( count n (char '=')
54                                                             <?>
55                                                             ("trailing " ++ take n (repeat '='))
56                                                           )
57                                              )
58                       ws
59                       eol
60                       return (Heading n (x:xs))
61
62
63 horizontalLine :: Parser BlockElement
64 horizontalLine = try ( do count 4 (char '-')
65                           many (char '-')
66                           ws
67                           eol
68                           return HorizontalLine
69                      )
70                  <?>
71                  "horizontal line"
72
73
74 listElement :: CommandTypeOf -> Parser BlockElement
75 listElement cmdTypeOf = listElement' [] >>= return . List
76     where
77       listElement' :: [Char] -> Parser ListElement
78       listElement' stack
79           = do t  <- oneOf "*#"
80                ws
81                xs <- items (stack ++ [t])
82                return (ListElement (toType t) xs)
83
84       -- ListItem の終了條件は、
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 Right xs ++ map Left (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                   _   -> pzero
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                   _   -> pzero
247       )
248       <?>
249       "block command"
250     where
251       contents :: Parser [BlockElement]
252       contents = do x  <- try $ blockElement cmdTypeOf
253                     xs <- contents
254                     return (x:xs)
255                  <|>
256                  (comment >> contents)
257                  <|>
258                  return []
259
260
261 inlineElement :: CommandTypeOf -> Parser InlineElement
262 inlineElement cmdTypeOf
263     = try $ do skipMany comment
264                foldr (<|>) pzero [ cdata
265                                  , apostrophes cmdTypeOf
266                                  , text
267                                  , pageLink
268                                  , inlineCmd cmdTypeOf
269                                  ]
270
271
272 cdata :: Parser InlineElement
273 cdata = try (string "<![CDATA[") >> cdata' >>= return . Text
274     where
275       cdata' :: Parser String
276       cdata' = do try (string "]]>")
277                   return []
278                <|>
279                do x  <- anyChar
280                   xs <- cdata'
281                   return (x:xs)
282
283
284 text :: Parser InlineElement
285 text = ( char ':'
286          >>
287          many (noneOf ('\n':inlineSymbols))
288          >>=
289          return . Text . (':' :)
290          -- 定義リストとの關係上、コロンは先頭にしか來れない。
291        )
292        <|>
293        ( many1 (noneOf ('\n':inlineSymbols))
294          >>=
295          return . Text
296        )
297        <?>
298        "text"
299
300
301 apostrophes :: CommandTypeOf -> Parser InlineElement
302 apostrophes cmdTypeOf = foldr (<|>) pzero (map try [apos1, apos2, apos3, apos4, apos5])
303     where
304       apos1 = apos 1 >> return (Text "'")
305
306       apos2 = do apos 2
307                  xs <- many1 $ inlineElement cmdTypeOf
308                  apos 2
309                  return (Italic xs)
310
311       apos3 = do apos 3
312                  xs <- many1 $ inlineElement cmdTypeOf
313                  apos 3
314                  return (Bold xs)
315
316       apos4 = apos 4 >> return (Text "'")
317
318       apos5 = do apos 5
319                  xs <- many1 $ inlineElement cmdTypeOf
320                  apos 5
321                  return (Italic [Bold xs])
322
323       apos :: Int -> Parser ()
324       apos n = count n (char '\'') >> notFollowedBy (char '\'')
325
326
327 pageLink :: Parser InlineElement
328 pageLink = do try (string "[[")
329               page     <- option Nothing 
330                           (many1 (noneOf "#|]") >>= return . Just)
331               fragment <- option Nothing
332                           (char '#' >> many1 (noneOf "|]") >>= return . Just)
333               text     <- option Nothing
334                           (char '|' >> many1 (satisfy (/= ']')) >>= return . Just)
335
336               case (page, fragment) of
337                 (Nothing, Nothing) -> pzero
338                 (_, _)             -> return ()
339
340               string "]]"
341               return $ PageLink page fragment text
342            <?>
343            "page link"
344
345
346 inlineCmd :: CommandTypeOf -> Parser InlineElement
347 inlineCmd cmdTypeOf
348     = (try $ do (tagName, tagAttrs) <- openTag
349                 case cmdTypeOf tagName of
350                   Just InlineCommandType
351                       -> do xs <- contents
352                             closeTag tagName
353                             return $ InlineCmd $ InlineCommand {
354                                          iCmdName       = tagName
355                                        , iCmdAttributes = tagAttrs
356                                        , iCmdContents   = xs
357                                        }
358                   _   -> pzero
359       )
360       <|>
361       (try $ do (tagName, tagAttrs) <- emptyTag
362                 case cmdTypeOf tagName of
363                   Just InlineCommandType
364                       -> return $ InlineCmd $ InlineCommand {
365                                          iCmdName       = tagName
366                                        , iCmdAttributes = tagAttrs
367                                        , iCmdContents   = []
368                                        }
369                   _   -> pzero
370       )
371       <?>
372       "inline command"
373     where
374       contents :: Parser [InlineElement]
375       contents = do x  <- inlineElement cmdTypeOf
376                     xs <- contents
377                     return (x:xs)
378                  <|>
379                  (comment >> contents)
380                  <|>
381                  (newline >> contents >>= return . (Text "\n" :))
382                  <|>
383                  return []
384
385
386 openTag :: Parser (String, [Attribute])
387 openTag = try $ do char '<'
388                    many space
389                    name  <- many1 letter
390                    many space
391                    attrs <- many $ do attr <- tagAttr
392                                       many space
393                                       return attr
394                    char '>'
395                    return (name, attrs)
396
397
398 emptyTag :: Parser (String, [Attribute])
399 emptyTag = try $ do char '<'
400                     many space
401                     name  <- many1 letter
402                     many space
403                     attrs <- many $ do attr <- tagAttr
404                                        many space
405                                        return attr
406                     char '/'
407                     many space
408                     char '>'
409                     return (name, attrs)
410
411
412 closeTag :: String -> Parser ()
413 closeTag name = try $ do char '<'
414                          many space
415                          char '/'
416                          many space
417                          string name
418                          many space
419                          char '>'
420                          return ()
421
422
423 tagAttr :: Parser (String, String)
424 tagAttr = do name  <- many1 letter
425              char '='
426              char '"'
427              value <- many (satisfy (/= '"'))
428              char '"'
429              return (name, value)
430
431
432 comment :: Parser ()
433 comment = (try (string "<!--") >> skipTillEnd 1)
434           <?>
435           "comment"
436     where
437       skipTillEnd :: Int -> Parser ()
438       skipTillEnd level = ( (try (string "<!--") >> skipTillEnd (level + 1))
439                             <|>
440                             (try (string "-->") >> case level of
441                                                      1 -> return ()
442                                                      n -> skipTillEnd (n - 1))
443                             <|>
444                             (anyChar >> skipTillEnd level)
445                           )
446
447
448 blockSymbols :: [Char]
449 blockSymbols = " =-*#;<"
450
451
452 inlineSymbols :: [Char]
453 inlineSymbols = "<[:'"
454
455 -- white space
456 ws :: Parser ()
457 ws = skipMany ( (oneOf " \t" >> return ())
458                 <|>
459                 comment
460               )
461
462 -- end of line
463 eol :: Parser ()
464 eol = ( (newline >> return ())
465         <|>
466         eof
467       )