Re: [GHC] #974: Add isLeft, isRight, fromLeft, fromRight, and splitEithers to Data.Either

ndmitchell:
Hi
#974: Add isLeft, isRight, fromLeft, fromRight, and splitEithers to Data.Either
Woohoo! Finally!
This proposal would add basic functionality to `Either` similar to that for `Maybe`. The `splitEithers` function of type `[Either a b] -> ([a],[b])` is unique; however, it seems to be a widely useful function.
This (in my mind) is a parallel to unzip? unzipEithers to me gives a much clearer picture of what is going on here.
yeah, if its an unzip, then unzipEithers makes more sense. -- Don

#974: Add isLeft, isRight, fromLeft, fromRight, and splitEithers to Data.Either
Woohoo! Finally!
I have a patch that was sumbitted using darcs send (as per the directions); however it is currently in limbo waiting for moderator approval. -- Russell O'Connor http://r6.ca/ ``All talk about `theft,''' the general counsel of the American Graphophone Company wrote, ``is the merest claptrap, for there exists no property in ideas musical, literary or artistic, except as defined by statute.''

This proposal would add basic functionality to `Either` similar to that for `Maybe`. The `splitEithers` function of type `[Either a b] -> ([a],[b])` is unique; however, it seems to be a widely useful function.
This (in my mind) is a parallel to unzip? unzipEithers to me gives a much clearer picture of what is going on here.
yeah, if its an unzip, then unzipEithers makes more sense.
The function strikes me as more like an instance of partition than unzip. I would be satisfied with either splitEithers, unzipEithers, or partitionEithers. My preferences are in that order (partitionEithers seems like an awfully long identifier). -- Russell O'Connor http://r6.ca/ ``All talk about `theft,''' the general counsel of the American Graphophone Company wrote, ``is the merest claptrap, for there exists no property in ideas musical, literary or artistic, except as defined by statute.''

I've removed the controvertial isLeft, fromLeft, isRight, fromRight from the trac, and added lefts and rights. The controvertial additions can be put in a new trac. Let us focus on the the noncontrovertial additions first. I've also renamed splitEithers into unzipEithers, which I think is better. A new patch is available on the trac: http://hackage.haskell.org/trac/ghc/ticket/974 -- Russell O'Connor http://r6.ca/ ``All talk about `theft,''' the general counsel of the American Graphophone Company wrote, ``is the merest claptrap, for there exists no property in ideas musical, literary or artistic, except as defined by statute.''

On Wed, 1 Nov 2006 roconnor@theorem.ca wrote:
I've removed the controvertial isLeft, fromLeft, isRight, fromRight from the trac, and added lefts and rights. The controvertial additions can be put in a new trac. Let us focus on the the noncontrovertial additions first.
I've also renamed splitEithers into unzipEithers, which I think is better.
What was the reason against 'partitionEither' ? 'unzip' suggests there is also a 'zip'.

On Wed, 1 Nov 2006, Henning Thielemann wrote:
On Wed, 1 Nov 2006 roconnor@theorem.ca wrote:
I've removed the controvertial isLeft, fromLeft, isRight, fromRight from the trac, and added lefts and rights. The controvertial additions can be put in a new trac. Let us focus on the the noncontrovertial additions first.
I've also renamed splitEithers into unzipEithers, which I think is better.
What was the reason against 'partitionEither' ? 'unzip' suggests there is also a 'zip'.
I thought partitionEithers was a bit long for an identifier. (What is the distribution for lengths of identifieres in the standard library?) However I would agree with partitionEithers if that is what people want. -- Russell O'Connor http://r6.ca/ ``All talk about `theft,''' the general counsel of the American Graphophone Company wrote, ``is the merest claptrap, for there exists no property in ideas musical, literary or artistic, except as defined by statute.''

Hi
What is the distribution for lengths of identifieres in the standard library?
http://www-users.cs.york.ac.uk/~ndm/temp/identifier_length.png Uses up the Y, length on the X. Thanks Neil

