Re: [Haskell-cafe] Parsec question

2013-07-24 Thread C K Kashyap
ybe? I'd like it very much if I could get > > an example of a missed match by not using the complete match. > > > > regards, > > Kashyap > > > > Sent from my Windows Phone > > From: Roman Cheplyaka > > Sent: 24/07/2013 8:19 PM > > To: C K Kash

Re: [Haskell-cafe] Parsec question

2013-07-24 Thread C K Kashyap
Thanks Kyle, My initial implementation was evaluating the whole list - the current one though just returns the first successful result. Anyway, I think I need the backtracking - I would want the "aaa" as the result :) I will now explore using go-routines to implement laziness. Thank you so much

Re: [Haskell-cafe] Parsec question

2013-07-24 Thread Roman Cheplyaka
t use it like Maybe? I'd like it very much if I could get > an example of a missed match by not using the complete match. > > regards, > Kashyap > > Sent from my Windows Phone > From: Roman Cheplyaka > Sent: 24/07/2013 8:19 PM > To: C K Kashyap > Cc: Haskell Cafe

Re: [Haskell-cafe] Parsec question

2013-07-24 Thread Kyle Miller
Because of laziness, you do in a sense only take the first successful value. When I've made parser combinators for Python before, I've used either generators or exceptions to get lazy evaluation, since computing the whole list of possibilities for each bind would ruin the running time of the algor

Re: [Haskell-cafe] Parsec question

2013-07-24 Thread Kashyap CK
PM To: C K Kashyap Cc: Haskell Cafe Subject: Re: [Haskell-cafe] Parsec question Think about this: if you always take only the first element, why do you need lists at all? Roman * C K Kashyap [2013-07-24 19:56:29+0530] > Dear Cafe, > > I am trying to implement[1] parsec in go using the &

Re: [Haskell-cafe] Parsec question

2013-07-24 Thread Roman Cheplyaka
Think about this: if you always take only the first element, why do you need lists at all? Roman * C K Kashyap [2013-07-24 19:56:29+0530] > Dear Cafe, > > I am trying to implement[1] parsec in go using the "Monadic Parser > Combinators" paper [2] . I've been able to implement "plus" "bind" and

[Haskell-cafe] Parsec question

2013-07-24 Thread C K Kashyap
Dear Cafe, I am trying to implement[1] parsec in go using the "Monadic Parser Combinators" paper [2] . I've been able to implement "plus" "bind" and "many" While doing the implementation - I looked at bind closely bind :: Parser a -> (a -> Parser b) -> Parser b p `bind` f = \inp -> concat [f v in

Re: [Haskell-cafe] simple parsec question

2013-03-05 Thread S. Doaitse Swierstra
Maybe this is something you do not even want to use a parser combinator library for. The package http://hackage.haskell.org/packages/archive/list-grouping/0.1.1/doc/html/Data-List-Grouping.html contains a function breakBefore, so you can write main = do inp <- readFile ... let

Re: [Haskell-cafe] simple parsec question

2013-03-05 Thread Immanuel Normann
Carlo, Thanks a lot! This looks very promising (though I have to test it for my purpose more in depth). As you mention, the key seems to be the optionMaybe combinator. Thanks for pointing to it. Immanuel 2013/3/5 Carlo Hamalainen > On Mon, Mar 4, 2013 at 1:44 AM, Immanuel Normann < > immanuel

Re: [Haskell-cafe] simple parsec question

2013-03-04 Thread Carlo Hamalainen
On Mon, Mar 4, 2013 at 1:44 AM, Immanuel Normann < immanuel.norm...@googlemail.com> wrote: > I am trying to parse a semi structured text with parsec that basically > should identify sections. Each section starts with a headline and has an > unstructured content - that's all. > Here's my attempt:

Re: [Haskell-cafe] simple parsec question

2013-03-04 Thread Immanuel Normann
Andrey, Thanks a lot for your effort! I have the same suspect that the lookahead in the content parser is the problem, but I don't know how to solve it either. At least the I learned from your code that noneOf is also a quite useful parser in this context which I have overlooked. Anyway, if you fin

Re: [Haskell-cafe] simple parsec question

2013-03-03 Thread Andrey Chudnov
Immanuel, I tried but I couldn't figure it out. Here's a gist with my attempts and results so far: https://gist.github.com/achudnov/f3af65f11d5162c73064 There, 'test' uses my attempt at specifying the parser, 'test2' uses yours. Note that your attempt wouldn't parse multiple sections -- for that yo

