]> gitweb @ CieloNegro.org - Rakka.git/blobdiff - Rakka/Wiki/Parser.hs
Applied HLint
[Rakka.git] / Rakka / Wiki / Parser.hs
index 912237c7eda8db5b2f7de3ca79e7ad5d257be6fd..33b68bd0ef0112df1b23f0ea7463a9e76e980f27 100644 (file)
@@ -53,7 +53,7 @@ heading = foldr (<|>) pzero (map heading' [1..5])
                       x  <- notFollowedBy (char '=') >> anyChar
                       xs <- manyTill anyChar (try $ ws >> ( count n (char '=')
                                                             <?>
-                                                            ("trailing " ++ take n (repeat '='))
+                                                            ("trailing " ++ replicate n '=')
                                                           )
                                              )
                       ws
@@ -88,7 +88,7 @@ listElement cmdTypeOf = listElement' []
                                  $ try $ do skipMany comment
                                             newline
                                             string stack
-                                            listElement' stack >>= return . Just
+                                            liftM Just (listElement' stack)
                        rest <- items stack
                        return $ (map Inline xs ++ map Block (catMaybes [nested])) : rest
                     <|>
@@ -108,7 +108,7 @@ listElement cmdTypeOf = listElement' []
 
 
 definitionList :: CommandTypeOf -> Parser BlockElement
-definitionList cmdTypeOf = many1 definition >>= return . DefinitionList
+definitionList cmdTypeOf = liftM DefinitionList (many1 definition)
     where
       definition :: Parser Definition
       definition = do char ';'
@@ -166,7 +166,7 @@ verbatim = do try (string "<!verbatim[")
 
 
 leadingSpaced :: CommandTypeOf -> Parser BlockElement
-leadingSpaced cmdTypeOf = (char ' ' >> leadingSpaced' >>= return . Preformatted)
+leadingSpaced cmdTypeOf = liftM Preformatted (char ' ' >> leadingSpaced')
                           <?>
                           "leading space"
     where
@@ -175,20 +175,19 @@ leadingSpaced cmdTypeOf = (char ' ' >> leadingSpaced' >>= return . Preformatted)
                           xs <- leadingSpaced'
                           return (x:xs)
                        <|>
-                       try ( newline
-                             >>
-                             char ' '
-                             >>
-                             leadingSpaced'
-                             >>=
-                             return . (Text "\n" :)
+                       try ( liftM (Text "\n" :) ( newline
+                                                   >>
+                                                   char ' '
+                                                   >>
+                                                   leadingSpaced'
+                                                 )
                            )
                        <|>
                        return []
 
 
 paragraph :: CommandTypeOf -> Parser BlockElement
-paragraph cmdTypeOf = paragraph' >>= return . Paragraph
+paragraph cmdTypeOf = liftM Paragraph paragraph'
     where
       paragraph' :: Parser [InlineElement]
       paragraph' = do x  <- inlineElement cmdTypeOf
@@ -224,7 +223,7 @@ blockCmd cmdTypeOf
                   Just BlockCommandType
                       -> do xs <- contents
                             closeTag tagName
-                            return $ BlockCmd BlockCommand {
+                            return $ BlockCmd BlockCommand {
                                          bCmdName       = tagName
                                        , bCmdAttributes = tagAttrs
                                        , bCmdContents   = xs
@@ -239,7 +238,7 @@ blockCmd cmdTypeOf
       (try $ do (tagName, tagAttrs) <- emptyTag
                 case cmdTypeOf tagName of
                   Just BlockCommandType
-                      -> return $ BlockCmd BlockCommand {
+                      -> return $ BlockCmd BlockCommand {
                                          bCmdName       = tagName
                                        , bCmdAttributes = tagAttrs
                                        , bCmdContents   = []
@@ -287,7 +286,7 @@ inlineElement cmdTypeOf
 
 
 nowiki :: Parser InlineElement
-nowiki = try (string "<!nowiki[") >> nowiki' >>= return . Text
+nowiki = liftM Text (try (string "<!nowiki[") >> nowiki')
     where
       nowiki' :: Parser String
       nowiki' = do try (string "]>")
@@ -299,18 +298,13 @@ nowiki = try (string "<!nowiki[") >> nowiki' >>= return . Text
 
 
 text :: Parser InlineElement
-text = ( char ':'
-         >>
-         many (noneOf ('\n':inlineSymbols))
-         >>=
-         return . Text . (':' :)
-         -- 定義リストとの關係上、コロンは先頭にしか來れない。
-       )
+text = liftM (Text . (':' :)) ( char ':'
+                                >>
+                                many (noneOf ('\n':inlineSymbols))
+                              )
+       -- 定義リストとの關係上、コロンは先頭にしか來られない。
        <|>
-       ( many1 (noneOf ('\n':inlineSymbols))
-         >>=
-         return . Text
-       )
+       liftM Text (many1 (noneOf ('\n':inlineSymbols)))
        <?>
        "text"
 
@@ -345,7 +339,7 @@ objLink :: Parser InlineElement
 objLink = do try (string "[[[")
              page  <- many1 (noneOf "|]")
              label <- option Nothing
-                      (char '|' >> many1 (satisfy (/= ']')) >>= return . Just)
+                      (liftM Just (char '|' >> many1 (satisfy (/= ']'))))
              string "]]]"
              return $ ObjectLink page label
           <?>
@@ -355,11 +349,11 @@ objLink = do try (string "[[[")
 pageLink :: Parser InlineElement
 pageLink = do try (string "[[")
               page     <- option Nothing 
-                          (many1 (noneOf "#|]") >>= return . Just)
+                          (liftM Just (many1 (noneOf "#|]")))
               fragment <- option Nothing
-                          (char '#' >> many1 (noneOf "|]") >>= return . Just)
+                          (liftM Just (char '#' >> many1 (noneOf "|]")))
               label    <- option Nothing
-                          (char '|' >> many1 (satisfy (/= ']')) >>= return . Just)
+                          (liftM Just (char '|' >> many1 (satisfy (/= ']'))))
 
               case (page, fragment) of
                 (Nothing, Nothing) -> pzero
@@ -376,7 +370,7 @@ extLink = do char '['
              uriStr <- many1 (noneOf " \t]")
              skipMany (oneOf " \t")
              label  <- option Nothing
-                       (many1 (noneOf "]") >>= return . Just)
+                       (liftM Just (many1 (noneOf "]")))
              
              case parseURI uriStr of
                Just uri -> char ']' >> return (ExternalLink uri label)
@@ -392,7 +386,7 @@ inlineCmd cmdTypeOf
                   Just InlineCommandType
                       -> do xs <- contents
                             closeTag tagName
-                            return $ InlineCmd InlineCommand {
+                            return $ InlineCmd InlineCommand {
                                          iCmdName       = tagName
                                        , iCmdAttributes = tagAttrs
                                        , iCmdContents   = xs
@@ -403,7 +397,7 @@ inlineCmd cmdTypeOf
       (try $ do (tagName, tagAttrs) <- emptyTag
                 case cmdTypeOf tagName of
                   Just InlineCommandType
-                      -> return $ InlineCmd InlineCommand {
+                      -> return $ InlineCmd InlineCommand {
                                          iCmdName       = tagName
                                        , iCmdAttributes = tagAttrs
                                        , iCmdContents   = []
@@ -420,7 +414,7 @@ inlineCmd cmdTypeOf
                  <|>
                  (comment >> contents)
                  <|>
-                 (newline >> contents >>= return . (Text "\n" :))
+                 liftM (Text "\n" :) (newline >> contents)
                  <|>
                  return []
 
@@ -477,14 +471,13 @@ comment = (try (string "<!--") >> skipTillEnd 1)
           "comment"
     where
       skipTillEnd :: Int -> Parser ()
-      skipTillEnd level = ( (try (string "<!--") >> skipTillEnd (level + 1))
-                            <|>
-                            (try (string "-->") >> case level of
-                                                     1 -> return ()
-                                                     n -> skipTillEnd (n - 1))
-                            <|>
-                            (anyChar >> skipTillEnd level)
-                          )
+      skipTillEnd level = (try (string "<!--") >> skipTillEnd (level + 1))
+                          <|>
+                          (try (string "-->") >> case level of
+                                                   1 -> return ()
+                                                   n -> skipTillEnd (n - 1))
+                          <|>
+                          (anyChar >> skipTillEnd level)
 
 
 blockSymbols :: [Char]
@@ -503,7 +496,6 @@ ws = skipMany ( (oneOf " \t" >> return ())
 
 -- end of line
 eol :: Parser ()
-eol = ( (newline >> return ())
-        <|>
-        eof
-      )
+eol = (newline >> return ())
+      <|>
+      eof