Hi
http://www-users.cs.york.ac.uk/~ndm/temp/identifier_length.png
Uses up the Y, length on the X.
Since roconnor asked, here is the raw data: 1 4 2 49 3 135 4 272 5 337 6 452 7 381 8 399 9 362 10 325 11 308 12 252 13 209 14 178 15 140 16 88 17 67 18 64 19 67 20 42 21 39 22 34 23 34 24 23 25 35 26 16 27 18 28 11 29 10 30 1 31 4 32 2 34 1 Thanks Neil

It appears that 95% of identifiers are between 2 and 21 (inclusive) characters long. So partitionEithers is not unusually long according to this metric. -- Russell O'Connor http://r6.ca/ ``All talk about `theft,''' the general counsel of the American Graphophone Company wrote, ``is the merest claptrap, for there exists no property in ideas musical, literary or artistic, except as defined by statute.''

On Wed, 1 Nov 2006, Henning Thielemann wrote:
On Wed, 1 Nov 2006 roconnor@theorem.ca wrote:
I've removed the controvertial isLeft, fromLeft, isRight, fromRight from the trac, and added lefts and rights. The controvertial additions can be put in a new trac. Let us focus on the the noncontrovertial additions first.
I've also renamed splitEithers into unzipEithers, which I think is better.
What was the reason against 'partitionEither' ? 'unzip' suggests there is also a 'zip'.
I have attached a new patch to the trac that now uses the identifier partitionEithers. -- Russell O'Connor http://r6.ca/ ``All talk about `theft,''' the general counsel of the American Graphophone Company wrote, ``is the merest claptrap, for there exists no property in ideas musical, literary or artistic, except as defined by statute.''

On Fri, 3 Nov 2006 roconnor@theorem.ca wrote:
On Wed, 1 Nov 2006, Henning Thielemann wrote:
On Wed, 1 Nov 2006 roconnor@theorem.ca wrote:
I've removed the controvertial isLeft, fromLeft, isRight, fromRight from the trac, and added lefts and rights. The controvertial additions can be put in a new trac. Let us focus on the the noncontrovertial additions first.
I've also renamed splitEithers into unzipEithers, which I think is better.
What was the reason against 'partitionEither' ? 'unzip' suggests there is also a 'zip'.
I have attached a new patch to the trac that now uses the identifier partitionEithers.
Sorry for being so inconstant. The more I thought about it, I found that unzipEither is the better choice. Since 'partition' takes a function, which decides, where an element should go, 'partitionEither' should also get such an argument: partitionEither :: (a -> Either b c) -> [a] -> ([b], [c]) partitionEither f = unzipEither . map f unzipEither :: [Either b c] -> ([b], [c]) I can imagine a 'zipEither' zipEither :: [Bool] -> [b] -> [c] -> [Either b c] zipEither = zipWith3 (\l r -> bool (Left l) (Right r)) with the recently proposed if-then-else replacement 'bool' http://www.haskell.org/pipermail/haskell-prime/2006-October/001803.html but maybe it is too simple, in order to be added to Data.Either. Analogously I suggest partitionMaybe :: (a -> Maybe b) -> [a] -> ([a], [b]) or partitionMaybe :: (a -> Maybe b) -> [a] -> ([b], [a]) where the parameter order of the second function is closer to 'partition' and is suitable for use in the State monad. A similar naming question arose with respect to Data.Map functions recently: http://www.haskell.org/pipermail/libraries/2006-August/005667.html

On Fri, Nov 03, 2006 at 09:57:35AM -0500, roconnor@theorem.ca wrote:
I have attached a new patch to the trac that now uses the identifier partitionEithers.
I'd suggest also having the following variant, by analogy with mapMaybe: -- | Map values and separate the 'Left' and 'Right' results. mapEither :: (a -> Either b c) -> [a] -> ([b], [c]) mapEither f = foldr (add . f) ([], []) where add (Left b) (bs, cs) = (b:bs, cs) add (Right c) (bs, cs) = (bs, c:cs)

On Thu, 9 Nov 2006, Ross Paterson wrote:
On Fri, Nov 03, 2006 at 09:57:35AM -0500, roconnor@theorem.ca wrote:
I have attached a new patch to the trac that now uses the identifier partitionEithers.
I'd suggest also having the following variant, by analogy with mapMaybe:
-- | Map values and separate the 'Left' and 'Right' results. mapEither :: (a -> Either b c) -> [a] -> ([b], [c]) mapEither f = foldr (add . f) ([], []) where add (Left b) (bs, cs) = (b:bs, cs) add (Right c) (bs, cs) = (bs, c:cs)
After my turnaround http://www.haskell.org/pipermail/libraries/2006-November/006204.html that's what I called partitionEither. From a 'map' function I expect a similarity to 'fmap', e.g. that the main input and the output have the same type constructor (here []).

On Thu, Nov 09, 2006 at 04:29:09PM +0100, Henning Thielemann wrote:
On Thu, 9 Nov 2006, Ross Paterson wrote:
I'd suggest also having the following variant, by analogy with mapMaybe:
-- | Map values and separate the 'Left' and 'Right' results. mapEither :: (a -> Either b c) -> [a] -> ([b], [c]) mapEither f = foldr (add . f) ([], []) where add (Left b) (bs, cs) = (b:bs, cs) add (Right c) (bs, cs) = (bs, c:cs)
After my turnaround http://www.haskell.org/pipermail/libraries/2006-November/006204.html that's what I called partitionEither. From a 'map' function I expect a similarity to 'fmap', e.g. that the main input and the output have the same type constructor (here []).
As I said before, it's a bit of both map and partition, in the same way that mapMaybe combines map and filter. But mapMaybe is already there, and this naming follows it.

On Thu, 9 Nov 2006, Ross Paterson wrote:
On Thu, Nov 09, 2006 at 04:29:09PM +0100, Henning Thielemann wrote:
On Thu, 9 Nov 2006, Ross Paterson wrote:
I'd suggest also having the following variant, by analogy with mapMaybe:
-- | Map values and separate the 'Left' and 'Right' results. mapEither :: (a -> Either b c) -> [a] -> ([b], [c]) mapEither f = foldr (add . f) ([], []) where add (Left b) (bs, cs) = (b:bs, cs) add (Right c) (bs, cs) = (bs, c:cs)
After my turnaround http://www.haskell.org/pipermail/libraries/2006-November/006204.html that's what I called partitionEither. From a 'map' function I expect a similarity to 'fmap', e.g. that the main input and the output have the same type constructor (here []).
As I said before, it's a bit of both map and partition, in the same way that mapMaybe combines map and filter. But mapMaybe is already there, and this naming follows it.
I can write mapMaybe f . mapMaybe g but not mapEither f . mapEither g that's why I think, this kind of mapEither is not as much 'map' as 'mapMaybe' is. :-)

Everyone seems satified with the name unzipEithers. There have been suggestions for partitionEither :: (a -> Either b c) -> [a] -> ([b], [c]) but I suggest they be pursued in a different trac. I suggest accepting the patch (not that I have any authority) on Nov. 17 if there are no further comments. -- Russell O'Connor http://r6.ca/ ``All talk about `theft,''' the general counsel of the American Graphophone Company wrote, ``is the merest claptrap, for there exists no property in ideas musical, literary or artistic, except as defined by statute.''

Hi
I suggest accepting the patch (not that I have any authority) on Nov. 17 if there are no further comments.
My only comment would be that you have thrown away the best part of this patch (fromLeft, fromRight, isLeft, isRight) without putting up enough of a fight! It's a real shame to loose the best bits of this patch, without already starting up the next discussion on how to get those in. So can I suggest that you keep this patch on with the Nov 17 deadline, but start up a new discussion right now about including the others. My worry is they'll be silently dropped never to return... Thanks Neil

Hello roconnor, Sunday, November 12, 2006, 7:40:19 PM, you wrote:
Everyone seems satified with the name unzipEithers. There have been suggestions for
partitionEither :: (a -> Either b c) -> [a] -> ([b], [c])
i prefer name splitEithers. for me, unzipping is process of splitting list of (a,b) values into the list of 'a' values and list of 'b' values - just like unzipping in real life. this don't have anything common with the algorithm of this function disclaimer: i'm not native English speaker, so my language understanding may be just wrong -- Best regards, Bulat mailto:Bulat.Ziganshin@gmail.com