Re: [Haskell-cafe] simple parsec question

2013-03-03 Thread Immanuel Normann
Andrey, Thanks for your attempt, but it doesn't seem to work. The easy part is the headline, but the content makes trouble. Let me write the code a bit more explicit, so you can copy and paste it: -- {-# LANGUAGE FlexibleContexts #-} module Main where im

Re: [Haskell-cafe] simple parsec question

2013-03-03 Thread Andrey Chudnov
Immanuel, Since a heading always starts with a new line (and ends with a colon followed by a carriage return or just a colon?), I think it might be useful to first separate the input into lines and then classify them depending on whether it's a heading or not and reassemble them into the value

[Haskell-cafe] simple parsec question

2013-03-03 Thread Immanuel Normann
Hi, I am trying to parse a semi structured text with parsec that basically should identify sections. Each section starts with a headline and has an unstructured content - that's all. For instance, consider the following example text (inside the dashed lines): --- top 1:

[Haskell-cafe] Re: Re: A parsec question

2010-10-03 Thread Ben Franksen
Antoine Latter wrote: > On Sun, Oct 3, 2010 at 11:55 AM, Ben Franksen > wrote: >> Stephen Tetley wrote: >>> Does this one give the "expected" error message for Parsec3.1 - >>> unfortunately I can't test as I'm still using Parsec 2.1.0.1. >>> parser = block (many digit "digit") >> >> Unfortun

Re: [Haskell-cafe] Re: A parsec question

2010-10-03 Thread Antoine Latter
On Sun, Oct 3, 2010 at 11:55 AM, Ben Franksen wrote: > Stephen Tetley wrote: >> Does this one give the "expected" error message for Parsec3.1 - >> unfortunately I can't test as I'm still using Parsec 2.1.0.1. >> >>> parser = block (many digit "digit") > > Unfortunately, no. > > Cheers > Ben > He

[Haskell-cafe] Re: A parsec question

2010-10-03 Thread Ben Franksen
Stephen Tetley wrote: > Does this one give the "expected" error message for Parsec3.1 - > unfortunately I can't test as I'm still using Parsec 2.1.0.1. > >> parser = block (many digit "digit") Unfortunately, no. Cheers Ben ___ Haskell-Cafe mailing li

Re: [Haskell-cafe] A parsec question

2010-10-03 Thread Stephen Tetley
Does this one give the "expected" error message for Parsec3.1 - unfortunately I can't test as I'm still using Parsec 2.1.0.1. > parser = block (many digit "digit") ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/lis

Re: [Haskell-cafe] Re: A parsec question

2010-10-02 Thread Antoine Latter
On Wed, Sep 29, 2010 at 1:01 PM, Daniel Fischer wrote: > On Wednesday 29 September 2010 19:10:22, Ben Franksen wrote: >> > >> > Note the last line mentions only '}'. I would rather like to see >> > >> >   expecting "}" or digit >> > >> > since the parser could very well accept another digit here.

[Haskell-cafe] Re: A parsec question

2010-09-30 Thread Ben Franksen
Christian Maeder wrote: > Am 29.09.2010 20:01, schrieb Daniel Fischer: >> On Wednesday 29 September 2010 19:10:22, Ben Franksen wrote: Note the last line mentions only '}'. I would rather like to see expecting "}" or digit since the parser could very well accept anot

[Haskell-cafe] Re: A parsec question

2010-09-30 Thread Christian Maeder
Am 29.09.2010 20:01, schrieb Daniel Fischer: > On Wednesday 29 September 2010 19:10:22, Ben Franksen wrote: >>> >>> Note the last line mentions only '}'. I would rather like to see >>> >>> expecting "}" or digit >>> >>> since the parser could very well accept another digit here. > > parsec2 did

[Haskell-cafe] Re: Parsec question (new user): unexpected end of input

2010-09-29 Thread Peter Schmitz
Antoine and Christian: Many thanks for your help on this thread. (I am still digesting it; much appreciated; will post when I get it working.) -- Peter ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-

[Haskell-cafe] Re: Re: A parsec question

2010-09-29 Thread Ben Franksen
Daniel Fischer wrote: > On Wednesday 29 September 2010 19:10:22, Ben Franksen wrote: >> > >> > Note the last line mentions only '}'. I would rather like to see >> > >> > expecting "}" or digit >> > >> > since the parser could very well accept another digit here. > > parsec2 did that, I don't kno

Re: [Haskell-cafe] Re: A parsec question

2010-09-29 Thread Daniel Fischer
On Wednesday 29 September 2010 19:10:22, Ben Franksen wrote: > > > > Note the last line mentions only '}'. I would rather like to see > > > > expecting "}" or digit > > > > since the parser could very well accept another digit here. parsec2 did that, I don't know whether that change is intention

[Haskell-cafe] Re: A parsec question

2010-09-29 Thread Ben Franksen
Ben Franksen wrote: >> import Control.Applicative ((*>),(<*)) >> import Text.Parsec >> import Text.Parsec.Char >> block p = char '{' *> p <* char '}' >> parser = block (many digit) >> main = parseTest parser "{123a}" > > gives the output > > parse error at (line 1, column 5): > unexpected "a"

[Haskell-cafe] A parsec question

2010-09-29 Thread Ben Franksen
I have a question about Parsec. The following program > import Control.Applicative ((*>),(<*)) > import Text.Parsec > import Text.Parsec.Char > block p = char '{' *> p <* char '}' > parser = block (many digit) > main = parseTest parser "{123a}" gives the output parse error at (line 1, column 5

[Haskell-cafe] Re: Parsec question (new user): unexpected end of input

2010-09-29 Thread Christian Maeder
Am 29.09.2010 11:55, schrieb Christian Maeder: > Am 29.09.2010 09:54, schrieb Christian Maeder: >> Am 29.09.2010 05:35, schrieb Peter Schmitz: >> [...] >>> Error parsing file: "...\sampleTaggedContent.txt" (line 4, column 1): >>> unexpected end of input >>> expecting "<" >>> >>> The input was: >> [

[Haskell-cafe] Re: Parsec question (new user): unexpected end of input

2010-09-29 Thread Christian Maeder
Am 29.09.2010 09:54, schrieb Christian Maeder: > Am 29.09.2010 05:35, schrieb Peter Schmitz: > [...] >> Error parsing file: "...\sampleTaggedContent.txt" (line 4, column 1): >> unexpected end of input >> expecting "<" >> >> The input was: > [...] >> >>> -- Parsers: >>> taggedContent = do >>>opt

[Haskell-cafe] Re: Parsec question (new user): unexpected end of input

2010-09-29 Thread Christian Maeder
Am 29.09.2010 05:35, schrieb Peter Schmitz: [...] > Error parsing file: "...\sampleTaggedContent.txt" (line 4, column 1): > unexpected end of input > expecting "<" > > The input was: [...] > >> -- Parsers: >> taggedContent = do >>optionalWhiteSpace >>aTag >>many tagOrContent >>aTa

Re: [Haskell-cafe] Parsec question (new user): unexpected end of input

2010-09-28 Thread Antoine Latter
On Tue, Sep 28, 2010 at 10:35 PM, Peter Schmitz wrote: > I am a new Parsec user, and having some trouble with a relatively > simple parser. > > The grammar I want to parse contains tags (not html) marked by > angle brackets (e.g., ""), with arbitrary text (no angle > brackets allowed) optionally i

[Haskell-cafe] Parsec question (new user): unexpected end of input

2010-09-28 Thread Peter Schmitz
I am a new Parsec user, and having some trouble with a relatively simple parser. The grammar I want to parse contains tags (not html) marked by angle brackets (e.g., ""), with arbitrary text (no angle brackets allowed) optionally in between tags. Tags may not nest, but the input must begin and en

Re: [Haskell-cafe] Parsec question

2009-04-17 Thread Daniel Fischer
Am Samstag 18 April 2009 01:33:44 schrieb Michael P Mossey: > I've just about got this parser working, but wondering about something. > Turns out I need "try" inside the "lookahead" here. > > parseText :: Parser String > parseText = manyTill anyChar $ lookAhead (try (string "//")) > > Without try,

Re: [Haskell-cafe] Parsec question

2009-04-17 Thread Michael P Mossey
I've just about got this parser working, but wondering about something. Turns out I need "try" inside the "lookahead" here. parseText :: Parser String parseText = manyTill anyChar $ lookAhead (try (string "//")) Without try, if I give it an input with a single slash, like "some/text" It stops

[Haskell-cafe] Re: Parsec question

2009-04-17 Thread Christian Maeder
Michael Mossey wrote: > Here's what I have so far. It works, but it's a bit weird to consume the > // as part of the text rather than the keyword. That happens because the > try( string "//" ), which is part of the end arg to manyTill, consumes > the // when it succeeds. But maybe it is the most na

Re: [Haskell-cafe] Parsec question

2009-04-17 Thread Michael Mossey
Jason Dusek wrote: 2009/04/17 minh thu : 2009/04/17 Michael Mossey : I wonder how I can get the manyTill to be happy with eof before finding the //? I tried parseText = manyTill anyChar (try (string "//") <|> eof) but got a type error. You can use 'notFollowedBy' [...] You get a type e

Re: [Haskell-cafe] Parsec question

2009-04-17 Thread Jason Dusek
2009/04/17 minh thu : > 2009/04/17 Michael Mossey : >> I wonder how I can get the manyTill to be happy with eof >> before finding the //? I tried >> >> parseText = manyTill anyChar (try (string "//") <|> eof) >> >> but got a type error. > > You can use 'notFollowedBy' [...] You get a type error

Re: [Haskell-cafe] Parsec question

2009-04-17 Thread Michael Mossey
My confusion is that text is by definition followed by // or eof. minh thu wrote: You can use 'notFollowedBy' (probably with 'many1' and 'try'). Something like (untested): notFollowedBy (try $ string "//") Thu 2009/4/17 Michael Mossey : Here's what I've got so far. -- Text is considered ev

Re: [Haskell-cafe] Parsec question

2009-04-17 Thread minh thu
You can use 'notFollowedBy' (probably with 'many1' and 'try'). Something like (untested): notFollowedBy (try $ string "//") Thu 2009/4/17 Michael Mossey : > Here's what I've got so far. > > -- Text is considered everything up to //. However, the problem > -- is that this consumes the //. > parse

Re: [Haskell-cafe] Parsec question

2009-04-17 Thread Michael Mossey
Here's what I've got so far. -- Text is considered everything up to //. However, the problem -- is that this consumes the //. parseText = manyTill anyChar (try (string "//")) -- Because the // is already consumed, parseKeyword just grabs -- the available letters. parseKeyword :: Parser String pa

Re: [Haskell-cafe] Parsec question

2009-04-16 Thread minh thu
2009/4/17 Michael P Mossey : > I want to write a parser that can read a file with this format: the file has > sections which are demarcated by keywords. Keywords always begin with two > forward slashes and consist of letters, digits, and underscore. The text can > be anything, including special cha

[Haskell-cafe] Parsec question

2009-04-16 Thread Michael P Mossey
I want to write a parser that can read a file with this format: the file has sections which are demarcated by keywords. Keywords always begin with two forward slashes and consist of letters, digits, and underscore. The text can be anything, including special characters. For instance: //keywor

Re: [Haskell-cafe] Re: Parsec question

2008-12-23 Thread Erik de Castro Lopo
Toby Hutton wrote: > One of the tricks I found early on is to understand where to use 'try' > (since by default input is consumed even if a parser fails) but apart > from that just read Daan's page, even though it's out of date, and > look at how all these cool combinators work. > > http://legacy

Re: [Haskell-cafe] Re: Parsec question

2008-12-23 Thread Toby Hutton
On Wed, Dec 24, 2008 at 9:22 AM, Erik de Castro Lopo wrote: > > My next problem is matching things like: > > identifier ('.' identifier)* ('.' '*')? > > I've had a look at lookAhead from Text.ParserCombinators.Parsec.Combinator > but I can't get it to work. * is analogous to the 'many' combi

Re: [Haskell-cafe] Re: Parsec question

2008-12-23 Thread Erik de Castro Lopo
Benedikt Huber wrote: > Using sepBy1, the above parser can be written as > > dot = T.dot lexer > qualifiedIdentifier = sepBy1 identifier dot My next problem is matching things like: identifier ('.' identifier)* ('.' '*')? I've had a look at lookAhead from Text.ParserCombinators

Re: [Haskell-cafe] Re: Parsec question

2008-12-23 Thread Erik de Castro Lopo
Benedikt Huber wrote: > have a look at the module Text.ParserCombinators.Parsec.Combinator. > Those functions should help you to build up parsers from smaller > building blocks. > > Using sepBy1, the above parser can be written as > > dot = T.dot lexer > qualifiedIdentifier = sepBy1 i

[Haskell-cafe] Re: Parsec question

2008-12-23 Thread Benedikt Huber
Erik de Castro Lopo schrieb: Erik de Castro Lopo wrote: qualifiedIdentifier :: CharParser st [ String ] Ahh, figured it out myself: qualifiedIdentifier :: CharParser st [ String ] qualifiedIdentifier = do i <- identifier r <- dotIdentifier retu

Re: [Haskell-cafe] Parsec question

2008-12-23 Thread Erik de Castro Lopo
Erik de Castro Lopo wrote: > qualifiedIdentifier :: CharParser st [ String ] Ahh, figured it out myself: qualifiedIdentifier :: CharParser st [ String ] qualifiedIdentifier = do i <- identifier r <- dotIdentifier return (i : r) where

[Haskell-cafe] Parsec question

2008-12-23 Thread Erik de Castro Lopo
Hi all, I'm rather new to Haskell and I'm diving right into the deep end writing a parser using Parsec. In particular I'm using Text.ParserCombinators.Parsec.Language to do some of the heavy lifting and have this: import qualified Text.ParserCombinators.Parsec.Language as L import qual

Re: [Haskell-cafe] Parsec question

2007-06-21 Thread Levi Stephen
Dave Tapley wrote: I find it's good for the soul to remember what the do notation is doing for us. Also I'm with Einstein on "You do not really understand something unless you can explain it to your grandmother" :) Personally I think (in this instance) your three 'Parser a' functions read nic

Re: [Haskell-cafe] Parsec question

2007-06-21 Thread Levi Stephen
Tillmann Rendel wrote: My self-defined monadic combinator of choice to use with parsec is a >>~ b = a >>= \x -> b >> return x It works like (>>), but returns the result of the first instead of the result of the second computation. It is kind of an alternative for between: between lpare

Re: [Haskell-cafe] Parsec question

2007-06-21 Thread Thomas Conway
On 6/21/07, Jules Bean <[EMAIL PROTECTED]> wrote: I would write primary = PrimaryIdentifier `fmap` identifer <|> PrimaryLiteral`fmap` stringLiteral (I prefer fmap to liftM but they are the same for monads). To my mind this fits the general pattern of 'constructor comes before content

Re: [Haskell-cafe] Parsec question

2007-06-21 Thread Tillmann Rendel
Levi Stephen wrote: newtype Identifier = Identifier String newtype Literal = StringLiteral String -- to be extended later data Primary = PrimaryLiteral Literal | PrimaryIdentifier Identifier primary = do { i <- identifier; return $ PrimaryIdentifier i; } <|> do { l <- s

Re: [Haskell-cafe] Parsec question

2007-06-21 Thread Jules Bean
Thomas Conway wrote: p `with` f = p >>= (return . f) so I can write primary = (identifier `with` PrimaryIdentifier) <|> (stringLiteral `with` PrimaryLiteral) I would write primary = PrimaryIdentifier `fmap` identifer <|> PrimaryLiteral`fmap` stringLiteral (I prefer fmap to liftM b

Re: [Haskell-cafe] Parsec question

2007-06-21 Thread Thomas Conway
On 6/21/07, Dave Tapley <[EMAIL PROTECTED]> wrote: > primary = (identifier >>= (return . PrimaryIdentifier)) <|> (stringLiteral >>= (return . PrimaryLiteral)) > identifier = (many1 letter) >>= (return . Identifier) > stringLiteral = (char '\'') >> (manyTill anyChar (char '\'')) >>= (return . St

Re: [Haskell-cafe] Parsec question

2007-06-21 Thread Dave Tapley
I find it's good for the soul to remember what the do notation is doing for us. Also I'm with Einstein on "You do not really understand something unless you can explain it to your grandmother" :) Personally I think (in this instance) your three 'Parser a' functions read nicer as: primary = (i

Re: [Haskell-cafe] Parsec question

2007-06-20 Thread Tomasz Zielonka
On Thu, Jun 21, 2007 at 03:34:54PM +0930, Levi Stephen wrote: > Is there a way through combining types/parsers that the double do > block in primary could be avoided? > > I understand it's necessary right now because the parsers identifier > and stringLiteral return different types, so I can't jus

[Haskell-cafe] Parsec question

2007-06-20 Thread Levi Stephen
Hi, Fairly new to Haskell and trying some parsec. (Also, new to parsers/interpreters) I had come up with this, which works, but I can't help thinking there's a better way :) |> newtype Identifier = Identifier String newtype Literal = StringLiteral String -- to be extended later data Primar

Re: [Haskell-cafe] Parsec question

2007-05-27 Thread Andrew Coppin
Malcolm Wallace wrote: Andrew Coppin <[EMAIL PROTECTED]> writes: Any hints? wholething = many comment comment = do fmap Left $ (linecomment `onFail` nestedcomment) `onFail` fmap Right $ noncomment Haskell: The language of truely scary people(tm) :-} Th

Re: [Haskell-cafe] Parsec question

2007-05-27 Thread Malcolm Wallace
Andrew Coppin <[EMAIL PROTECTED]> writes: > I have a parser that recognises single-line comments, and another that > recognises multi-line comments. What I'd like to do is make a big parser > that returns [Either String String], which all the comments in one side > and all the rest in the other

[Haskell-cafe] Parsec question

2007-05-27 Thread Andrew Coppin
Greetings. I'd like to write a parser that takes some Haskell source code and seperates it into two piles - comments, and everything else. I have a parser that recognises single-line comments, and another that recognises multi-line comments. What I'd like to do is make a big parser that retu

[Haskell-cafe] Re: Parsec Question

2006-01-09 Thread Gerd M
despite SourcePos being abstract, it can be fully manipulated using newPos. Thanks for the tip, I thought it wasn't exported. Gerd M wrote: I'm trying to use parsec for parsing a custom input stream. As far as I understood the manual correctly I need to define the primitive parser: type M

[Haskell-cafe] Re: Parsec Question

2006-01-09 Thread Christian Maeder
Hi Gerd, despite SourcePos being abstract, it can be fully manipulated using newPos. import Text.ParserCombinators.Parsec.Pos If you can compute the positions from your Tok-stream then you may consider using "tokenPrim" and work with "GenParser Tok () a" HTH Christian Gerd M wrote: I'm tryi

Re: [Haskell-cafe] Parsec Question

2006-01-09 Thread Daniel Fischer
Am Montag, 9. Januar 2006 12:52 schrieb Gerd M: > I'm trying to use parsec for parsing a custom input stream. As far as I > understood the manual correctly I need to define the primitive parser: > > type MyParser a = GenParser (SourcePos,Tok) () a > mytoken :: (Tok -> Maybe a) -> MyParser a > myt

[Haskell-cafe] Parsec Question

2006-01-09 Thread Gerd M
I'm trying to use parsec for parsing a custom input stream. As far as I understood the manual correctly I need to define the primitive parser: type MyParser a = GenParser (SourcePos,Tok) () a mytoken :: (Tok -> Maybe a) -> MyParser a mytoken test = token showToken posToken testToken where

Re: [Haskell-cafe] Parsec question

2005-04-19 Thread Tomasz Zielonka
On Tue, Apr 19, 2005 at 09:47:22AM +0200, Ketil Malde wrote: > > Hi, > > I've started using Parsec for my parsing needs, and must say I'm very > happy with it. There is one thing that I'm struggling with > implementing though. > > Basically, I want to parse a file containing multiple records.

[Haskell-cafe] Parsec question

2005-04-19 Thread Ketil Malde
Hi, I've started using Parsec for my parsing needs, and must say I'm very happy with it. There is one thing that I'm struggling with implementing though. Basically, I want to parse a file containing multiple records. I already have a parser for a single record, and of course I could parse the

Re: [Haskell-cafe] Parsec question: how to access parser state

2005-03-20 Thread Andrew Pimlott
On Sun, Mar 20, 2005 at 03:32:38PM -0500, Dimitry Golubovsky wrote: > type TParser a = GenParser Token (FiniteMap String Declaration) a > > The FiniteMap (which is the user state) is expected to be updated during > parsing whus building some internal lookup table. > > and in one of the parsing f

[Haskell-cafe] Parsec question: how to access parser state

2005-03-20 Thread Dimitry Golubovsky
Hi, I am trying to develop a parser with the Parsec library. At some point I need to do something with parser state, say, convert it to a string. I declared the type for the parser: type TParser a = GenParser Token (FiniteMap String Declaration) a The FiniteMap (which is the user state) is expect

Re: [Haskell-cafe] Parsec question

2004-11-19 Thread John Goerzen
On Fri, Nov 19, 2004 at 02:56:38PM -, Bayley, Alistair wrote: > I've also used Parsec for separated lexer + parser and currently have > something like this to invoke them: > > testParse inputString = do > case (parse myLexer "" inputString) of > Left err -> fail ("lexical error: " ++ err

RE: [Haskell-cafe] Parsec question

2004-11-19 Thread Bayley, Alistair
TECTED] > Sent: 19 November 2004 14:28 > To: [EMAIL PROTECTED] > Subject: [Haskell-cafe] Parsec question > > Hi, > > I'm porting a parser over from an OCamllex/Ocamlyacc version and I'm > using Parsec for both the tokenizer and the resulting token > stream parser.

[Haskell-cafe] Parsec question

2004-11-19 Thread Tomasz Zielonka
On Fri, 19 Nov 2004 14:28:07 + (UTC), John Goerzen <[EMAIL PROTECTED]> wrote: > Hi, > > I'm porting a parser over from an OCamllex/Ocamlyacc version and I'm > using Parsec for both the tokenizer and the resulting token stream parser. > > I have both of them working fine, but now my question is:

[Haskell-cafe] Parsec question

2004-11-19 Thread John Goerzen
Hi, I'm porting a parser over from an OCamllex/Ocamlyacc version and I'm using Parsec for both the tokenizer and the resulting token stream parser. I have both of them working fine, but now my question is: how do I combine them? I can't quite figure out how to say "take the output from this GenP

Re: [Haskell-cafe] Re: [Haskell] Parsec question: attempted 'notMatching' combinator

2004-02-18 Thread Andrew Pimlott
On Wed, Feb 18, 2004 at 10:48:39AM +, Graham Klyne wrote: > [To Haskell-cafe...] > > At 16:57 17/02/04 -0500, Andrew Pimlott wrote: > >On Tue, Feb 17, 2004 at 07:48:52PM +, Graham Klyne wrote: > >> [[ > >> notMatching :: Show a => GenParser tok st a -> GenParser tok st () > >> notMatching

[Haskell-cafe] Re: [Haskell] Parsec question: attempted 'notMatching' combinator

2004-02-18 Thread Graham Klyne
[To Haskell-cafe...] At 16:57 17/02/04 -0500, Andrew Pimlott wrote: On Tue, Feb 17, 2004 at 07:48:52PM +, Graham Klyne wrote: > Thanks! That got me going, though not with quite what you suggested. > > I ended up with this: > [[ > notMatching :: Show a => GenParser tok st a -> GenParser tok st

Re: Parsec question

2004-01-01 Thread Mark Carroll
Thanks to Tom for his interesting points. I am still developing an inuition for how the error reporting goes. (-: On Thu, 1 Jan 2004, Derek Elkins wrote: (snip) > > > testOr3 = do{ try (string "(a"); char ')'; return "(a)" } (snip) > example both issues come up. If we successfully parse the >

Re: Parsec question

2004-01-01 Thread Tomasz Zielonka
On Wed, Dec 31, 2003 at 07:21:54PM -0500, Mark Carroll wrote: > I tried posting this before but, from my point of view, it vanished. My > apologies if it's a duplicate. > > In http://www.cs.uu.nl/~daan/download/parsec/parsec.html we read, > > > testOr2 = try (string "(a)") > > <|> strin

Re: Parsec question

2004-01-01 Thread Derek Elkins
On Wed, 31 Dec 2003 19:21:54 -0500 (EST) Mark Carroll <[EMAIL PROTECTED]> wrote: > I tried posting this before but, from my point of view, it vanished. > My apologies if it's a duplicate. > > In http://www.cs.uu.nl/~daan/download/parsec/parsec.html we read, > > > testOr2 = try (string "(a)") >

Parsec question

2003-12-31 Thread Mark Carroll
I tried posting this before but, from my point of view, it vanished. My apologies if it's a duplicate. In http://www.cs.uu.nl/~daan/download/parsec/parsec.html we read, > testOr2 = try (string "(a)") > <|> string "(b)" > > or an even better version: > > testOr3 = do{ try (string "(a")

Parsec question

2002-07-10 Thread Eray Ozkural
Hi there, I'm hacking together a small parser for a subset of C++. I'm in trouble with left recursion as you may guess. What is the best way to write a parser for the part of grammar below in Parsec? Declarator -> Name -> PtrOper Declarator -> Declarator '(' ArgDeclaratio