proposal #3335: make some Applicative functions into methods, and split off Data.Functor

The proposal is that the following functions (<$) :: Functor f => a -> f b -> f a (*>) :: Applicative f => f a -> f b -> f b (<*) :: Applicative f => f a -> f b -> f a some :: Alternative f => f a -> f [a] many :: Alternative f => f a -> f [a] are moved into the corresponding classes, with the existing implementations as default definitions. This gives people creating instances the option of defining specialized implementations of these functions, though they should be equivalent to the default definitions. Although (<$) is now a method of the Functor class, it is hidden in the re-export by the Prelude, Control.Monad and Monad. The new module Data.Functor exposes the full class, plus the function (<$>). These are also re-exported by Control.Applicative. Deadline: 20th July 2009.

Hi,
On Mon, Jun 29, 2009 at 2:45 PM, Ross Paterson
Although (<$) is now a method of the Functor class, it is hidden in the re-export by the Prelude, Control.Monad and Monad. The new module Data.Functor exposes the full class, plus the function (<$>). These are also re-exported by Control.Applicative.
Could we come up with some policy on what goes in Control.* versus Data.*? As we add more and more modules that fits in both categories it's becoming increasingly hard to remember what lives where. Using both Data and Control gives import lists an ugly asymmetry: import Control.Applicative import Data.Functor import Control.Monad Cheers, Johan

Either way there is an asymmetry when Functor is involved, putting it in
Control would break up the cluster of:
import Data.Functor
import Data.Foldable
import Data.Traversable
So, I can't see it mattering too much which color the bikeshed is painted,
but if the community decides that Control.Functor is the place this should
go I'll happily move the Control.Functor module in category-extras to
another name.
-Edward Kmett
On Mon, Jun 29, 2009 at 9:03 AM, Johan Tibell
Hi,
On Mon, Jun 29, 2009 at 2:45 PM, Ross Paterson
wrote: Although (<$) is now a method of the Functor class, it is hidden in the re-export by the Prelude, Control.Monad and Monad. The new module Data.Functor exposes the full class, plus the function (<$>). These are also re-exported by Control.Applicative.
Could we come up with some policy on what goes in Control.* versus Data.*? As we add more and more modules that fits in both categories it's becoming increasingly hard to remember what lives where. Using both Data and Control gives import lists an ugly asymmetry:
import Control.Applicative import Data.Functor import Control.Monad
Cheers,
Johan
_______________________________________________ Libraries mailing list Libraries@haskell.org http://www.haskell.org/mailman/listinfo/libraries

+++++ This would solve some serious problems I have encountered using these routines in practice. John -- John Meacham - ⑆repetae.net⑆john⑈ - http://notanumber.net/

On Mon, Jun 29, 2009 at 8:45 AM, Ross Paterson
The proposal is that the following functions
(<$) :: Functor f => a -> f b -> f a (*>) :: Applicative f => f a -> f b -> f b (<*) :: Applicative f => f a -> f b -> f a some :: Alternative f => f a -> f [a] many :: Alternative f => f a -> f [a]
are moved into the corresponding classes, with the existing implementations as default definitions. This gives people creating instances the option of defining specialized implementations of these functions, though they should be equivalent to the default definitions.
How about liftA2?
--
Dave Menendez

On Mon, Jun 29, 2009 at 02:37:56PM -0400, David Menendez wrote:
How about liftA2?
2 is a scary number. Do you have an example in mind where a customized liftA2 would be a big win?

On Mon, Jun 29, 2009 at 4:31 PM, Ross Paterson
On Mon, Jun 29, 2009 at 02:37:56PM -0400, David Menendez wrote:
How about liftA2?
2 is a scary number. Do you have an example in mind where a customized liftA2 would be a big win?
I don't know about a big win, but my preference for Applicative has always been to define <*> and liftA2 as co-primitives, like so: class Functor f => Applicative f where pure :: a -> f a liftA2 :: (a -> b -> c) -> f a -> f b -> f c (<*>) :: f (a -> b) -> f a -> f b (<*>) = liftA2 ($) liftA2 f a b = fmap f a <*> b This is how the old arrows package defined Sequence, one of the precursors to Applicative., and it's analogous to the argument that
= and join should both be members of Monad.
Back in 2006 I pointed out that a custom liftA2 would be sufficient to
fix frisby's problems with *> and <*.
http://www.haskell.org/pipermail/libraries/2006-October/005902.html
Specifically, if liftA2 is defined like so:
liftA2 f (P a) (P b) = P $ PMap (uncurry f) (Then a b)
and (*>) is defined using liftA2,
(*>) = liftA2 (const id)
then (*>) is naturally the same as Frisby's custom (->>), without the
need for a custom definition.
--
Dave Menendez

Am Dienstag, 30. Juni 2009 00:01 schrieb David Menendez:
On Mon, Jun 29, 2009 at 4:31 PM, Ross Paterson
wrote: On Mon, Jun 29, 2009 at 02:37:56PM -0400, David Menendez wrote:
How about liftA2?
2 is a scary number. Do you have an example in mind where a customized liftA2 would be a big win?
I don't know about a big win, but my preference for Applicative has always been to define <*> and liftA2 as co-primitives, like so:
class Functor f => Applicative f where pure :: a -> f a liftA2 :: (a -> b -> c) -> f a -> f b -> f c (<*>) :: f (a -> b) -> f a -> f b
(<*>) = liftA2 ($) liftA2 f a b = fmap f a <*> b
Wouldn’t it make more sense to define (<*>) and pair as co-primitives, where pair = liftA2 (,)? class Functor f => Applicative f where pure :: a -> f a pair :: f a -> f b -> f (a,b) (<*>) :: f (a -> b) -> f a -> f b (<*>) = fmap (uncurry ($)) . pair pair fa fb = pure (,) <*> fa <*> fb Best wishes, Wolfgang

On Fri, Jul 17, 2009 at 9:56 AM, Wolfgang
Jeltsch
Am Dienstag, 30. Juni 2009 00:01 schrieb David Menendez:
On Mon, Jun 29, 2009 at 4:31 PM, Ross Paterson
wrote: On Mon, Jun 29, 2009 at 02:37:56PM -0400, David Menendez wrote:
How about liftA2?
2 is a scary number. Do you have an example in mind where a customized liftA2 would be a big win?
I don't know about a big win, but my preference for Applicative has always been to define <*> and liftA2 as co-primitives, like so:
class Functor f => Applicative f where pure :: a -> f a liftA2 :: (a -> b -> c) -> f a -> f b -> f c (<*>) :: f (a -> b) -> f a -> f b
(<*>) = liftA2 ($) liftA2 f a b = fmap f a <*> b
Wouldn’t it make more sense to define (<*>) and pair as co-primitives, where pair = liftA2 (,)?
Defining pair in terms of liftA2 is simpler than defining liftA2 in
terms of pair.
pair = liftA2 (,) -- just partial application
liftA2 f a b =uncurry f <$> pair a b -- creates and destroys an
intermediate representation
--
Dave Menendez

On Mon, 29 Jun 2009, Ross Paterson wrote:
The proposal is that the following functions
(<$) :: Functor f => a -> f b -> f a (*>) :: Applicative f => f a -> f b -> f b (<*) :: Applicative f => f a -> f b -> f a some :: Alternative f => f a -> f [a] many :: Alternative f => f a -> f [a]
are moved into the corresponding classes, with the existing implementations as default definitions. This gives people creating instances the option of defining specialized implementations of these functions, though they should be equivalent to the default definitions.
This sounds like a rather ad-hoc extension of the already complicated hierarchy of those category classes. Are there particular examples where the specialisation is needed and where it cannot be done by optimizer rules? In case the specialised functions differ semantically from the default implementations - are there generic algorithms that rely on these semantic exceptions? Otherwise specialised functons can well be implemented as plain functions and don't need to be type class methods.

On Tue, Jun 30, 2009 at 01:37:05PM +0200, Henning Thielemann wrote:
This sounds like a rather ad-hoc extension of the already complicated hierarchy of those category classes. Are there particular examples where the specialisation is needed and where it cannot be done by optimizer rules?
Here's one for (<$). In Data.Sequence, I could define x <$ s = replicate (size s) x (using Louis Wasserman's replicate), which would take O(log n) time and space, a big improvement over the O(n) version using const and fmap.

