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
> 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?
>
> Many thanks in advance!
>

I'm almost convinced, you don't really want to parse a list of (SourcePos,Tok) 
pairs. The SourcePos is taken care of in the internal state of the parsers. 
And maybe, you should use tokenPrim instead of token. Then you'd probably get 
something like

type MyParser a = GenParser Tok () a

mytoken :: (Tok -> Maybe a) -> MyParser a
mytoken test = tokenPrim show update test
               where
                 update pos tok toks = case tok of
                               NewL -> setSourceColumn (incSourceLine pos 1) 1
                               _    -> incSourceColumn pos 1

or whatever is an appropriate update function for the SourcePos. If Tok is 
Char, of course a wealth of parsers are already supplied.

HTH

Cheers,
Daniel
_______________________________________________
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe

Reply via email to