
Hi, I'm trying out some combinatorial parsers, and I ran into a slightly inelegant construction. To parse a sequence of things, we have a function like pThen3 :: (a->b->c->d) -> Parser a -> Parser b -> Parser c -> Parser d pThen3 combine p1 p2 p3 toks = [(combine v1 v2 v3, toks3) | (v1, toks1) <- p1 toks, (v2, toks2) <- p2 toks1, (v3, toks3) <- p3 toks2] The problem with this is that this structure has to be duplicated for pThen2, pThen4, and so on. These other forms are very similar to pThen3, but there seems to be no way to capture this in Haskell's type system, as the combine function has a different signature for each pThenX. (This is actually the first time the Haskell type system has got in my way rather than helping.) Is there a way around this problem? mrak

Mark Wotton writes: | Hi, | | I'm trying out some combinatorial parsers, and I ran into a slightly | inelegant construction. To parse a sequence of things, we have a function | like | | pThen3 :: (a->b->c->d) -> Parser a -> Parser b -> Parser c -> Parser d | pThen3 combine p1 p2 p3 toks = | [(combine v1 v2 v3, toks3) | (v1, toks1) <- p1 toks, | (v2, toks2) <- p2 toks1, | (v3, toks3) <- p3 toks2] | | The problem with this is that this structure has to be duplicated for | pThen2, pThen4, and so on. These other forms are very similar to pThen3, | but there seems to be no way to capture this in Haskell's type system, as | the combine function has a different signature for each pThenX. (This is | actually the first time the Haskell type system has got in my way rather | than helping.) Is there a way around this problem? If you can build the list of tokens into the state of your Parser monad - which would include making Parser a a distinct type instead of an alias for [Token] -> [(a, Token)] - you could condense pThen3 down to this: pThen3 combine p1 p2 p3 toks = do v1 <- p1 v2 <- p2 v3 <- p3 return (combine v1 v2 v3) which is equivalent to the liftM3 function from the Monad library. You'd still be stuck with a family of lifting functions, but at least they're predefined. I don't see any way of getting by with a fixed number of lifting functions, unless you're willing to clutter the call sites: infixl 0 `ap` ap :: Parser (a -> b) -> Parser a -> Parser b ap = Monad.ap ... ... Monad.liftM f p1 `ap` p2 `ap` p3 `ap` p4 Regards, Tom

On Thu, 21 Feb 2002, Mark Wotton wrote:
Hi,
I'm trying out some combinatorial parsers, and I ran into a slightly inelegant construction. To parse a sequence of things, we have a function like
pThen3 :: (a->b->c->d) -> Parser a -> Parser b -> Parser c -> Parser d pThen3 combine p1 p2 p3 toks = [(combine v1 v2 v3, toks3) | (v1, toks1) <- p1 toks, (v2, toks2) <- p2 toks1, (v3, toks3) <- p3 toks2]
The problem with this is that this structure has to be duplicated for pThen2, pThen4, and so on. These other forms are very similar to pThen3, but there seems to be no way to capture this in Haskell's type system, as the combine function has a different signature for each pThenX. (This is actually the first time the Haskell type system has got in my way rather than helping.) Is there a way around this problem?
Yes there is a way around this problem. You can use multi parameter type classes to create (and give a type to) a function such as pThenX. The details are worked out in the paper "Faking it" by Conor McBride. In that paper shows how to implement a generic zipWith in Haskell. The same technique should work for your function. The paper can be found on: http://www.dur.ac.uk/~dcs1ctm/ Cheers, /Josef

