]> gitweb @ CieloNegro.org - Rakka.git/blobdiff - Rakka/Wiki/Parser.hs
Implemented dummy trackback commands
[Rakka.git] / Rakka / Wiki / Parser.hs
index 0433612ba5746bcd98312f5993b6847831336717..eb236ce1e54e57bab3d8c22cbd4e7433d193dc31 100644 (file)
@@ -5,6 +5,7 @@ module Rakka.Wiki.Parser
     where
 
 import           Data.Maybe
+import           Network.URI
 import           Rakka.Wiki
 import           Text.ParserCombinators.Parsec
 
@@ -232,7 +233,11 @@ blockCmd cmdTypeOf
                                        , bCmdAttributes = tagAttrs
                                        , bCmdContents   = xs
                                        }
-                  _   -> pzero
+
+                  Just InlineCommandType
+                      -> pzero
+
+                  _   -> return $ undefinedCmdErr tagName
       )
       <|>
       (try $ do (tagName, tagAttrs) <- emptyTag
@@ -243,7 +248,11 @@ blockCmd cmdTypeOf
                                        , bCmdAttributes = tagAttrs
                                        , bCmdContents   = []
                                        }
-                  _   -> pzero
+
+                  Just InlineCommandType
+                      -> pzero
+
+                  _   -> return $ undefinedCmdErr tagName
       )
       <?>
       "block command"
@@ -259,6 +268,14 @@ blockCmd cmdTypeOf
                  <|>
                  return []
 
+      undefinedCmdErr :: String -> BlockElement
+      undefinedCmdErr name
+          = Div [("class", "error")]
+            [ Paragraph [Text ("The command `" ++ name ++ "' is not defined. " ++
+                               "Make sure you haven't mistyped.")
+                        ]
+            ]
+
 
 inlineElement :: CommandTypeOf -> Parser InlineElement
 inlineElement cmdTypeOf
@@ -267,6 +284,7 @@ inlineElement cmdTypeOf
                                  , apostrophes cmdTypeOf
                                  , text
                                  , pageLink
+                                 , extLink
                                  , inlineCmd cmdTypeOf
                                  ]
 
@@ -345,6 +363,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