Neil Mitchell wrote:
> Hi,
>
> I'm using parsec to parse something which is either a "name" or a
> "type". The particular test string I'm using is a type, but isn't a
> name. I want things to default to "name" before "type".
I just finished a parsec grammar for C99, and found this very useful
wh
Hi,
I'm using parsec to parse something which is either a "name" or a
"type". The particular test string I'm using is a type, but isn't a
name. I want things to default to "name" before "type".
Some examples of the parsec function, and the result when applied to a
test string:
parsecQuery = do
--- [EMAIL PROTECTED] wrote:
I wish I knew what that meant. If someone could explain it and tell me
what's wrong, I'd appreciate it.
--- end of quote ---
Lexeme is actually a selector function over the TokenParser record. In the previous
section (also on lexical analysis), he included the code:
On Mon, 26 Jul 2004 22:45:50 -0500, <[EMAIL PROTECTED]> wrote:
Hello,
I copied this example exactly from the page
http://www.cs.uu.nl/people/daan/download/parsec/parsec.html
-begin-
module Parser where
import Data.Char
import Text.ParserCombinators.Parsec
import Text.ParserCombinators.Parse
> I copied this example exactly from the page
> http://www.cs.uu.nl/people/daan/download/parsec/parsec.html
>
> price = lexeme (do{ ds1 <- many1 digit
> ...
> However attempting to compile it gives the error message
> ...
> I wish I knew what that meant. If someone could explain it
> and tell m
Hello,
I copied this example exactly from the page
http://www.cs.uu.nl/people/daan/download/parsec/parsec.html
-begin-
module Parser where
import Data.Char
import Text.ParserCombinators.Parsec
import Text.ParserCombinators.Parsec.Char
import Text.ParserCombinators.Parsec.Token
price