
Hi, I propose to remove class Alternative and functions depending on it (optional, some, and many) from Control.Applicative. They can be moved into a separate module Control.Alternative if people desire such a class, but I doubt that it has many useful applications, at least in its present form. Rationale: Although the idea behind Alternative, i.e. generalize some of the functions commonly found in parser combinator libs, is a nice one, it doesn't work too well in practice, /even/ for the case that has inspired it (namely parsers). This is mostly due to the class method 'empty'. First of all, this is a bad name, /especially/ in the context of parsers, where 'empty' intuitively means 'recognize the empty sequence of tokens' which is definitely /not/ what Alternative's 'empty' means. (Indeed, this is normally be the meaning of 'pure' from class Applicative.) The 'empty' from Alternative rather means 'fail'. Yeah, I know that this name is already taken by class Monad. Many names would be better than 'empty', for instance 'none', or just 'failed'. (I'll stick with 'none' in what follows.) Second, and more important, is that some parser libs would like to, but cannot offer a sensible implementation for it. For instance, any error-correcting library of parser combinators (like those invented by Swierstra & Duponcheel) need to construct a valid result even in case of a failed parse. Thus, the user must be able to pass an argument to 'none' which would be possible only if it had a function type, like in class Alternative f where ... none :: a -> f a However, even this wouldn't be enough in practice because typically you will want to pass additional data, like an error message. How this can be properly generalized is something that needs more thought. Some of you might be tempted to say "if you don't like Alternative, just don't use it". However, not using it means additional effort, as I /would/ like to use class Applicative /and/ the <|> operator with its intended meaning, i.e. choice/alternative, and also the dependent functions (optional, many, etc). So currently I have to explicitly hide all the Alternative stuff, like this import Control.Applicative hiding (Alternative(..),optional,some,many) which is not nice at all. As a final point, class Alternative comes with no stated laws. While there are a number of standard classes where laws don't make much sense (like, e.g. Show, or Typeable), this is clearly not one of those cases: The docs say Alternative is "a monoid on applicative functors". This suggests associativity and left/right unit laws. However, this is most probably not the whole story, i.e. how are <|> and the ill-named 'empty' supposed to interact with the operations and laws for Applicative? Are we going to have the same dilemma here, as with MonadPlus vs. MonadZero/MonadOr, whatever? Conclusion: In its current form, class Alternative looks like it has been hastily cobbled together. Thus it has no place in Control.Applicative. Moving it into its own separate module is the least we can do. Cheers Ben

I have the exact same issues with Alternative. My frisby parser library[1] is incompatable with the way Alternative is defined. It is particularly irksome because I have users that want to use the applicative syntax, but the Alternative definitions get in the way. Even if we don't get rid of it, moving many,some, etc.. into the class itself would be an improvement. But as was mentioned, it is quite unclear whether sensible definitions exist for all things we may want to be in alternative, or even what belongs in alternative at all. [1] http://repetae.net/computer/frisby/ John -- John Meacham - ⑆repetae.net⑆john⑈

Am Sonntag, 15. März 2009 23:50 schrieb Ben Franksen:
This is mostly due to the class method 'empty'.
First of all, this is a bad name, /especially/ in the context of parsers, where 'empty' intuitively means 'recognize the empty sequence of tokens' which is definitely /not/ what Alternative's 'empty' means. (Indeed, this is normally be the meaning of 'pure' from class Applicative.)
The 'empty' from Alternative rather means 'fail'. Yeah, I know that this name is already taken by class Monad. Many names would be better than 'empty', for instance 'none', or just 'failed'. (I'll stick with 'none' in what follows.)
The parser fails so “fail” might be a good name. However, when using an applicative style for writing parsers (in contrast to the “imperative” do notation), you almost write a grammar of your language. And “empty” just denotes the empty language. So the name might be not as bad as it first looks like. Best wishes, Wolfgang

On Sun, Mar 15, 2009 at 11:50:15PM +0100, Ben Franksen wrote:
I propose to remove class Alternative and functions depending on it (optional, some, and many) from Control.Applicative. They can be moved into a separate module Control.Alternative if people desire such a class, but I doubt that it has many useful applications, at least in its present form.
In my opinion, the "killer app" for Alternative is "Parsing Permutation Phrases", by Arthur Baars, Andres Loeh and S. Doaitse Swierstra, Haskell Workshop 2001. I've just uploaded a package action-permutations based on this.
Rationale:
Although the idea behind Alternative, i.e. generalize some of the functions commonly found in parser combinator libs, is a nice one, it doesn't work too well in practice, /even/ for the case that has inspired it (namely parsers).
This is mostly due to the class method 'empty'. [...] Second, and more important, is that some parser libs would like to, but cannot offer a sensible implementation for it. For instance, any error-correcting library of parser combinators (like those invented by Swierstra & Duponcheel) need to construct a valid result even in case of a failed parse.
That's odd: I thought all of Doaitse's parsers had pFail :: p a.

Ross Paterson wrote:
On Sun, Mar 15, 2009 at 11:50:15PM +0100, Ben Franksen wrote:
I propose to remove class Alternative and functions depending on it (optional, some, and many) from Control.Applicative. They can be moved into a separate module Control.Alternative if people desire such a class, but I doubt that it has many useful applications, at least in its present form.
In my opinion, the "killer app" for Alternative is "Parsing Permutation Phrases", by Arthur Baars, Andres Loeh and S. Doaitse Swierstra, Haskell Workshop 2001. I've just uploaded a package action-permutations based on this.
Taking a quick look at the paper, I can't seem to find the definition of pFail. Hmm, have to read it more carefully; look at your code, too.
Rationale:
Although the idea behind Alternative, i.e. generalize some of the functions commonly found in parser combinator libs, is a nice one, it doesn't work too well in practice, /even/ for the case that has inspired it (namely parsers).
This is mostly due to the class method 'empty'. [...] Second, and more important, is that some parser libs would like to, but cannot offer a sensible implementation for it. For instance, any error-correcting library of parser combinators (like those invented by Swierstra & Duponcheel) need to construct a valid result even in case of a failed parse.
That's odd: I thought all of Doaitse's parsers had pFail :: p a.
I was refering to the 1996 paper titled "Deterministic, Error-Correcting Combinator Parsers", where the 'fail' parser needs extra arguments. Maybe I am dense, but I can't see how to avoid the arguments w/o constraining the type of the result (which would mean the parsers can't even be instances of Applicative). What about the lack of stated laws for Alternative, i.e. how do the monoid laws interact with the Applicative laws? Cheers Ben

Ben Franksen wrote:
I was refering to the 1996 paper titled "Deterministic, Error-Correcting Combinator Parsers", where the 'fail' parser needs extra arguments. Maybe I am dense, but I can't see how to avoid the arguments w/o constraining the type of the result (which would mean the parsers can't even be instances of Applicative).
The trick is to not constrain the result type: pFail should be polymorphic in its result type. Suppose you use the list of successes parser:
type Parser s a = [s] -> [(a, [s])]
Then pFail may be defined as:
pFail :: Parser s a pFail = const []
i.e. polymorphic in output (and input too), because [] :: [a] is polymorphic in its element type. I'm pretty sure most if not all modern parse libraries contain such a function. HTH, Martijn.

Martijn van Steenbergen wrote:
Ben Franksen wrote:
I was refering to the 1996 paper titled "Deterministic, Error-Correcting Combinator Parsers", where the 'fail' parser needs extra arguments. Maybe I am dense, but I can't see how to avoid the arguments w/o constraining the type of the result (which would mean the parsers can't even be instances of Applicative).
The trick is to not constrain the result type: pFail should be polymorphic in its result type. Suppose you use the list of successes parser:
type Parser s a = [s] -> [(a, [s])]
Then pFail may be defined as:
pFail :: Parser s a pFail = const []
i.e. polymorphic in output (and input too), because [] :: [a] is polymorphic in its element type.
I never claimed that _no_ parser combinator library can offer pFail :: p a ; indeed, most do. The problem I see is when parsers are supposed to be error-correcting, particularly if this means they should never fail to produce a result. (A parser of the 'list of successes' type can not have this property, because [] means 'no result'.) And now the question is how some pFail :: p a can conjure up a result value if the result type a is not constrained (e.g. to have a 'default' element). The other problem is good error messages. For instance, although Parsec has a parserZero :: (Monad m) => ParsecT s u m a it is defined thus (in version 3.0.0): parserZero = ParsecT $ \s -> return $ Empty $ return $ Error (unknownError s) that is, you'll get no usable error message. Fortunately, for practical use there is parserFail :: (Monad m) => String -> ParsecT s u m a and this requires an extra argument. Cheers Ben
participants (5)
-
Ben Franksen
-
John Meacham
-
Martijn van Steenbergen
-
Ross Paterson
-
Wolfgang Jeltsch