On Mon, 13 Nov 2006, Bulat Ziganshin wrote:
i prefer name splitEithers. for me, unzipping is process of splitting list of (a,b) values into the list of 'a' values and list of 'b' values - just like unzipping in real life. this don't have anything common with the algorithm of this function
The concern I have with split is that almost all the other split functions work by taking an ordered container and returning two containers where everything in the first container preceeds everything in the second container. unzipEithers doesn't have this property. However unzipEithers is a process of splitting a list of Either a b values into a list of 'a' values and a list of 'b' values, similar to the unzip function. -- Russell O'Connor http://r6.ca/ ``All talk about `theft,''' the general counsel of the American Graphophone Company wrote, ``is the merest claptrap, for there exists no property in ideas musical, literary or artistic, except as defined by statute.''

On 2006-11-13, roconnor@theorem.ca
On Mon, 13 Nov 2006, Bulat Ziganshin wrote:
i prefer name splitEithers. for me, unzipping is process of splitting list of (a,b) values into the list of 'a' values and list of 'b' values - just like unzipping in real life. this don't have anything common with the algorithm of this function
The concern I have with split is that almost all the other split functions work by taking an ordered container and returning two containers where everything in the first container preceeds everything in the second container. unzipEithers doesn't have this property. However unzipEithers is a process of splitting a list of Either a b values into a list of 'a' values and a list of 'b' values, similar to the unzip function.
Unzip is reversible though. The order is preserved, and (uncurry zip) . unzip = id = unzip . (uncurry zip) There is no "zipEithers" that is any sort of reverse. While I understand what is meant by unzipEithers, I think that I too would prefer split, break, extract, partition, or similar. If we think of lazy stream processing, it's a type of sorting fork or railway switch. Hmm. (,) is the generic product, and Either is the generic coproduct. counzip? -- Aaron Denney -><-

Aaron Denney wrote:
On 2006-11-13, roconnor@theorem.ca
wrote: On Mon, 13 Nov 2006, Bulat Ziganshin wrote:
i prefer name splitEithers. [...]
[...]
Unzip is reversible though. The order is preserved, and (uncurry zip) . unzip = id = unzip . (uncurry zip) There is no "zipEithers" that is any sort of reverse.
Only one-sided, of course: splitEithers . (\ (xs, ys) -> map Left xs ++ map Right ys) = id
Hmm. (,) is the generic product, and Either is the generic coproduct. counzip?
Or, better even, ``cozip'' ;-) (I couldn't resist...) (uncurry zip) :: ([a],[b]) -> [a * b] / / / / / / / / / / cozip :: [a + b] -> ([a],[b]) ;-) Wolfram P.S.: I currently have: eitherList :: [Either a b] -> ([a], [b]) eitherPair2 :: (a, Either b c) -> Either (a,b) (a,c) eitherMap :: (a -> c) -> (b -> d) -> Either a b -> Either c d

How about the name separateEithers : [Either a b] -> ([a],[b]) I mean the verb not the adjective. :/ -- Russell O'Connor http://r6.ca/ ``All talk about `theft,''' the general counsel of the American Graphophone Company wrote, ``is the merest claptrap, for there exists no property in ideas musical, literary or artistic, except as defined by statute.''

On Mon, 13 Nov 2006, roconnor@theorem.ca wrote:
How about the name
separateEithers : [Either a b] -> ([a],[b])
I mean the verb not the adjective. :/
I have also anonymously received the suggestion of demux :: [Either a b] -> ([a],[b]) -- Russell O'Connor http://r6.ca/ ``All talk about `theft,''' the general counsel of the American Graphophone Company wrote, ``is the merest claptrap, for there exists no property in ideas musical, literary or artistic, except as defined by statute.''

On 11/14/06, roconnor@theorem.ca
I have also anonymously received the suggestion of
demux :: [Either a b] -> ([a],[b])
Nice name, but it invites namespace collision again.
--
Taral

On 2006-11-14, roconnor@theorem.ca
I have also anonymously received the suggestion of
demux :: [Either a b] -> ([a],[b])
That's not too bad. A bit general of name though, if we're concerned about namespace pollution. -- Aaron Denney -><-

How about the name
separateEithers : [Either a b] -> ([a],[b])
So far this is appears to be the least objectional name for this function. Are there any further concerns about using this name?

On Sun, Nov 12, 2006 at 11:40:19AM -0500, roconnor@theorem.ca wrote:
Everyone seems satified with the name unzipEithers. There have been suggestions for
partitionEither :: (a -> Either b c) -> [a] -> ([b], [c])
but I suggest they be pursued in a different trac.
I think it makes sense to consider them together, as these functions are closely related, the only concerns anyone has raised about them relate to names, and they're competing for the same part of the namespace. Apropos of that, I'm convinced by Henning's argument against the name mapEither (that you can't compose them). I'm not sure about unzip, but I agree there are too many split's.

