Haskell problem

Jon Fairbairn Jon.Fairbairn@cl.cam.ac.uk
Thu, 21 Feb 2002 15:17:48 +0000


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 func=
tion
> > like
> >
> > pThen3 :: (a->b->c->d) -> Parser a -> Parser b -> Parser c -> Parser =
d
> > pThen3 combine p1 p2 p3 toks =3D
> >         [(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 pThe=
n3,
> > 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 rat=
her
> > than helping.) Is there a way around this problem?
> >
> Yes there is a way around this problem. You can use multi parameter typ=
e
> 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 =3D [(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 =3D [(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=F3n


-- =

J=F3n Fairbairn                                 Jon.Fairbairn@cl.cam.ac.u=
k
31 Chalmers Road                                         jf@cl.cam.ac.uk
Cambridge CB1 3SZ            +44 1223 570179 (after 14:00 only, please!)