Ross Paterson schrieb:
On Tue, Jun 30, 2009 at 01:37:05PM +0200, Henning Thielemann wrote:
This sounds like a rather ad-hoc extension of the already complicated hierarchy of those category classes. Are there particular examples where the specialisation is needed and where it cannot be done by optimizer rules?
Here's one for (<$). In Data.Sequence, I could define
x <$ s = replicate (size s) x
(using Louis Wasserman's replicate), which would take O(log n) time and space, a big improvement over the O(n) version using const and fmap.
Would it be reasonable to let the optimizer replace (x <$ s) by (replicate (size s) x) via RULES?

On Sat, Jul 04, 2009 at 01:08:41AM +0200, Henning Thielemann wrote:
Ross Paterson schrieb:
On Tue, Jun 30, 2009 at 01:37:05PM +0200, Henning Thielemann wrote:
This sounds like a rather ad-hoc extension of the already complicated hierarchy of those category classes. Are there particular examples where the specialisation is needed and where it cannot be done by optimizer rules?
Here's one for (<$). In Data.Sequence, I could define
x <$ s = replicate (size s) x
(using Louis Wasserman's replicate), which would take O(log n) time and space, a big improvement over the O(n) version using const and fmap.
Would it be reasonable to let the optimizer replace (x <$ s) by (replicate (size s) x) via RULES?
I don't like using RULES for optimizations that actually change the computational or space complexity of code. The reason being that often the complexity determines whether an algorithm works at all (like whether frisby requires O(n) space or O(1) space, a fundamental difference in functionality). We need control of what algorithms are used, not to rely on an compiler specific extension that may or may not get applied properly. In addition, RULES won't apply to polymorphic functions written on top of the existing ones that call class methods. RULES only apply to the top level interface when they do apply. instance definitions will always be used. John -- John Meacham - ⑆repetae.net⑆john⑈ - http://notanumber.net/

John Meacham wrote:
On Sat, Jul 04, 2009 at 01:08:41AM +0200, Henning Thielemann wrote:
Ross Paterson schrieb:
On Tue, Jun 30, 2009 at 01:37:05PM +0200, Henning Thielemann wrote:
This sounds like a rather ad-hoc extension of the already complicated hierarchy of those category classes. Are there particular examples where the specialisation is needed and where it cannot be done by optimizer rules? Here's one for (<$). In Data.Sequence, I could define
x <$ s = replicate (size s) x
(using Louis Wasserman's replicate), which would take O(log n) time and space, a big improvement over the O(n) version using const and fmap. Would it be reasonable to let the optimizer replace (x <$ s) by (replicate (size s) x) via RULES?
I don't like using RULES for optimizations that actually change the computational or space complexity of code.
It was said, that the new methods should equal the default definitions, that is, they cannot be "optimized too much", e.g. the specialized definitions are not allow to produce something defined where the default definition is undefined. That's the situation where RULES are made for. It's sad that application of RULES is so unreliable and maybe that should be seriously improved. However, when doing optimization via type class methods I see the danger that after splitting all standard type classes down to one method per class in the past years we will see another flood of extending the type class by specialized functions, maybe followed by new splits. Maybe such a development is a good thing, but then again, we still have no good tools to keep in sync with all these modifications.

On Tue, Jun 30, 2009 at 7:37 AM, Henning Thielemann < lemming@henning-thielemann.de> wrote:
On Mon, 29 Jun 2009, Ross Paterson wrote:
The proposal is that the following functions
(<$) :: Functor f => a -> f b -> f a (*>) :: Applicative f => f a -> f b -> f b (<*) :: Applicative f => f a -> f b -> f a some :: Alternative f => f a -> f [a] many :: Alternative f => f a -> f [a]
This sounds like a rather ad-hoc extension of the already complicated hierarchy of those category classes. Are there particular examples where the specialisation is needed and where it cannot be done by optimizer rules? In case the specialised functions differ semantically from the default implementations - are there generic algorithms that rely on these semantic exceptions? Otherwise specialised functons can well be implemented as plain functions and don't need to be type class methods.
Yes, there are. Usually the arise when deriving new parser combinators. uu-parsinglib currently deals with its own 'ExtApplicative' type to get functionality that could otherwise be readily provided by these methods. In general, its faster not to bother with the 'pure' parts of an applicative computation when you know you are going to throw away the result. In uu-parsinglib this is done with a separate 'R' type of recognizing parser, but the recognizing parser could be folded into their P_m parser type and the above instance methods used. I've been burned by this myself as well. I also have a set of parser combinators that I've been working on that could currently greatly benefit from these asymptotically in some places and in the case of a bottom up monoidal parser I've been working with, the availability of these makes the difference between termination and non-termination in some cases. In particular, if you buid up a GADT out of your applicative, you can usually fold together nodes that differ only in terms of the components generated by calls to 'pure' when you are down a branch in one of these specialized cases. When building a parser bottom up, this can dramatically increase sharing. It might be nice to also have (<**>) in the patch. -Edward Kmett

On Tue, Jun 30, 2009 at 11:45:50AM -0400, Edward Kmett wrote:
I've been burned by this myself as well. I also have a set of parser combinators that I've been working on that could currently greatly benefit from these asymptotically in some places and in the case of a bottom up monoidal parser I've been working with, the availability of these makes the difference between termination and non-termination in some cases.
Ah, but that's changing the meaning, which isn't what these are supposed to be for.

Admittedly, my non-termination case basically kicks in when the pure
function returns bottom and might be resolved by being less strict at the
risk of space leaks in the parser. The asymptotic issues arise from much
more defensible use cases ala your enhanced sharing example, since I can
share leaf level recognizers regardless of the pure annotation, if I don't
care about the value that results.
As a parenthetical aside, by special casing 'many' and 'sepEndBy' I can
implement all of the other parsec style combinators that make sense in an
Applicative setting without any other form of recursion allowed in the GADT
I construct from the grammar. You still need arbitrary recursion for user
defined grammars, but the common grammar combinators can all be implemented
by biting off those two cases, or just the latter if you want to be
minimalist about it.
-Edward Kmett
On Tue, Jun 30, 2009 at 11:58 AM, Ross Paterson
On Tue, Jun 30, 2009 at 11:45:50AM -0400, Edward Kmett wrote:
I've been burned by this myself as well. I also have a set of parser combinators that I've been working on that could currently greatly benefit from these asymptotically in some places and in the case of a bottom up monoidal parser I've been working with, the availability of these makes the difference between termination and non-termination in some cases.
Ah, but that's changing the meaning, which isn't what these are supposed to be for. _______________________________________________ Libraries mailing list Libraries@haskell.org http://www.haskell.org/mailman/listinfo/libraries

On Tue, Jun 30, 2009 at 04:58:13PM +0100, Ross Paterson wrote:
On Tue, Jun 30, 2009 at 11:45:50AM -0400, Edward Kmett wrote:
I've been burned by this myself as well. I also have a set of parser combinators that I've been working on that could currently greatly benefit from these asymptotically in some places and in the case of a bottom up monoidal parser I've been working with, the availability of these makes the difference between termination and non-termination in some cases.
Ah, but that's changing the meaning, which isn't what these are supposed to be for.
I don't see why not. As long as your versions follow whatever rules are specified for the class. frisby also cannot use Applicative as is because these methods arn't able to be overridden and the default implementations lead to pessimal (to the point of unusabality, or even non-termination) performance. However frisby can provide perfectly valid implementations of them that follow the Applicative laws and have no such issues. Actually, 'Alternative' doesn't have any rules as to its meaning, which is probably why the broken 'many' and 'some' ended up there in the first place. Personally, I'd prefer just to drop 'many' and 'some' (and perhaps 'Alternative' itself) completely since it isn't clear meaningful definitions exist for what we might consider members of 'Alternative'. But making them members of the class is an acceptable compromise if people don't want to drop Alternative. Without a clear meaning, it is basically just a syntax reuse class. John -- John Meacham - ⑆repetae.net⑆john⑈ - http://notanumber.net/

On Tue, Jun 30, 2009 at 06:24:57PM -0700, John Meacham wrote:
On Tue, Jun 30, 2009 at 04:58:13PM +0100, Ross Paterson wrote:
Ah, but that's changing the meaning, which isn't what these are supposed to be for.
I don't see why not. As long as your versions follow whatever rules are specified for the class.
The rules specified in this case are that the specialized version defines the same function as the default definition.
frisby also cannot use Applicative as is because these methods arn't able to be overridden and the default implementations lead to pessimal (to the point of unusabality, or even non-termination) performance. However frisby can provide perfectly valid implementations of them that follow the Applicative laws and have no such issues.
Something doesn't add up here: things that don't terminate are not equal to things that do.
Actually, 'Alternative' doesn't have any rules as to its meaning, which is probably why the broken 'many' and 'some' ended up there in the first place. Personally, I'd prefer just to drop 'many' and 'some' (and perhaps 'Alternative' itself) completely since it isn't clear meaningful definitions exist for what we might consider members of 'Alternative'.
It's true that Alternative is loosely specified, requiring only a monoid, but it's still very useful (like MonadPlus). In my opinion, the compelling application is "Parsing Permutation Phrases", by Arthur Baars, Andres Loeh and S. Doaitse Swierstra, Haskell Workshop 2001 (see the action-permutations package). It does seem that your application doesn't fit the class, but it's not clear how dropping it would help.

On Tue, Jun 30, 2009 at 01:37:05PM +0200, Henning Thielemann wrote:
On Mon, 29 Jun 2009, Ross Paterson wrote:
The proposal is that the following functions
(<$) :: Functor f => a -> f b -> f a (*>) :: Applicative f => f a -> f b -> f b (<*) :: Applicative f => f a -> f b -> f a some :: Alternative f => f a -> f [a] many :: Alternative f => f a -> f [a]
are moved into the corresponding classes, with the existing implementations as default definitions. This gives people creating instances the option of defining specialized implementations of these functions, though they should be equivalent to the default definitions.
This sounds like a rather ad-hoc extension of the already complicated hierarchy of those category classes. Are there particular examples where the specialisation is needed and where it cannot be done by optimizer rules? In case the specialised functions differ semantically from the default implementations - are there generic algorithms that rely on these semantic exceptions? Otherwise specialised functons can well be implemented as plain functions and don't need to be type class methods.
I think this is a fair point: each proposed method should be justified by a concrete example (i.e. code) of an equivalent definition that achieves a significant performance improvement that one could not reasonably expect from an optimizer. I've given one for (<$).

On Mon, Jun 29, 2009 at 01:45:45PM +0100, Ross Paterson wrote:
The proposal is that the following functions
(<$) :: Functor f => a -> f b -> f a (*>) :: Applicative f => f a -> f b -> f b (<*) :: Applicative f => f a -> f b -> f a some :: Alternative f => f a -> f [a] many :: Alternative f => f a -> f [a]
are moved into the corresponding classes, with the existing implementations as default definitions.
Henning asked for concrete examples (i.e. code) where this would give a substantial performance win while still defining the same function, including termination properties. (But it seems reasonable not to rely on RULES to improve the asymptotic complexity.) I gave an example for (<$). Does anyone have concrete examples for the others?

(*>) 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.
-Edward Kmett
On Wed, Aug 19, 2009 at 11:40 AM, Ross Paterson
On Mon, Jun 29, 2009 at 01:45:45PM +0100, Ross Paterson wrote:
The proposal is that the following functions
(<$) :: Functor f => a -> f b -> f a (*>) :: Applicative f => f a -> f b -> f b (<*) :: Applicative f => f a -> f b -> f a some :: Alternative f => f a -> f [a] many :: Alternative f => f a -> f [a]
are moved into the corresponding classes, with the existing implementations as default definitions.
Henning asked for concrete examples (i.e. code) where this would give a substantial performance win while still defining the same function, including termination properties. (But it seems reasonable not to rely on RULES to improve the asymptotic complexity.)
I gave an example for (<$). Does anyone have concrete examples for the others? _______________________________________________ Libraries mailing list Libraries@haskell.org http://www.haskell.org/mailman/listinfo/libraries

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?

On Wed, Aug 19, 2009 at 4:21 PM, Ross Paterson
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

Please pretend I sprinkled primes liberally through the last two code
fragments. ;)
On Wed, Aug 19, 2009 at 5:00 PM, Edward Kmett
On Wed, Aug 19, 2009 at 4:21 PM, Ross Paterson
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
participants (7)
-
David Menendez
-
Edward Kmett
-
Henning Thielemann
-
Johan Tibell
-
John Meacham
-
Ross Paterson
-
Wolfgang Jeltsch