On Mon, 13 Nov 2006, Ross Paterson wrote:
On Sun, Nov 12, 2006 at 11:40:19AM -0500, roconnor@theorem.ca wrote:
Everyone seems satified with the name unzipEithers. There have been suggestions for
partitionEither :: (a -> Either b c) -> [a] -> ([b], [c])
but I suggest they be pursued in a different trac.
I think it makes sense to consider them together, as these functions are closely related, the only concerns anyone has raised about them relate to names, and they're competing for the same part of the namespace.
But is this function (a -> Either b c) -> [a] -> ([b],[c]) defined by anyone and/or used anywhere? If not, is there any evidence that people will use this function in the future if it is added? My reason for adding [Either a b] -> ([a],[b]) is that at least two independent projects from independent authors use it and it seems generally widely useful. Althought techinically I don't have the same evidence for lefts and rights, I believe such evidence exists. At least one instance is for specifying the behaviour of unzipEithers, which is why I include it in the same patch. However I'm not convinced that there is demand fur the (a -> Either b c) -> [a] -> ([b],[c]) function. This is my concern. Since no one is suggesting the name of partitionEithers for the [Either a b] -> ([a],[b]) function anymore, there is currently no name space dispute. For these reasons, I suggest (a -> Either b c) -> [a] -> ([b],[c]) be pursued in another trac. -- Russell O'Connor http://r6.ca/ ``All talk about `theft,''' the general counsel of the American Graphophone Company wrote, ``is the merest claptrap, for there exists no property in ideas musical, literary or artistic, except as defined by statute.''

On 2006-11-13, roconnor@theorem.ca
My reason for adding [Either a b] -> ([a],[b]) is that at least two independent projects from independent authors use it and it seems generally widely useful. Althought techinically I don't have the same evidence for lefts and rights, I believe such evidence exists. At least one instance is for specifying the behaviour of unzipEithers, which is why I include it in the same patch.
Well since f x = (lefts x, rights x), why not name f "leftsAndRights", or "boths", or some such? -- Aaron Denney -><-

I think that the type of lefts and rights should be generalized to lefts :: (MonadPlus m) => m (Either a b) -> m a rights :: (MonadPlus m) => m (Either a b) -> m b Any concerns about this? Are the names still acceptable? -- Russell O'Connor http://r6.ca/ ``All talk about `theft,''' the general counsel of the American Graphophone Company wrote, ``is the merest claptrap, for there exists no property in ideas musical, literary or artistic, except as defined by statute.''

Hi
I think that the type of lefts and rights should be generalized to
lefts :: (MonadPlus m) => m (Either a b) -> m a rights :: (MonadPlus m) => m (Either a b) -> m b
Any concerns about this? Are the names still acceptable?
I think the original one was much much clearer.... Now you have to know that list is an instance of MonadPlus, and have to understand higher kinded type classes, just to grab the left things out of a list. Thanks Neil
participants (10)
-
Aaron Denney
-
Bulat Ziganshin
-
dons@cse.unsw.edu.au
-
Henning Thielemann
-
kahl@cas.mcmaster.ca
-
Neil Mitchell
-
roconnor@theorem.ca
-
Ross Paterson
-
Russell O'Connor
-
Taral