]> gitweb @ CieloNegro.org - Rakka.git/blob - Rakka/Wiki/Parser.hs
Implemented more features
[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 $ try (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     = skipMany ( comment
29                  <|>
30                  (newline >> return ())
31                )
32       >>
33       ( foldr (<|>) pzero [ heading
34                           , horizontalLine
35                           , listElement cmdTypeOf
36                           , definitionList cmdTypeOf
37                           , pdata
38                           , leadingSpaced cmdTypeOf
39                           , paragraph cmdTypeOf
40                           ]
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' [] >>= return . List
77     where
78       listElement' :: [Char] -> Parser ListElement
79       listElement' stack
80           = do t  <- oneOf "*#"
81                ws
82                xs <- items (stack ++ [t])
83                return (ListElement (toType t) xs)
84
85       -- ListItem の終了條件は、
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                                             listElement' stack >>= return . Just
93                        rest <- items stack
94                        return $ (map Right xs ++ map Left (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
109
110 definitionList :: CommandTypeOf -> Parser BlockElement
111 definitionList cmdTypeOf = many1 definition >>= return . DefinitionList
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 pdata :: Parser BlockElement
154 pdata = do try (string "<![PDATA[")
155            many (oneOf " \t\n")
156            x <- pdata'
157            return (Preformatted [Text x])
158     where
159       pdata' :: Parser String
160       pdata' = do try (many (oneOf " \t\n") >> string "]]>")
161                   return []
162                <|>
163                do x  <- anyChar
164                   xs <- pdata'
165                   return (x:xs)
166
167
168 leadingSpaced :: CommandTypeOf -> Parser BlockElement
169 leadingSpaced cmdTypeOf = (char ' ' >> leadingSpaced' >>= return . Preformatted)
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 ( newline
179                              >>
180                              char ' '
181                              >>
182                              leadingSpaced'
183                              >>=
184                              return . (Text "\n" :)
185                            )
186                        <|>
187                        return []
188
189
190 blockCommand :: Parser BlockElement
191 blockCommand = pzero -- not implemented
192
193
194 paragraph :: CommandTypeOf -> Parser BlockElement
195 paragraph cmdTypeOf = paragraph' >>= return . Paragraph
196     where
197       paragraph' :: Parser [InlineElement]
198       paragraph' = do x  <- inlineElement cmdTypeOf
199                       xs <- try ( do newline
200                                      eof
201                                      return []
202                                   -- \n で文字列が終はってゐたら、ここ
203                                   -- で終了。
204                                 )
205                             <|>
206                             try ( do newline
207                                      ((oneOf ('\n':blockSymbols) >> pzero) <|> return ())
208                                      ((blockCommand              >> pzero) <|> return ())
209                                      ys <- (paragraph' <|> return [])
210                                      return (Text "\n" : ys)
211                                   -- \n があり、その次に \n、ブロックタ
212                                   -- グまたは blockSymbols があれば、
213                                   -- fail して 最初の newline を讀んだ
214                                   -- 所まで卷き戻す。
215                                 )
216                             <|>
217                             try paragraph'
218                             -- それ以外の場合は次の inlineElement から
219                             -- を讀んで見る。但し一つも無くても良い。
220                             <|>
221                             return [] -- 全部失敗したらここで終了。
222                       return (x:xs)
223
224
225 inlineElement :: CommandTypeOf -> Parser InlineElement
226 inlineElement cmdTypeOf
227     = try $ do skipMany comment
228                foldr (<|>) pzero [ cdata
229                                  , apostrophes cmdTypeOf
230                                  , text
231                                  , pageLink
232                                  , inlineCmd cmdTypeOf
233                                  ]
234
235
236 cdata :: Parser InlineElement
237 cdata = try (string "<![CDATA[") >> cdata' >>= return . Text
238     where
239       cdata' :: Parser String
240       cdata' = do try (string "]]>")
241                   return []
242                <|>
243                do x  <- anyChar
244                   xs <- cdata'
245                   return (x:xs)
246
247
248 text :: Parser InlineElement
249 text = ( char ':'
250          >>
251          many (noneOf ('\n':inlineSymbols))
252          >>=
253          return . Text . (':' :)
254          -- 定義リストとの關係上、コロンは先頭にしか來れない。
255        )
256        <|>
257        ( many1 (noneOf ('\n':inlineSymbols))
258          >>=
259          return . Text
260        )
261        <?>
262        "text"
263
264
265 apostrophes :: CommandTypeOf -> Parser InlineElement
266 apostrophes cmdTypeOf = foldr (<|>) pzero (map try [apos1, apos2, apos3, apos4, apos5])
267     where
268       apos1 = apos 1 >> return (Text "'")
269
270       apos2 = do apos 2
271                  xs <- many1 $ inlineElement cmdTypeOf
272                  apos 2
273                  return (Italic xs)
274
275       apos3 = do apos 3
276                  xs <- many1 $ inlineElement cmdTypeOf
277                  apos 3
278                  return (Bold xs)
279
280       apos4 = apos 4 >> return (Text "'")
281
282       apos5 = do apos 5
283                  xs <- many1 $ inlineElement cmdTypeOf
284                  apos 5
285                  return (Italic [Bold xs])
286
287       apos :: Int -> Parser ()
288       apos n = count n (char '\'') >> notFollowedBy (char '\'')
289
290
291 pageLink :: Parser InlineElement
292 pageLink = do try (string "[[")
293               page     <- option Nothing 
294                           (many1 (noneOf "#|]") >>= return . Just)
295               fragment <- option Nothing
296                           (char '#' >> many1 (noneOf "|]") >>= return . Just)
297               text     <- option Nothing
298                           (char '|' >> many1 (satisfy (/= ']')) >>= return . Just)
299
300               case (page, fragment) of
301                 (Nothing, Nothing) -> pzero
302                 (_, _)             -> return ()
303
304               string "]]"
305               return $ PageLink page fragment text
306            <?>
307            "page link"
308
309
310 inlineCmd :: CommandTypeOf -> Parser InlineElement
311 inlineCmd cmdTypeOf
312     = (try $ do (tagName, tagAttrs) <- openTag
313                 case cmdTypeOf tagName of
314                   Just InlineCommandType
315                       -> do xs <- contents
316                             closeTag tagName
317                             return $ InlineCmd $ InlineCommand {
318                                          iCmdName       = tagName
319                                        , iCmdAttributes = tagAttrs
320                                        , iCmdContents   =  xs
321                                        }
322                   _   -> pzero
323       )
324       <|>
325       (try $ do (tagName, tagAttrs) <- emptyTag
326                 case cmdTypeOf tagName of
327                   Just InlineCommandType
328                       -> return $ InlineCmd $ InlineCommand {
329                                          iCmdName       = tagName
330                                        , iCmdAttributes = tagAttrs
331                                        , iCmdContents   = []
332                                        }
333                   _   -> pzero
334       )
335     where
336       contents :: Parser [InlineElement]
337       contents = do x  <- inlineElement cmdTypeOf
338                     xs <- contents
339                     return (x:xs)
340                  <|>
341                  (comment >> contents)
342                  <|>
343                  (newline >> contents >>= return . (Text "\n" :))
344                  <|>
345                  return []
346
347
348 openTag :: Parser (String, [Attribute])
349 openTag = try $ do char '<'
350                    many space
351                    name  <- many1 letter
352                    many space
353                    attrs <- many $ do attr <- tagAttr
354                                       many space
355                                       return attr
356                    char '>'
357                    return (name, attrs)
358
359
360 emptyTag :: Parser (String, [Attribute])
361 emptyTag = try $ do char '<'
362                     many space
363                     name  <- many1 letter
364                     many space
365                     attrs <- many $ do attr <- tagAttr
366                                        many space
367                                        return attr
368                     char '/'
369                     many space
370                     char '>'
371                     return (name, attrs)
372
373
374 closeTag :: String -> Parser ()
375 closeTag name = try $ do char '<'
376                          many space
377                          char '/'
378                          many space
379                          string name
380                          many space
381                          char '>'
382                          return ()
383
384
385 tagAttr :: Parser (String, String)
386 tagAttr = do name  <- many1 letter
387              char '='
388              char '"'
389              value <- many (satisfy (/= '"'))
390              char '"'
391              return (name, value)
392
393
394 comment :: Parser ()
395 comment = (try (string "<!--") >> skipTillEnd 1)
396           <?>
397           "comment"
398     where
399       skipTillEnd :: Int -> Parser ()
400       skipTillEnd level = ( (try (string "<!--") >> skipTillEnd (level + 1))
401                             <|>
402                             (try (string "-->") >> case level of
403                                                      1 -> return ()
404                                                      n -> skipTillEnd (n - 1))
405                             <|>
406                             (anyChar >> skipTillEnd level)
407                           )
408
409
410 blockSymbols :: [Char]
411 blockSymbols = " =-*#;"
412
413
414 inlineSymbols :: [Char]
415 inlineSymbols = "<[:'"
416
417 -- white space
418 ws :: Parser ()
419 ws = skipMany ( (oneOf " \t" >> return ())
420                 <|>
421                 comment
422               )
423
424 -- end of line
425 eol :: Parser ()
426 eol = ( (newline >> return ())
427         <|>
428         eof
429       )