[Haskell-cafe] Parsec on TeX

Ross Boylan RossBoylan at stanfordalumni.org
Sun May 4 23:40:47 EDT 2008


I am new to Haskell and Parsec, and am trying to understand both.  I tried
to follow the example of how to use Parsec to parse TeX begin/end groups,
but can't get it to run.  I'm using HUGS -98 on Debian.

When I copied the code I got errors about unknown terms (reserved and
braces).  I've tried to get them from the lexer, but now get this error
 :load grammar.hsl
ERROR "grammar.hsl":21 - Type error in explicitly typed binding
*** Term           : envEnd
*** Type           : String -> GenParser Char a [Char]
*** Does not match : String -> Parser ()

Can anyone help me understand what the problem is?

Here's the code the caused the above error; I believe the part after --TeX
example is verbatim from the Parsec documentation.  I picked haskell as the
language for to lexer "arbitrarily."

import Text.ParserCombinators.Parsec
import qualified Text.ParserCombinators.Parsec.Token as P
import Text.ParserCombinators.Parsec.Language(haskell)
reserved = P.reserved haskell
braces = P.braces haskell


-- TeX example
environment = do{ name <- envBegin
                ; environment
                ; envEnd name
                }
              <|> return ()

envBegin :: Parser String
envBegin     = do{ reserved "\\begin"
                 ; braces (many1 letter)
                 }

envEnd :: String -> Parser ()
envEnd name = do{ reserved "\\end"
                ; braces (string name)
                }





More information about the Haskell-Cafe mailing list