Josef Sveningsson wrote:
On Thu, 21 Feb 2002, Mark Wotton wrote:
Hi,
I'm trying out some combinatorial parsers, and I ran into a slightly inelegant construction. To parse a sequence of things, we have a function like
pThen3 :: (a->b->c->d) -> Parser a -> Parser b -> Parser c -> Parser d pThen3 combine p1 p2 p3 toks = [(combine v1 v2 v3, toks3) | (v1, toks1) <- p1 toks, (v2, toks2) <- p2 toks1, (v3, toks3) <- p3 toks2]
The problem with this is that this structure has to be duplicated for pThen2, pThen4, and so on. These other forms are very similar to pThen3, but there seems to be no way to capture this in Haskell's type system, as the combine function has a different signature for each pThenX. (This is actually the first time the Haskell type system has got in my way rather than helping.) Is there a way around this problem?
Yes there is a way around this problem. You can use multi parameter type classes to create (and give a type to) a function such as pThenX.
Or, in Standard Haskell you can do something like this: infixr `then2` infixr `thenn` then2:: Parser b -> Parser c -> ((b,c)->d) -> Parser d then2 p1 p2 comb toks = [(comb (a, b), rest) | (a, r1) <- p1 toks, (b, rest) <- p2 r1] thenn:: Parser a b -> ((t->d) -> Parser a d) -> ((b,t)->d) -> Parser a d thenn p1 cp2 comb toks = [(cmb, rest) | (a, r1) <- p1 toks, (cmb, rest) <- cp2 (\t->comb (a,t)) r1] and use like this (p1 `thenn` p2 `thenn` p3 `then2` p4) (\(a,(b,(c,d))) -> whatever) I'm not sure if you can get rid of the `then2`, but is seems quite servicable even so. Jón -- Jón Fairbairn Jon.Fairbairn@cl.cam.ac.uk 31 Chalmers Road jf@cl.cam.ac.uk Cambridge CB1 3SZ +44 1223 570179 (after 14:00 only, please!)

Hi all, There exist a really neat solution to this. I think that it is pioneered by Doaitse Swierstra and Luc Duponcheel in their parser combinators: http://www.cs.uu.nl/~doaitse/Papers/1996/LL1.pdf
I'm trying out some combinatorial parsers, and I ran into a slightly inelegant construction. To parse a sequence of things, we have a function like
pThen3 :: (a->b->c->d) -> Parser a -> Parser b -> Parser c -> Parser d
The problem with this is that this structure has to be duplicated for pThen2, pThen4, and so on. These other forms are very similar to pThen3,
Yes there is a way around this problem. You can use multi parameter type classes to create (and give a type to) a function such as pThenX.
Or, in Standard Haskell you can do something like this:
infixr `then2` infixr `thenn`
then2:: Parser b -> Parser c -> ((b,c)->d) -> Parser d thenn:: Parser a b -> ((t->d) -> Parser a d) -> ((b,t)->d) -> Parser a d
and use like this
(p1 `thenn` p2 `thenn` p3 `then2` p4) (\(a,(b,(c,d))) -> whatever)
I'm not sure if you can get rid of the `then2`, but is seems quite servicable even so.
The last solution is almost right, what we can do is to define two (arrow style) combinators, one for sequential composition and one for lifting values into the Parser type: (<*>) :: Parser (a -> b) -> Parser a -> Parser b succeed :: a -> Parser a Now, if we assign a left-associative priority to the (<*>) operator: infixl 4 <*>, we can combine it as follows: succeed (\x y z -> (x,y,z)) <*> p1 <*> p2 <*> p3 Note that the parens are as follows: (((succeed (\x y z -> (x,y,z)) <*> p1) <*> p2) <*> p3) And indeed, the first component has type: Parser (a -> b -> c -> (a,b,c)) and combines through (<*>) with (p1 :: Parser a) into (Parser (b -> c -> (a,b,c))) which combines through (<*>) and (p2 :: Parser b) into (Parser (c -> (a,b,c))) etc. Now, it helps off course to define another combinator: infix 5 <$> f <$> p = succeed f <*> p And you can write: f <$> p1 <*> p2 <*> p3 where f x y z = (x,y,z) With a little more cunning, you can also define combinators like (*>) and (<*) that leave out parser results: parens p = char '(' *> p <* char ')' The UU_parsing library embodies the epitome of this technique: http://www.cs.uu.nl/groups/ST/Software/UU_Parsing/ All the best, Daan.
-- Jón Fairbairn Jon.Fairbairn@cl.cam.ac.uk 31 Chalmers Road jf@cl.cam.ac.uk Cambridge CB1 3SZ +44 1223 570179 (after 14:00 only, please!)
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

On Fri, 22 Feb 2002, Daan Leijen wrote:
There exist a really neat solution to this. I think that it is pioneered by Doaitse Swierstra and Luc Duponcheel in their parser combinators:
Niklas Röjemo uses this style of combinators in his paper: "Efficient parsing combinators" from 95. It can be found on: http://www.cs.chalmers.se/~rojemo/thesis.html Cheers, /Josef
participants (5)
-
Daan Leijen
-
Jon Fairbairn
-
Josef Svenningsson
-
Mark Wotton
-
Tom Pledger