]> gitweb @ CieloNegro.org - Rakka.git/blobdiff - Rakka/Wiki/Parser.hs
Wrote many...
[Rakka.git] / Rakka / Wiki / Parser.hs
index 313521c23cf89971862f4091657d9ef22bef5348..6e4edeb4bc5c604aab1f6e97c0080471c1ebeff4 100644 (file)
@@ -5,6 +5,7 @@ module Rakka.Wiki.Parser
     where
 
 import           Data.Maybe
+import           Network.URI
 import           Rakka.Wiki
 import           Text.ParserCombinators.Parsec
 
@@ -72,16 +73,15 @@ horizontalLine = try ( do count 4 (char '-')
 
 
 listElement :: CommandTypeOf -> Parser BlockElement
-listElement cmdTypeOf = listElement' [] >>= return . List
+listElement cmdTypeOf = listElement' []
     where
-      listElement' :: [Char] -> Parser ListElement
+      listElement' :: [Char] -> Parser BlockElement
       listElement' stack
           = do t  <- oneOf "*#"
                ws
                xs <- items (stack ++ [t])
-               return (ListElement (toType t) xs)
+               return (List (toType t) xs)
 
-      -- ListItem の終了條件は、
       items :: [Char] -> Parser [ListItem]
       items stack = do xs     <- many1 $ inlineElement cmdTypeOf
                        nested <- option Nothing
@@ -90,7 +90,7 @@ listElement cmdTypeOf = listElement' [] >>= return . List
                                             string stack
                                             listElement' stack >>= return . Just
                        rest <- items stack
-                       return $ (map Right xs ++ map Left (catMaybes [nested])) : rest
+                       return $ (map Inline xs ++ map Block (catMaybes [nested])) : rest
                     <|>
                     (try $ do skipMany comment
                               newline
@@ -232,7 +232,11 @@ blockCmd cmdTypeOf
                                        , bCmdAttributes = tagAttrs
                                        , bCmdContents   = xs
                                        }
-                  _   -> pzero
+
+                  Just InlineCommandType
+                      -> pzero
+
+                  _   -> return $ undefinedCmdErr tagName
       )
       <|>
       (try $ do (tagName, tagAttrs) <- emptyTag
@@ -243,20 +247,34 @@ blockCmd cmdTypeOf
                                        , bCmdAttributes = tagAttrs
                                        , bCmdContents   = []
                                        }
-                  _   -> pzero
+
+                  Just InlineCommandType
+                      -> pzero
+
+                  _   -> return $ undefinedCmdErr tagName
       )
       <?>
       "block command"
     where
       contents :: Parser [BlockElement]
-      contents = do x  <- try $ blockElement cmdTypeOf
+      contents = do x  <- blockElement cmdTypeOf
                     xs <- contents
                     return (x:xs)
                  <|>
+                 (newline >> contents)
+                 <|>
                  (comment >> contents)
                  <|>
                  return []
 
+      undefinedCmdErr :: String -> BlockElement
+      undefinedCmdErr name
+          = Div [("class", "error")]
+            [ Block (Paragraph [Text ("The command `" ++ name ++ "' is not defined. " ++
+                                      "Make sure you haven't mistyped.")
+                               ])
+            ]
+
 
 inlineElement :: CommandTypeOf -> Parser InlineElement
 inlineElement cmdTypeOf
@@ -264,7 +282,9 @@ inlineElement cmdTypeOf
                foldr (<|>) pzero [ cdata
                                  , apostrophes cmdTypeOf
                                  , text
+                                 , objLink
                                  , pageLink
+                                 , extLink
                                  , inlineCmd cmdTypeOf
                                  ]
 
@@ -324,6 +344,17 @@ apostrophes cmdTypeOf = foldr (<|>) pzero (map try [apos1, apos2, apos3, apos4,
       apos n = count n (char '\'') >> notFollowedBy (char '\'')
 
 
+objLink :: Parser InlineElement
+objLink = do try (string "[[[")
+             page <- many1 (noneOf "|]")
+             text <- option Nothing
+                     (char '|' >> many1 (satisfy (/= ']')) >>= return . Just)
+             string "]]]"
+             return $ ObjectLink page text
+          <?>
+          "object link"
+
+
 pageLink :: Parser InlineElement
 pageLink = do try (string "[[")
               page     <- option Nothing 
@@ -343,6 +374,20 @@ pageLink = do try (string "[[")
            "page link"
 
 
+extLink :: Parser InlineElement
+extLink = do char '['
+             uriStr <- many1 (noneOf " \t]")
+             skipMany (oneOf " \t")
+             text <- option Nothing
+                     (many1 (noneOf "]") >>= return . Just)
+             
+             case parseURI uriStr of
+               Just uri -> char ']' >> return (ExternalLink uri text)
+               Nothing  -> pzero <?> "absolute URI"
+          <?>
+          "external link"
+
+
 inlineCmd :: CommandTypeOf -> Parser InlineElement
 inlineCmd cmdTypeOf
     = (try $ do (tagName, tagAttrs) <- openTag