
Am Dienstag, 6. Mai 2008 18:52 schrieb Ross Boylan:
g.hs:11:19: Couldn't match expected type `t1 -> GenParser Char () t' against inferred type `CharParser st ()' In the expression: reserved "\\begin" 1 In a 'do' expression: reserved "\\begin" 1 In the expression: do reserved "\\begin" 1 braces (many1 letter) Failed, modules loaded: none.
More generally, how can I go about diagnosing such problems? Since I can't load it, I can't debug it or get :info on the types.
It looks as if maybe it's expecting a Monad, but getting a parser. But
(GenParser tok st) is a monad. GenParser tok st a is the type of parsers which parse lists of tok, using a state of type st and returning a value of type a. There are two type synonyms I remember, type CharParser st a = GenParser Char st a and type Parser a = GenParser Char () a Now let's look at what ghc does with the code envBegin :: Parser String envBegin = do reserved "\\begin" 1 braces (many1 letter) which you had (btw, had you used layout instead of explicit braces, the 1 in the first column of the line would have led to a parse error and been more obvious). From the last expression, braces (many1 letter), which has type CharParser st [Char], the type checker infers that the whole do-expression has the same type. So the first expression in the do-block must have type CharParser st a, or, not using the type synonym, GenParser Char st a. The type signature says that the user state st is actually (), which is okay, because it's a more specific type. Now that first expression is parsed (reserved "\\begin") 1 , so the subexpression (reserved "\\begin") is applied to an argument and has to return a value of type GenParser Char st a, hence the type checker expects the type t1 -> GenParser Char st t for (reserved "\\begin"). That is the expected type from the error message, with st specialised to () due to the type signature. Next, the type of the expression (reserved "\\begin") is inferred. 'reserved' is defined as P.reserved haskell, P.reserved has type P.TokenParser st -> String -> CharParser st () haskell has type P.TokenParser st , so reserved has type String -> CharParser st () and hence (reserved "\\begin") has type CharParser st () , that is the inferred type of the error message. Since one of the two is a function type and the other not, these types do not match. The error message Couldn't match expected type `thing' against inferred type `umajig' In the expression: foo bar oops tells you that from the use of (foo bar) in that expression, the type checker expects it to have type `thing', but the type inference of the expression (foo bar), without surrounding context, yields type `umajig', which can't be matched (or unified) with `thing'. HTH, Daniel
I don't know why that would have changed vs using 6.6.
More questions about the error messages. Where is the expected type, and where is the inferred type, coming from? I'm guessing the expected type is from the function signature and the position inside a do (or perhaps from the argument following the ; in the do?) and the inferred type is what I would just call the type of reserved "begin".
And what is the 1 that appears after 'reserved "\\begin"'? An indicator that all occurrences of the text refer to the same spot in the program? Nesting level?
Thanks. Ross
P.S. There have been some issues with the Debian packaging of ghc6.8, so it's possible I'm bumping into them. I thought/hoped the problems were limited to non i386 architectures. Also, I'm pretty sure that the parsec code used by ghc6.6, ghc6.8, and hugs is all in different files. So conceivably the parsec source differs. I have ghc6 6.8.2-5 and libghc6-parsec-dev 2.1.0.0-2.
Source: 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
envBegin :: Parser String envBegin = do{ reserved "\\begin" 1 ; braces (many1 letter) }
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe