[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
aTag

many tagOrContent will consume all tags, so that no tag for the
following aTag will be left.

Cheers Christian

eof
return Parse complete.

 tagOrContent = aTag | someContent ? tagOrContent

 aTag = do
tagBegin
xs - many (noneOf [tagEndChar])
tagEnd
optionalWhiteSpace
return ()

 someContent = do
manyTill anyChar tagBegin
return ()

 optionalWhiteSpace = spaces   -- i.e., any of  \v\f\t\r\n
 tagBegin = char tagBeginChar
 tagEnd = char tagEndChar

 -- Etc:
 tagBeginChar = ''
 tagEndChar = ''
 
 
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[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
optionalWhiteSpace
aTag
many tagOrContent
aTag
 
 many tagOrContent will consume all tags, so that no tag for the
 following aTag will be left.

if you want to match a final tag, you could try:

  manyTill tagOrContent (try (aTag  eof))

 
 Cheers Christian
 
eof
return Parse complete.

 tagOrContent = aTag | someContent ? tagOrContent

 aTag = do
tagBegin
xs - many (noneOf [tagEndChar])

this also looks like manyTill anyChar tagEnd

C.

tagEnd
optionalWhiteSpace
return ()

 someContent = do
manyTill anyChar tagBegin
return ()

 optionalWhiteSpace = spaces   -- i.e., any of  \v\f\t\r\n
 tagBegin = char tagBeginChar
 tagEnd = char tagEndChar

 -- Etc:
 tagBeginChar = ''
 tagEndChar = ''

 
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[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:
 [...]

 -- Parsers:
 taggedContent = do
optionalWhiteSpace
aTag
many tagOrContent
aTag

 many tagOrContent will consume all tags, so that no tag for the
 following aTag will be left.
 
 if you want to match a final tag, you could try:
 
   manyTill tagOrContent (try (aTag  eof))

better yet, avoiding backtracking, return different things for aTag and
someContents and check if the last entry is a tag.

  tagOrContent = fmap Left aTag | fmap Right someContent

  taggedContent = do
   spaces
   aTag
   l - many tagOrContent
   eof
   case reverse l of
 Left _ : _ - return ()
 _ - fail expected final tag before EOF

C.


 Cheers Christian

eof
return Parse complete.

 tagOrContent = aTag | someContent ? tagOrContent

 aTag = do
tagBegin
xs - many (noneOf [tagEndChar])
 
 this also looks like manyTill anyChar tagEnd
 
 C.
 
tagEnd
optionalWhiteSpace
return ()

 someContent = do
manyTill anyChar tagBegin
return ()

 optionalWhiteSpace = spaces   -- i.e., any of  \v\f\t\r\n
 tagBegin = char tagBeginChar
 tagEnd = char tagEndChar

 -- Etc:
 tagBeginChar = ''
 tagEndChar = ''

 
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[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-cafe


[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 natural way to express
 the problem.

use lookAhead!

 parseKeyword :: Parser String
 parseKeyword = many1 (alphaNum | char '_')

  parseKeyword = string //  many1 (alphaNum | char '_')

 parseText :: Parser String
 parseText = manyTill anyChar ((try (string //)  return ())
   | eof)

  parseText = manyTill anyChar
$ (lookAhead (try $ string //)  return ())
  | eof

(untested)
C.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[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
return (i : r)
where
dotIdentifier = do
char '.'
i - identifier
r - dotIdentifier
return (i  : r)
| return []

Does that look sane to people who know Haskell and Parsec
better than  me?

Hi Erik,
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 identifier dot

benedikt
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


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 identifier dot

WOW That is really impressive!

Thanks,
Erik
-- 
-
Erik de Castro Lopo
-
One serious obstacle to the adoption of good programming languages is
the notion that everything has to be sacrificed for speed. In computer
languages as in life, speed kills. -- Mike Vanier
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


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.Parsec.Combinator
but I can't get it to work.

Clues?

Erik
-- 
-
Erik de Castro Lopo
-
That being done, all you have to do next is call free() slightly
less often than malloc(). You may want to examine the Solaris
system libraries for a particularly ambitious implementation of
this technique.
-- Eric O'Dell (comp.lang.dylan)
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


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
mle...@mega-nerd.com 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' combinator, and ? can be implemented with
the 'option' combinator.  Parsec is all about composing bigger parsers
out of smaller ones using combinators like these.

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.cs.uu.nl/daan/download/parsec/parsec.html
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


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.cs.uu.nl/daan/download/parsec/parsec.html

Ah yes, reading that document and using 'try' is a good tip. This
is what I cam up with:

qualifiedIdentStar :: CharParser st [ String ]
qualifiedIdentStar = do
try identDotStar
| qualifiedIdentifier
where
identDotStar = do
s - sepEndBy1 identifier dot
char '*'
return (s ++ [ * ])


Cheers,
Erik

-- 
-
Erik de Castro Lopo
-
It has been discovered that C++ provides a remarkable facility
for concealing the trival details of a program -- such as where
its bugs are. -- David Keppel
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[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 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
   showToken (pos,tok)   = show tok
   posToken  (pos,tok)   = pos
   testToken (pos,tok)   = test tok

The problem is, since SourcePos is an abstract datatype, how can I 
actually run this parser without explicitly using values of type 
SourcePos in the input stream?

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[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 MyParser a   = GenParser (SourcePos,Tok) () a
mytoken :: (Tok - Maybe a) - MyParser a
mytoken test
 = token showToken posToken testToken
 where
   showToken (pos,tok)   = show tok
   posToken  (pos,tok)   = pos
   testToken (pos,tok)   = test tok

The problem is, since SourcePos is an abstract datatype, how can I 
actually run this parser without explicitly using values of type SourcePos 
in the input stream?


_
Express yourself instantly with MSN Messenger! Download today it's FREE! 
http://messenger.msn.click-url.com/go/onm00200471ave/direct/01/


___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe