[Alternative] summary of my understanding so far

Hey everyone! First of all, it sounds like we all agree that the documentation for Alternative needs to be improved; that alone would clear a lot of the confusion up. I think that a fairly convincing case has also been made that removing many/some from the typeclass doesn't help too much since they are generically defined in terms of the other methods. Put another way, arguing that removing many/some makes Alternative more safe would be like arguing that removing "forever" from the definition of Monad (assuming it were currently a method rather than a function) made Monad more safe. (On the other hand, it might be nice if many/some were not featured so prominently above other functions/combinators in the module.) As a corollary to the above paragraph, if the many/some methods *were* moved to a subclass --- call it, "Parser" --- then essentially this subclass would be redundant. Nonetheless, such a subclass could still be useful because it supplies more information to the user about how the type behaves. That is, while any user of an instance of Alternative can always theoretically use something like many/some, in practice a user might want to add the Parser constraint to their type just to get an extra guarantee that many/some not only exist but are well-behaved. Although many/some cause infinite loops for the current instance of Maybe and [], forever also causes loops for (return (undefined)) for any Monad. Thus, even in the likely event that we decide to keep many/some in Alternative, it still makes sense to have Alternative instances for Maybe and [], despite the fact that they don't play well with many/some for non-empty values. In fact, if anything the existence of the Maybe and [] instances provides a strong reason *to* have the many/some methods inside Alternative, precisely because it gives us a customization point that allows us to make many and some provide well-defined answers for all values of these types. To quote Ross Paterson's proposals: instance Alternative Maybe where ... some Nothing = Nothing some (Just x) = Just (repeat x) many Nothing = Just [] many (Just x) = Just (repeat x) instance Alternative [] where ... some [] = [] some (x:xs) = repeat (repeat x) many [] = [[]] many (x:xs) = repeat (repeat x) The only price that we pay for these instances is that, while some and many are still solutions of • some v = (:) <$> v <*> many v • many v = some v <|> pure [] they no longer the *least* solutions of these equations. In my opinion this is a relatively small price to pay since they nonetheless *are* solutions to these questions, and they have the nice property that they converge sensibly. In fact, in a sense they are the least solutions to the equations that out of all the solutions that converge, though I don't know enough about the theory involved to use the proper technical terminology to express what I really mean, or even if what I just wrote was true. :-) Anyway, as the above discussion illustrates, the existence of pure types that are instances of Alternative actually *adds* to the case of keeping some and maybe in Alternative. So in conclusion: 1) Documentation really needs to be improved 2) some/many cannot be physically separated from Alternative, but there *might* be an advantage to creating a subclass for them anyway purely for the sake of conveying more information about a type to users 3) Maybe and [] are sensible instances of Alternative, even if many/some often enters an infinite loop. 4) It is possible to provide special instance of many/some that satisfy the equations of many/some, with the slight disadvantage that these solutions are no longer the "least" solutions. Based on all of this, at this moment in time it seems to me that the most sensible way forward is to fix the documentation, tweak the definition of Alternative to no longer require the least solutions of the equations, and then to adopt the new instances for Maybe and []. Thoughts? Cheers, Greg

On Thu, Dec 15, 2011 at 9:13 PM, Gregory Crosswhite
First of all, it sounds like we all agree that the documentation for Alternative needs to be improved; that alone would clear a lot of the confusion up.
I wonder if "fully documenting the Haskell base library" is a valid SoC project :)

On 15/12/2011, Gregory Crosswhite
1) Documentation really needs to be improved 2) some/many cannot be physically separated from Alternative, but there *might* be an advantage to creating a subclass for them anyway purely for the sake of conveying more information about a type to users 3) Maybe and [] are sensible instances of Alternative, even if many/some often enters an infinite loop. 4) It is possible to provide special instance of many/some that satisfy the equations of many/some, with the slight disadvantage that these solutions are no longer the "least" solutions.
Based on all of this, at this moment in time it seems to me that the most sensible way forward is to fix the documentation, tweak the definition of Alternative to no longer require the least solutions of the equations, and then to adopt the new instances for Maybe and [].
Thoughts?
(1) If we do (4), then the documentation ought to be adequate as-is. (2) In my opinion, no. If one is writing code polymorphic in (Alternative f => f), then one needn't worry. If one is using such code, then one ought to know whether some and many are sane for the types in question, anyhow (O_ō) (4) This is very reasonable; not the least solutions, but hey, they converge (^_^)
Cheers, Greg
Cheers, Matthew Farkas-Dyck

On Dec 17, 2011, at 12:35 PM, Matthew Farkas-Dyck wrote:
(1) If we do (4), then the documentation ought to be adequate as-is.
I see your point that if we do (4) then some and many are no longer problematic for Maybe and [], and thus we don't need warnings for those types. However, nonetheless we will *still* need *big warnings* *for the sake of others who write Alternative instances* for new types to make sure that these instances do not fall into the same trap as Maybe and []. That is, we want to let future authors of instances know about the conditions under which they will need to write their own versions of some and maybe in order to make sure that these methods have sensible behavior. In addition to this, we also really need some additional documentation explaining what the point of some and many are, since few people have any clue about them. :-) Finally, if we adopt (4) then we will need to change the documentation to remove "least" from "least solutions of the equations" since the phrase will no longer be correct. Better still, we could replace the phrase entirely with something like "least *converging* solutions of the equations". (*) Cheers, Greg (*) P.S: Dear people who are better at this kind of technical language than I: I am fully aware of the fact that the phrase "least converging solutions of the equations [...]" is sloppy wording at best and absolutely wrong at worst, but hopefully you should at least understand what I am *trying* to get at. Thus, I would welcome either your feedback on what it is that I am supposed to be thinking and saying, or an explanation about why the idea I am trying to conceive and convey is so intrinsically poorly formed that I am best off just giving up on it. ;-)

On 16/12/2011, Gregory Crosswhite
On Dec 17, 2011, at 12:35 PM, Matthew Farkas-Dyck wrote:
(1) If we do (4), then the documentation ought to be adequate as-is.
I see your point that if we do (4) then some and many are no longer problematic for Maybe and [], and thus we don't need warnings for those types. However, nonetheless we will *still* need *big warnings* *for the sake of others who write Alternative instances* for new types to make sure that these instances do not fall into the same trap as Maybe and []. That is, we want to let future authors of instances know about the conditions under which they will need to write their own versions of some and maybe in order to make sure that these methods have sensible behavior.
Finally, if we adopt (4) then we will need to change the documentation to remove "least" from "least solutions of the equations" since the phrase will no longer be correct. Better still, we could replace the phrase entirely with something like "least *converging* solutions of the equations". (*)
Ah, true. Sorry.
In addition to this, we also really need some additional documentation explaining what the point of some and many are, since few people have any clue about them. :-)
Myself, I think it's quite clear by the axioms given, but I certainly shan't grouch about more/better documentation.
Cheers, Greg
(*) P.S:
Dear people who are better at this kind of technical language than I:
I am fully aware of the fact that the phrase "least converging solutions of the equations [...]" is sloppy wording at best and absolutely wrong at worst, but hopefully you should at least understand what I am *trying* to get at. Thus, I would welcome either your feedback on what it is that I am supposed to be thinking and saying, or an explanation about why the idea I am trying to conceive and convey is so intrinsically poorly formed that I am best off just giving up on it. ;-)
Actually, now that I think of it, they are not, in general, the least converging solutions -- in the case of a parser, for example, (some (pure x)) would nevertheless diverge (I think). Perhaps "least sane solutions" (^_^) Cheers, Matthew Farkas-Dyck

On 17/12/2011, at 3:35 PM, Matthew Farkas-Dyck wrote:
On 15/12/2011, Gregory Crosswhite
wrote: 1) Documentation really needs to be improved 2) some/many cannot be physically separated from Alternative, but there *might* be an advantage to creating a subclass for them anyway purely for the sake of conveying more information about a type to users 3) Maybe and [] are sensible instances of Alternative, even if many/some often enters an infinite loop. 4) It is possible to provide special instance of many/some that satisfy the equations of many/some, with the slight disadvantage that these solutions are no longer the "least" solutions.
Based on all of this, at this moment in time it seems to me that the most sensible way forward is to fix the documentation, tweak the definition of Alternative to no longer require the least solutions of the equations, and then to adopt the new instances for Maybe and [].
Thoughts?
(1) If we do (4), then the documentation ought to be adequate as-is.
No. Not by a country mile. It's better than "non-existent". It's better than "misleading". But it's not even on the same *continent* as "adequate". A lot of Haskell packages have pretty much the same level of documentation. And I didn't pay one single cent for it, so I can't scream too loudly. But let's not kid ourselves.

On Sun, Dec 18, 2011 at 20:42, Richard O'Keefe
No. Not by a country mile. It's better than "non-existent". It's better than "misleading". But it's not even on the same *continent* as "adequate".
+1 -- brandon s allbery allbery.b@gmail.com wandering unix systems administrator (available) (412) 475-9364 vm/sms

On Dec 19, 2011, at 12:39 PM, Brandon Allbery wrote:
On Sun, Dec 18, 2011 at 20:42, Richard O'Keefe
wrote: No. Not by a country mile. It's better than "non-existent". It's better than "misleading". But it's not even on the same *continent* as "adequate". +1
So what do you all think about my own suggestion for the documentation? The following is the same as what I've posted before, but with some tweaks such as swapping the last two paragraphs. ============================================================ The Monoid instance for Maybe has the property that, for all x and y, (Just x) wins when combined (on either side) with Nothing values, and when (Just x) is combined with (Just y) then the result is (Just (x `mappend` y)). Note that the behavior of the Monoid instance of Maybe is *different* from the behavior of the MonadPlus and Alternative instance of Maybe. For the latter two typeclasses, the behavior is that when (Just x) is combined with (Just y) the x and y values themselves are not combined but rather y is discarded so (Just x) simply wins; put another way, for all x and z, we have that (Just x) `mappend` z is *always* equal to (Just x), regardless of whether z is equal to Nothing or whether it is equal to (Just y) for some y. For this reason, unlike the instance for Monoid, the instances for these MonadPlus and Alternative place no additional constraints on the type lifted into Maybe. Incidentally, for the more mathematically inclined, you may think of this as being equivalent to the standard practice of turning an arbitrary semigroup into a monoid by simply adding a new element to the semigroup to serve as the identity element, where in this case the identity element is the Nothing value of Maybe; unfortunately, since the base libraries do not come with a Semigroup typeclass, this process is expressed in code as lifting from the Monoid typeclass. ============================================================ I welcome any feedback that you all have to offer. If some iteration of the above is considered an improvement, then I would be happy to submit a patch using whatever process someone is kind enough to point me towards. :-) Cheers, Greg

On 19/12/2011, at 3:44 PM, Gregory Crosswhite wrote:
So what do you all think about my own suggestion for the documentation?
It is an improvement. Documentation for a library module needs to start by telling people what it is for. For a particular function, someone needs to know very quickly "is this what I am looking for? is this the kind of thing I _should_ have been looking for?" One important thing about the Monoid instance for Maybe is that There is more than one way to turn Maybe into a Monoid. One way treats Maybe a as a truncated [a] and does not depend on any properties of a, it takes mappend (Just x) _ = Just x The other requires a itself to be a Monoid, and lift's a's operations to Maybe a: mappend (Just x) (Just y) = mappend x y The latter, more interesting, case is the one implemented here. (In the same way, bounded integers like Int can be viewed as Monoids in at least 4 ways, only two of which are predefined in Data.Monoid. mempty = minBound mappend = max mempty = maxBound mappend = min are the other two. In fact these apply to anything that is Bounded and Ord.) The point is not that your proposed documentation doesn't say that, but it doesn't say that the MonadPlus reading is a *LEGITIMATE* way to view Maybe as a Monoid, which happens not to have been the one chosen; also that this possibility that the Monoid instance you WANT might not be the one you GET is to me the first thing you need to understand about it. Yes, there is a blanket warning about this, but it specifically mentions Num. Whenever it is possible for a reasonable person to want a Monoid instance and get one that is not the instance s/he wanted, it's worth highlighting in the docs.

On Dec 19, 2011, at 1:01 PM, Richard O'Keefe wrote:
On 19/12/2011, at 3:44 PM, Gregory Crosswhite wrote:
So what do you all think about my own suggestion for the documentation?
It is an improvement.
Documentation for a library module needs to start by telling people what it is for. For a particular function, someone needs to know very quickly "is this what I am looking for? is this the kind of thing I _should_ have been looking for?"
I agree, though really much of that kind of information should be in the Monoid typeclass rather than in the Maybe instance in particular.
The point is not that your proposed documentation doesn't say that, but it doesn't say that the MonadPlus reading is a *LEGITIMATE* way to view Maybe as a Monoid, which happens not to have been the one chosen; also that this possibility that the Monoid instance you WANT might not be the one you GET is to me the first thing you need to understand about it. Yes, there is a blanket warning about this, but it specifically mentions Num. Whenever it is possible for a reasonable person to want a Monoid instance and get one that is not the instance s/he wanted, it's worth highlighting in the docs.
I understand what you are getting at here, but the reason why think that the word "warning" needs to appear somewhere is to get users' attention long enough to let them know that this instance might break their expectations since it is inconsistent with MonadPlus and Alternative. Nonetheless, I agree that it is a good idea to let users know that the alternative behavior might be the most useful one in their own case, so how about the following (including changes listed in an earlier e-mail), which I will call Version 5: ================================================================ This instance satisfies the property that, for all x any y: (1) Nothing `mappend` Nothing = Nothing (2) Just x `mappend` Nothing = Just x (3) Nothing `mappend` Just y = Just y (4) Just x `mappend` Just y = Just (x `mappend` y) Put in formal terms, this instance performs the standard procedure of turning an arbitrary semigroup into a monoid by simply adding a new element to the semigroup to serve as the identity element, where in this case the identity element is the Nothing value of Maybe; unfortunately, since the base libraries do not come with a Semigroup typeclass, this process is expressed in code as lifting from the Monoid typeclass. CAVEAT: Note that rule (4) here is different from the case of the MonadPlus/Alternative instances where the Just y value is discarded so that Just x `mplus` Just y = Just x <|> Just y = Just x; if this is alternative behavior is what you were looking for, then try those typeclasses instead. ================================================================ Cheers, Greg

On Dec 19, 2011, at 1:01 PM, Richard O'Keefe wrote:
Documentation for a library module needs to start by telling people what it is for. For a particular function, someone needs to know very quickly "is this what I am looking for? is this the kind of thing I _should_ have been looking for?"
As I said before, some of this information really belongs in the Monoid typeclass itself, so here is my attempt at adding more information in this vein to the Monoid typeclass: ================================================================ The Monoid typeclass provides a standard interface for specifying how pairs of values of a given type can be combined to form new values of that type, as well well as an identity value for that type that when combined with any value x produces x. The Monoid class typically appears in higher-order functions that produce a list of values that need to be summarized into a single result, such as in Data.Foldable.foldMap function or the Writer monad. Formally, an instance of Monoid provides a binary associative operator with an identity element; to do this one must specify (at a minimum) the methods mempty and mappend such that they obey following properties: (*) mempty is the identity: mempty `mappend` x = x `mappend` mempty = x (*) mappend is associative: x `mappend` (y `mappend` z) = (x `mappend` y) `mappend` z Although not strictly necessary, for reasons of performance the Monoid typeclass also includes the method mconcat which combines all the elements in a list, i.e. it is a method which obeys the property (*) mconcat = foldr mappend mempty The above is the default definition of mconcat if no other is supplied, but for some times users may wish to override it when it can be performed more efficiently. Regardless, the minimal complete definition for an instance of the Monoid typeclass is mempty and mappend. For many types there are multiple equally sensible ways to combine pairs of values; for example, for the Int type one could use either addition or multiplication. In such cases where there is no single "natural" way to combine values, we often (though not always) define newtype wrappers for these types so that we can make it explicit which operation we are using. In the case of the Int type, for example, we define the Sum and Product newtypes and make these instances of Monoid using the corresponding mathematical operator. ================================================================ This additional information unfortunately makes the documentation more verbose, but the hope was to try to explain as much as possible the "whys" and "whens" of the Monoid class (to a non-mathematician audience) in addition to the "whats", since as you point out often the most important part of the documentation is where it explains why something exists and when you would need it. Cheers, Greg

On 19/12/2011, at 5:46 PM, Gregory Crosswhite wrote: [improved Monoid documentation] I would go so far as to point out that "mappend is a generalisation of Data.List.sum, Data.List.product, Data.List.and, and Data.List.or, where the initial value and combining rule are implied by the type.
This additional information unfortunately makes the documentation more verbose,
One man's "more verbose" is another man's "less cryptic". I really don't like the emphasis on Num, as if it was a bizarre feature of Num that there's more than one Monoid reading for it. This is a *common* property of data types. For example, Sets can be seen as monoids with empty and union; and Sets with a universe can also be seen as monoids with universe and intersection. The more I think about it, the less idea I have _what_ to expect for _any_ instance of Monoid.

On Dec 19, 2011, at 3:49 PM, Richard O'Keefe wrote:
On 19/12/2011, at 5:46 PM, Gregory Crosswhite wrote: [improved Monoid documentation]
Thank you. :-)
I would go so far as to point out that "mappend is a generalisation of Data.List.sum, Data.List.product, Data.List.and, and Data.List.or, where the initial value and combining rule are implied by the type.
Inspired by the idea behind your suggestion, I modified the documentation as follows: ======================================================== The Monoid typeclass provides a standard interface for specifying how pairs of values of a given type can be combined to form new values of that type, as well as an identity value for that type that when combined with any value x produces x. The Monoid class typically appears in higher-order functions that produce a list of values that need to be summarized into a single result, such as in Data.Foldable.foldMap function or the Writer monad. Formally, an instance of Monoid provides a binary associative operator with an identity element; to do this one must specify (at a minimum) the methods mempty and mappend such that they obey following properties: (*) mempty is the identity: mempty `mappend` x = x `mappend` mempty = x (*) mappend is associative: x `mappend` (y `mappend` z) = (x `mappend` y) `mappend` z Note that this structure is very generic; it includes addition with the identity element 0 (i.e. mappend = (+), mempty = 0), multiplication with the identity element 1 (i.e. mappend = (*), mempty = 1), list concatenation with the identity element [] (i.e. mappend = (++), mempty = []), logical and with the identity element True (i.e., mappend = (&&), mempty = True), logical or with the identity element False (i.e., mappend = (||), mempty = False), etc. Unfortunately, sometimes this very generality results in there being multiple equally sensible ways to define a Monoid instance for a type. For example, for numeric values addition and multiplication work equally well, and for boolean values logical and and logical or work equally well. In such cases, it is a good idea to define newtype wrappers for these types so that we can make it explicit which operation we are using. In the case of the Int type, for example, we define the Sum and Product newtypes and make these instances of Monoid using the corresponding mathematical operator; see also Any, All, First, and Last for other examples of this. Although not strictly necessary, for reasons of performance the Monoid typeclass also includes the method mconcat which combines all the elements in a list, i.e. it is a method which obeys the property (*) mconcat = foldr mappend mempty The above is the default definition of mconcat if no other is supplied, but for some times users may wish to override it when it can be performed more efficiently. Regardless, the minimal complete definition for an instance of the Monoid typeclass is mempty and mappend. ========================================================
This additional information unfortunately makes the documentation more verbose,
One man's "more verbose" is another man's "less cryptic".
Don't get me wrong, I completely agree with you that adding more words for the sake of making a subject less cryptic is a net win. :-) There are two dangers that lurk, however. First, there needs to be lots of that makes it easy for people to skim through and pick out the specific information that they want to find out about, and in particular the information that is most important/most urgently needed needs to be placed first so that it is the first thing that reader sees. Second, if you take too long to explain a point then you risk having your reader get fatigued so that all that effort you put in to make things clear just ends up getting going in one eye and out the other. :-)
I really don't like the emphasis on Num, as if it was a bizarre feature of Num that there's more than one Monoid reading for it. This is a *common* property of data types. For example, Sets can be seen as monoids with empty and union; and Sets with a universe can also be seen as monoids with universe and intersection.
In the revised version above, added Booleans as another example.
The more I think about it, the less idea I have _what_ to expect for _any_ instance of Monoid.
This is an inherent weakness of typeclasses, and why languages like Agda use record systems where instance declarations are records that you can either pass in explicitly or import explicitly to use implicitly within a particular scope. I think, though, that for many types, though, there really is a sort of "most intuitive"/"most natural" Monoid operation. For lists and sequences, for example, I think that the most intuitive operation is concatenation, rather than say taking the intersection of the elements of the two arguments. Likewise when you are accumulating over a bunch of sets of values you are probably more likely to be wanting the union of all the values you have seen so far than the intersection. Of course, such notions are ill-formed. :-) Cheers, Greg

On Dec 19, 2011, at 4:45 PM, Gregory Crosswhite wrote:
First, there needs to be lots of [STRUCTURE] that makes it easy for people to skim through and pick out the specific information that they want to find out about [...]
Grr! I have no idea why that word got dropped out, since it was kinda important... writing too many words at once puts my brain in a fog. :-) Also, just to clarify I don't necessarily mean structure as in explicit headlines so much as any kind of structure --- including implicit structure from paragraph breaks and careful choice of presentation and ordering --- that makes it easy to pick up on how a text is broken into logical parts, what each part is roughly about, and how the parts are related. Cheers, Greg

On Sun, Dec 18, 2011 at 6:44 PM, Gregory Crosswhite
On Dec 19, 2011, at 12:39 PM, Brandon Allbery wrote:
On Sun, Dec 18, 2011 at 20:42, Richard O'Keefe
wrote: No. Not by a country mile. It's better than "non-existent". It's better than "misleading". But it's not even on the same *continent* as "adequate".
+1
So what do you all think about my own suggestion for the documentation? The following is the same as what I've posted before, but with some tweaks such as swapping the last two paragraphs.
============================================================
The Monoid instance for Maybe has the property that, for all x and y, (Just x) wins when combined (on either side) with Nothing values, and when (Just x) is combined with (Just y) then the result is (Just (x `mappend` y)).
Note that the behavior of the Monoid instance of Maybe is *different* from the behavior of the MonadPlus and Alternative instance of Maybe. For the latter two typeclasses, the behavior is that when (Just x) is combined with (Just y) the x and y values themselves are not combined but rather y is discarded so (Just x) simply wins; put another way, for all x and z, we have that (Just x) `mappend` z is *always* equal to (Just x), regardless of whether z is equal to Nothing or whether it is equal to (Just y) for some y. For this reason, unlike the instance for Monoid, the instances for these MonadPlus and Alternative place no additional constraints on the type lifted into Maybe.
Incidentally, for the more mathematically inclined, you may think of this as being equivalent to the standard practice of turning an arbitrary semigroup into a monoid by simply adding a new element to the semigroup to serve as the identity element, where in this case the identity element is the Nothing value of Maybe; unfortunately, since the base libraries do not come with a Semigroup typeclass, this process is expressed in code as lifting from the Monoid typeclass.
============================================================
I welcome any feedback that you all have to offer. If some iteration of the above is considered an improvement, then I would be happy to submit a patch using whatever process someone is kind enough to point me towards. :-)
The "incidental" comment is significantly more clear than an English description. As somebody else has said in these threads, the problem is that syntactically equivalent but semantically distinct types have been collapsed into Maybe. That complicates the reading of the source code, since it is much harder to figure out which interpretation is intended, and so which theorems we get from the types. In other words, they are not free theorems (since those are true in any interpretation). We have to work for them. I would rather see commutative diagrams (or what amounts to the same, usage examples) that describe the behavior than a "plain English" description.

On Dec 19, 2011, at 1:03 PM, Alexander Solla wrote:
The "incidental" comment is significantly more clear than an English description.
That is only true for someone who has already seen a sentence like that one before and so can immediately pick up what it is getting at. :-) In particular, if one has never heard of a semigroup then the sentence is not very helpful.
I would rather see commutative diagrams (or what amounts to the same, usage examples) that describe the behavior than a "plain English" description.
I find it amusing that anyone would consider commutative diagram to be the same thing as usage examples for anyone other than a mathematician. :-) Nonetheless, I see your point that examples may be clearer than English, so how about: ================================================================ This instance satisfies the property that, for all x any y: (1) Nothing `mappend` Nothing = Nothing (2) Just x `mappend` Nothing = Just x (3) Nothing `mappend` Just y = Just y (4) Just x `mappend` Just y = Just (x `mappend` y) (Warning: Note that rule (4) for this instance is different from the case of the MonadPlus/Alternative instances where the Just y value is discarded so that Just x `mplus` Just y = Just x <|> Just y = Just x.) Formally, this instance performs the standard procedure of turning an arbitrary semigroup into a monoid by simply adding a new element to the semigroup to serve as the identity element, where in this case the identity element is the Nothing value of Maybe; unfortunately, since the base libraries do not come with a Semigroup typeclass, this process is expressed in code as lifting from the Monoid typeclass. ================================================================

On Thu, Dec 15, 2011 at 9:13 AM, Gregory Crosswhite
To quote Ross Paterson's proposals:
instance Alternative [] where ... some [] = [] some (x:xs) = repeat (repeat x)
many [] = [[]] many (x:xs) = repeat (repeat x)
Isn't this instance conflating the ZipList notion and the nondeterministic list notion?
• some v = (:) <$> v <*> many v • many v = some v <|> pure []
Is there a motivation for writing the second law like this and not like many v = pure [] <|> some v other than "parsers should try longest match first"? Because apart from that, I find the version with flipped arguments to <|> more natural (base case first). Incidentally, it would lead to terminating definitions of 'some' and 'many' for lists: ghci> take 5 . map (take 5) $ some [1,2] [[1],[1,1],[1,1,1],[1,1,1,1],[1,1,1,1,1]] ghci> take 5 . map (take 5) $ many [1,2] [[],[1],[1,1],[1,1,1],[1,1,1,1]] Sebastian
participants (7)
-
Alexander Solla
-
Brandon Allbery
-
Chris Wong
-
Gregory Crosswhite
-
Matthew Farkas-Dyck
-
Richard O'Keefe
-
Sebastian Fischer