The Parsec library distributed with GHC

José Romildo Malaquias romildo@urano.iceb.ufop.br
Wed, 15 Nov 2000 03:15:53 -0200


--VS++wcV0S1rZb1Fb
Content-Type: text/plain; charset=iso-8859-1
Content-Disposition: inline
Content-Transfer-Encoding: 8bit

Hello.

The Parsec library (in package text from hslibs)
distributed with GHC 4.08.1 and from CVS does not
work as expected. When I try the attached
program, ghc gives me error messages:

=================================
test.hs:6:
    Couldn't match `TokenParser' against `[Char]'
        Expected type: TokenParser
        Inferred type: [Char]
    In the first argument of `symbol', namely `"let"'
    In a do statement: symbol "let"

test.hs:12:
    Ambiguous type variable(s) `a' in the constraint `Show a'
    arising from use of `print' at test.hs:12
    In the right-hand side of an equation for `main':
        print (parse pLet "" "let a = 232")

Compilation had errors
=================================

This same program works if I use the Parsec library
downloaded from the author page <http://www.cs.uu.nl/~daan>
(after correcting a small bug relative to using some
names from the Char module without importing them).

I hope the library gets updated in the GHC CVS repository
and the next GHC release corrects this problem.

Regards,

Romildo
-- 
Prof. José Romildo Malaquias <romildo@iceb.ufop.br>
Departamento de Computação
Universidade Federal de Ouro Preto
Brasil

--VS++wcV0S1rZb1Fb
Content-Type: text/plain; charset=us-ascii
Content-Disposition: attachment; filename="test.hs"

module Main where

import Parsec
import ParsecToken

pLet = do symbol "let"
          id <- identifier
          symbol "="
          x <- integer 
          return (id,x)

main = print (parse pLet "" "let a = 232")


--VS++wcV0S1rZb1Fb--