[Haskell-cafe] How to do a special kind of comment with the TokenParser

John Ky newhoggy at gmail.com
Wed Jul 9 09:31:21 EDT 2008


Hi,

TokenParser supports two kinds of comments, the multi-line comments (ie. {-
-}) and the single line comments (ie. -- \n).

The language I am trying to parse, however, has comments which are neither.
The -- acts like a single line comment which extends to the end of the line
usually, but can also be truncated to before the end of the line by another
--.  For example:

  noncomment -- comment comment
  noncomment -- comment comment -- noncomment noncomment -- comment --
noncomment
  noncomment

I haven't been able to get the TokenParser to work with this style of
comment.  The best I could do was copy the whole Token module and modify the
code:

data LanguageDef st
    = LanguageDef
    {      {- snip -}
    *, commentLine    :: String*
           {- snip -}
    }

           {- snip -}

makeTokenParser languageDef
    = TokenParser{   {- snip -}   }
    where
           {- snip -}
      whiteSpace
        | noLine && noMulti  = skipMany (simpleSpace *<|> customComment* <?>
"")
        | noLine             = skipMany (simpleSpace *<|> customComment* <|>
multiLineComment <?> "")
        | noMulti            = skipMany (simpleSpace *<|> customComment* <|>
oneLineComment <?> "")
        | otherwise          = skipMany (simpleSpace *<|> customComment* <|>
oneLineComment <|> multiLineComment <?> "")
        where
          noLine  = null (commentLine languageDef)
          noMulti = null (commentStart languageDef)
      *customComment =
        do{commentCustom languageDef
          ;return()
        }*

Then I put my specialised comment parser in the customComment field:

languageDef = TOKEN.LanguageDef
   {        {- snip -}
   , TOKEN.commentCustom = customComment
            {- snip -}
   }
   where
      customComment = do
         string "--"
         untilLineCommentEnd
         return ()

      untilLineCommentEnd = do
         c <- manyTill anyChar (string "\n" <|> try (string "--"))
         return ()

Anyone know of a way I could reuse the TokenParser code rather than copy and
tweaking it?

Thanks

-John
-------------- next part --------------
An HTML attachment was scrubbed...
URL: http://www.haskell.org/pipermail/haskell-cafe/attachments/20080709/b1ccdc17/attachment.htm


More information about the Haskell-Cafe mailing list