Please pretend I sprinkled primes liberally through the last two code fragments. ;)

On Wed, Aug 19, 2009 at 5:00 PM, Edward Kmett <ekmett@gmail.com> wrote:
On Wed, Aug 19, 2009 at 4:21 PM, Ross Paterson <ross@soi.city.ac.uk> wrote:
On Wed, Aug 19, 2009 at 01:04:13PM -0400, Edward Kmett wrote:
> (*>) and (<*) could be used to apply recognizing parsers for the
> discarded half.  This makes a huge gain for uu-parsinglib.
> uu-parsinglib's P_m monad could be extended just as it has done with
> P_f and P_h to also wrap its existing R monad, which would let it
> apply the parser as a recognizer efficiently.
>
> And for parsimony it allows me to treat that side of the alternative
> grammar as a right seminearring ignoring the argument, this increases
> sharing opportunities for my grammar fragments, because pure nodes in
> recognizers can be treated as epsilons in the grammar and safely elided.

code?
 
The parsimony case is a bit drastic to post here, because I'd have to basically post the whole library and I haven't released it yet, or rewritten it to accomodate these extra Applicative actions.
 
However, I can try to do justice to how uu-parsinglib could use the new members. It currently has several parsers, which have types i'll abridge here.
 
newtype  P_h    st  a =  P_h  (forall r . (a  -> st -> Steps r)  -> st -> Steps r)
newtype  P_f st a  = P_f (forall r . (st -> Steps   r) -> st -> Steps   (a, r))
newtype  R st a  = R (forall r . (st -> Steps   r) -> st -> Steps r)
newtype P_m state a = P_m (P_h  state a, P_f state a)

It uses an 'ExtApplicative' class to let it mix recognizers (R's) with other parsers when you will just be discarding the recognized branch of the result. Note P_f and R are both Applicative, not Monadic.
 
I'll just handle (<*) to avoid clutter below.
 
class  Applicative p => ExtApplicative p where
  (<<*)      ::  p  a -> R (State p) b   -> p  a
 
instance ExtApplicative (P_h st)  where
  P_h p <<* R r     = P_h ( p. (r.))
instance ExtApplicative (P_f st) where
  P_f p <<* R r     = P_f (\ k st -> p (r k) st)
 
R just discards its phantom type argument. So it is trivially a Functor.
 
instance Functor (R st) where
     fmap _  (R r)       =  R r
 
Also note that the ExtApplicative case above could not be defined with P_f rather than R.  P_f has to deal with its argument, and isn't able to when you would try to apply it like R above. When used applicatively however...
 
instance  Functor (P_f st) where
    fmap f (P_f p)     =  P_f (\k inp ->  Apply (\(a,r) -> (f a, r)) (p k inp))
 
This could be made into a more palatable functor by Yoneda encoding some of the Step GADT constructors, to carry around any mappings, but that is irrelevant to this exposition.
 
The P_m monad uses a mechanism for binding history parsers to future parsers, which basically lets the context-free future be glued onto a context-sensitive history.
 
instance Applicative (P_m st) => Monad (P_m st) where
     P_m  (P_h p, _)  >>=  a2q =
           P_m  (  P_h   (\k -> p (\ a -> unP_m_h (a2q a) k))
                ,  P_f   (\k -> p (\ a -> unP_m_f (a2q a) k))
                )
But the same thing can be done with some modifications to P_m to add a possible recognizer (R) as an end-state. These represent a monadic computation with the final batch of applicative or right seminearring operations that end it separated out.

newtype P_m' state a = P_m (P_h  state a, P_f state a, R state a)
instance Applicative (P_m st) => Monad (P_m st) where
     P_m'  (P_h p, _)  >>=  a2q =
           P_m'  (  P_h   (\k -> p (\ a -> unP_m'_h (a2q a) k))
                ,  P_f   (\k -> p (\ a -> unP_m'_f (a2q a) k))
                ,  P_r   (\k -> p (\ a -> unP_m'_r (a2q a) k))
                )
And then you can drop in special cases for (*>) and (<*) which
mirror the existing code for the ExtApplicative operators of the same name in uu-parsinglib.

instance  Applicative (P_m st) where
  P_m (hp, fp,rp)  <* P_m (_,_,r)  = P_m  (hp <<* r, fp <<* r, rp <* r)
 
 
Now, the a parser written with a substantially unmodified uu-parsinglib can efficiently evaluate the side of the computation that is being ignored because any epsilon productions in that side come for free, so all the fiddly little fmapping that goes on in the Applicative is ignored.
 
Doaitse could probably do this better justice than I, as I only have a passing familiarity with the internals of uu-parsinglib.
 
parsimony can derive a similar benefit by accumulating a right seminnearring parser as a grammar-algebra off of the base functor for my grammars and applying that grammar when possible for <*'d fragments in a similar fashion, but as it only deals with context-free attribute grammars, it has a simpler job to do.
 
-Edward Kmett
 
_______________________________________________
Libraries mailing list
Libraries@haskell.org
http://www.haskell.org/mailman/listinfo/libraries