
The function on defined by (*) `on` f = \x y -> f x * f y is convenient when using functions like sortBy: sortBy (compare `on` fst), for example. It also makes the code more readable. Furthermore I consider on to be above the Fairbairn threshold, since * we get rid of two lambdas, * we get rid of the duplication of p, * on has some nice algebraic properties (documented in the patch) * and, most importantly, it is easier at a glance to understand (*) `on` p than to understand \x y -> p x * p y (assuming one knows about on). The main question seems to be which module to put the function in. Based on previous discussion on the libraries list I suggest creating a new module Control.Function containing on plus (initially) some other combinators (working solely on and with functions) from the Prelude. Deadline for discussion: 2006-11-09. Trac ticket number: 979. -- /NAD

Nils Anders Danielsson
(*) `on` f = \x y -> f x * f y
The main question seems to be which module to put the function in. Based on previous discussion on the libraries list I suggest creating a new module Control.Function containing on plus (initially) some other combinators (working solely on and with functions) from the Prelude.
I support the addition of `on`. I also agree it should be placed with other combinators that operate purely on functions. However, the "Control." hierarchy is certainly the wrong place for it. The very name Control is intended to suggest things that are slightly outside the usual functional domain - more in the region of imperative control structures. Here are some alternative suggestions: Data.Function Data.Functional Prelude.Functional Function.Combinators Prelude.Combinators Regards, Malcolm

On Thu, 02 Nov 2006, Malcolm Wallace
However, the "Control." hierarchy is certainly the wrong place for it. The very name Control is intended to suggest things that are slightly outside the usual functional domain - more in the region of imperative control structures.
In that case, why do we have Control.Applicative, Control.Arrow etc., which are purely functional? The only non-functional libraries are those that involve the IO or ST monads (Control.Concurrent, Control.Exception, Control.Monad.ST, etc.). Personally I prefer Data.Function (to match Data.Tuple, etc.), but it doesn't really seem to match the current division between Data and Control. Many nice little combinators (like (&&&) and (***)) can be found in Control.Arrow, for instance. -- /NAD

Nils Anders Danielsson
However, the "Control." hierarchy is certainly the wrong place for it. The very name Control is intended to suggest things that are slightly outside the usual functional domain - more in the region of imperative control structures.
In that case, why do we have Control.Applicative, Control.Arrow etc., which are purely functional? The only non-functional libraries are those that involve the IO or ST monads (Control.Concurrent, Control.Exception, Control.Monad.ST, etc.).
Well, since I was responsible for the original classification of Control.Monad into the Control hierarchy, I suppose it is all my fault. Monads are of course purely functional too. However, like concurrency and exceptions, at the time they had the "feel" of imperative programming, especially given the sugar of "do" notation. I certainly don't think of the monad concept as being a mere data structure, which is why it does not live in Data.Monad, but as something rather bigger in scope, involving sequence and so on. I'm not totally sure why Applicative has ended up in Control, but arrows are often thought of as "like Monads, only more general", so that would be why Control.Arrow is alongside Control.Monad. I'm not sure that there is a good word to describe all these such things that are more structured than mere data. Perhaps they should really live in a "Category." hierarchy, or "Idiom." (not to be confused with Conor's use of the term), or "Abstract." ? Regards, Malcolm

Hello Malcolm, Thursday, November 2, 2006, 9:00:00 PM, you wrote:
Control.Arrow is alongside Control.Monad.
I'm not sure that there is a good word to describe all these such things that are more structured than mere data. Perhaps they should really live in a "Category." hierarchy, or "Idiom." (not to be confused with Conor's use of the term), or "Abstract." ?
perhaps Monsters.* ? -- Best regards, Bulat mailto:Bulat.Ziganshin@gmail.com

Bulat Ziganshin wrote:
Hello Malcolm,
Thursday, November 2, 2006, 9:00:00 PM, you wrote:
Control.Arrow is alongside Control.Monad.
I'm not sure that there is a good word to describe all these such things that are more structured than mere data. Perhaps they should really live in a "Category." hierarchy, or "Idiom." (not to be confused with Conor's use of the term), or "Abstract." ?
perhaps Monsters.* ?
My favourite suggestion so far, thankyou Bulat :-D

Hello Malcolm, Thursday, November 2, 2006, 8:18:25 PM, you wrote:
(*) `on` f = \x y -> f x * f y
Here are some alternative suggestions:
Data.Function Data.Functional Prelude.Functional Function.Combinators Prelude.Combinators
also Data.Combinators -- Best regards, Bulat mailto:Bulat.Ziganshin@gmail.com

On Fri, 3 Nov 2006, Bulat Ziganshin wrote:
Hello Malcolm,
Thursday, November 2, 2006, 8:18:25 PM, you wrote:
(*) `on` f = \x y -> f x * f y
Here are some alternative suggestions:
Data.Function Data.Functional Prelude.Functional Function.Combinators Prelude.Combinators
also Data.Combinators
singular Function.Combinator Prelude.Combinator Data.Combinator ?

Hi
also Data.Combinators
Combinators "combine things" - depending on your exact definition of combinators pretty much anything can be a "combinator". My System.FilePath has been called a combinator library by some people. I'd rather avoid terms like Combinator (and Idiom, unless in the very specific sense of Connor's work) which tend to increase in scope as time goes by. Data.Function seems a much more appropriate place, or perhaps just Function on its own. (Maybe we need a Function.* heirarchy?) Thanks Neil

On Thu, 02 Nov 2006, Malcolm Wallace
However, the "Control." hierarchy is certainly the wrong place for it. [...] Here are some alternative suggestions:
Data.Function [...]
Data.Function has been suggested by a lot of people, so I suggest that we go with that. I've updated the patch. (Not the proposal though, since I couldn't edit it, presumably since I haven't bothered to register.) -- /NAD

Nils Anders Danielsson
The function on defined by
(*) `on` f = \x y -> f x * f y
[...]
The main question seems to be which module to put the function in. Based on previous discussion on the libraries list I suggest creating a new module Control.Function
Functional programming means functions are first class citizens, and that means that function types are data types just like other data types. In addition, function application by itself does not influence control flow. Therefore I would strongly suggest Data.Function instead. Wolfram

I agree it should go in. I wonder about how this relates to 'comparing' which we already have in Data.Ord. Does adding 'on' mean we should remove 'comparing' ? I would suggest we keep both and add 'equating' to Data.Eq too, for symmetry with 'comparing'. Why? Because for the cases covered by comparing/equating I think the code feel simpler and reads more naturally. In my own code I think I would use comparing/equating when using the ordinary Ord/Eq instances and use `on` when I was using a non-standard comparison. Duncan On Thu, 2006-11-02 at 18:00 +0100, Nils Anders Danielsson wrote:
The function on defined by
(*) `on` f = \x y -> f x * f y
is convenient when using functions like sortBy: sortBy (compare `on` fst), for example. It also makes the code more readable.
Furthermore I consider on to be above the Fairbairn threshold, since * we get rid of two lambdas, * we get rid of the duplication of p, * on has some nice algebraic properties (documented in the patch) * and, most importantly, it is easier at a glance to understand (*) `on` p than to understand \x y -> p x * p y (assuming one knows about on).

Since Data.Ord and Data.Eq now have there on modules and are part of the prelude, I suggest to create Data.Function and put in "flip", "id", "const" (did I forget one?) and "on". The prelude need/should not reexport "on", though. 1. I agree to have comparing and equating separately (however implemented) 2. Data.Function seems right to me, too (because "Data.->" is illegal as module identifier) Christian Duncan Coutts schrieb:
I agree it should go in.
I wonder about how this relates to 'comparing' which we already have in Data.Ord. Does adding 'on' mean we should remove 'comparing' ?
I would suggest we keep both and add 'equating' to Data.Eq too, for symmetry with 'comparing'.
Why? Because for the cases covered by comparing/equating I think the code feel simpler and reads more naturally.
In my own code I think I would use comparing/equating when using the ordinary Ord/Eq instances and use `on` when I was using a non-standard comparison.
Duncan
On Thu, 2006-11-02 at 18:00 +0100, Nils Anders Danielsson wrote:
The function on defined by
(*) `on` f = \x y -> f x * f y
is convenient when using functions like sortBy: sortBy (compare `on` fst), for example. It also makes the code more readable.
Furthermore I consider on to be above the Fairbairn threshold, since * we get rid of two lambdas, * we get rid of the duplication of p, * on has some nice algebraic properties (documented in the patch) * and, most importantly, it is easier at a glance to understand (*) `on` p than to understand \x y -> p x * p y (assuming one knows about on).

On Fri, 03 Nov 2006, Christian Maeder
Since Data.Ord and Data.Eq now have there on modules and are part of the prelude, I suggest to create Data.Function and put in "flip", "id", "const" (did I forget one?) and "on".
You forgot (.) and ($), which are already included. I didn't include seq, ($!) or asTypeOf. -- /NAD

Nils Anders Danielsson schrieb:
On Fri, 03 Nov 2006, Christian Maeder
wrote: Since Data.Ord and Data.Eq now have there on modules and are part of the prelude, I suggest to create Data.Function and put in "flip", "id", "const" (did I forget one?) and "on".
You forgot (.) and ($), which are already included.
Right, although I did look into your code I overlooked your re-export, because I expected the implementation of these function to be in the module whereas the prelude should re-export parts of it (Data.Function). However, the "true origin" of a function does not seem to matter and I don't know if Data.Ord re-exports parts of the Prelude or vice versa.
I didn't include seq, ($!) or asTypeOf.
Good, Christian

On 11/3/06, Christian Maeder
2. Data.Function seems right to me, too (because "Data.->" is illegal as module identifier)
This really doesn't sit right with me. Functions may be first-class,
but they're not just data.
--
Taral

Hello Duncan, Friday, November 3, 2006, 1:21:13 AM, you wrote:
I wonder about how this relates to 'comparing' which we already have in Data.Ord. Does adding 'on' mean we should remove 'comparing' ?
I would suggest we keep both and add 'equating' to Data.Eq too, for symmetry with 'comparing'.
i greatly support this idea. otherwise, we will make laguage understandable only by postgraduates. we shouldn't remove simple features from the libs only because there more complex ways to do the same. as far as it is easier to understand/has a lot of uses, simple feature should exist with their generalizations -- Best regards, Bulat mailto:Bulat.Ziganshin@gmail.com

On Thu, 02 Nov 2006, Duncan Coutts
I wonder about how this relates to 'comparing' which we already have in Data.Ord. Does adding 'on' mean we should remove 'comparing' ?
I would suggest we keep both and add 'equating' to Data.Eq too, for symmetry with 'comparing'.
I think it's just as easy to understand (compare `on` f) as (comparing f), so having both just adds extra complexity. Hence I place comparing _under_ the Fairbairn threshold. My patch adds documentation to Data.List pointing to on, by the way. -- /NAD

On Fri, 2006-11-03 at 13:23 +0100, Nils Anders Danielsson wrote:
On Thu, 02 Nov 2006, Duncan Coutts
wrote: I wonder about how this relates to 'comparing' which we already have in Data.Ord. Does adding 'on' mean we should remove 'comparing' ?
I would suggest we keep both and add 'equating' to Data.Eq too, for symmetry with 'comparing'.
I think it's just as easy to understand (compare `on` f) as (comparing f), so having both just adds extra complexity. Hence I place comparing _under_ the Fairbairn threshold.
groupBy ((==) `on` fst) vs groupBy (equating fst) well, I disagree. Yes it's a special case, but I would use it in the common special case and use `on` in the rarer general case. But no matter. So do you suggest that we deprecate and remove comparing? Or do you think we should have comparing but not equating, leaving it asymmetric and just claim that comparing was added too soon but couldn't be removed? If the latter then perhaps you want to add a comment to the comparing docs: Don't use @comparing foo@, use @compare `on` foo@. Duncan

Hello Duncan, Friday, November 3, 2006, 4:42:27 PM, you wrote:
groupBy ((==) `on` fst) vs groupBy (equating fst)
groupOn fst sortOn snd -- |Sort list by function result (use Schwarznegian transform) sortOn f = map snd . sortOn' fst . map (keyval f) -- |Sort list by function result (don't use Schwarznegian transform!) sortOn' f = sortBy (map2cmp f) -- |Group list by function result groupOn f = groupBy (map2eq f) -- |Sort and Group list by function result sort_and_groupOn f = groupOn f . sortOn f sort_and_groupOn' f = groupOn f . sortOn' f -- |Check that all adjacent values in the list meets given criteria isAll f [] = True isAll f [x] = True isAll f (x:y:ys) = f x y && isAll f (y:ys) -- |Check that list is sorted by given field/critery isSortedOn f = isAll (<=) . map f -- |Check that all elements in list are equal by given field/critery isEqOn f = isAll (==) . map f -- Utility functions for list operations keyval f x = (f x, x) -- |Return pair containing computed key and original value map2cmp f x y = (f x) `compare` (f y) -- |Converts "key_func" to "compare_func" map2eq f x y = (f x) == (f y) -- |Converts "key_func" to "eq_func" while we are here, i also propose to export from Data.List 'merge' function that is useful on its own -- Best regards, Bulat mailto:Bulat.Ziganshin@gmail.com

On Nov 3, 2006, at 11:58 AM, Bulat Ziganshin wrote:
while we are here, i also propose to export from Data.List 'merge' function that is useful on its own
Yes, please. This qualifies as my most commonly rewritten multi-line Haskell function. That said, I've also written most of the variations of merge you might care to imagine (indeed, sorted-list sets and multisets together use pretty much all of them if you include difference and merging of equals). -Jan-Willem Maessen
-- Best regards, Bulat mailto:Bulat.Ziganshin@gmail.com
_______________________________________________ Libraries mailing list Libraries@haskell.org http://www.haskell.org/mailman/listinfo/libraries

On Sat, 2006-11-04 at 21:25 -0500, Jan-Willem Maessen wrote:
On Nov 3, 2006, at 11:58 AM, Bulat Ziganshin wrote:
while we are here, i also propose to export from Data.List 'merge' function that is useful on its own
Yes, please. This qualifies as my most commonly rewritten multi-line Haskell function.
That said, I've also written most of the variations of merge you might care to imagine (indeed, sorted-list sets and multisets together use pretty much all of them if you include difference and merging of equals).
Yes, there are a number of different options for what we might call 'merge'. It would be good to discuss what the variations are and which variations might be sensible to include in a standard lib and what they might be called. However I think this is a separate issue from the discussion about 'on'. So start a new thread and lets try and find out if there is a consensus. As an example variation from a program I wrote: -- mergeBy cmp xs ys = (only_in_xs, in_both, only_in_ys) mergeBy :: (a -> b -> Ordering) -> [a] -> [b] -> ([a], [(a, b)], [b]) mergeBy cmp = merge [] [] [] where merge l m r [] ys = (reverse l, reverse m, reverse (ys++r)) merge l m r xs [] = (reverse (xs++l), reverse m, reverse r) merge l m r (x:xs) (y:ys) = case x `cmp` y of GT -> merge l m (y:r) (x:xs) ys EQ -> merge l ((x,y):m) r xs ys LT -> merge (x:l) m r xs (y:ys) It's rare of course that you need the generality of merging lists of different types. Though of course this also covers the slightly more common case of comparing where == is only an equivalence relation and you want to keep or combine both elements. Duncan

Duncan Coutts schrieb:
So start a new thread and lets try and find out if there is a consensus.
As an example variation from a program I wrote:
-- mergeBy cmp xs ys = (only_in_xs, in_both, only_in_ys)
mergeBy :: (a -> b -> Ordering) -> [a] -> [b] -> ([a], [(a, b)], [b]) mergeBy cmp = merge [] [] [] where merge l m r [] ys = (reverse l, reverse m, reverse (ys++r)) merge l m r xs [] = (reverse (xs++l), reverse m, reverse r) merge l m r (x:xs) (y:ys) = case x `cmp` y of GT -> merge l m (y:r) (x:xs) ys EQ -> merge l ((x,y):m) r xs ys LT -> merge (x:l) m r xs (y:ys)
It's rare of course that you need the generality of merging lists of different types. Though of course this also covers the slightly more common case of comparing where == is only an equivalence relation and you want to keep or combine both elements.
I've found the following generalization sufficient enough: merge :: (a -> a -> Ordering) -> (a -> a -> [a] -> [a]) -> [a] -> [a] -> [a] merge cmp jn l1 l2 = case l1 of [] -> l2 x1 : r1 -> case l2 of [] -> l1 x2 : r2 -> let recmerge = merge cmp jn in case cmp x1 x2 of LT -> x1 : recmerge r1 l2 EQ -> jn x1 x2 $ recmerge r1 r2 GT -> x2 : recmerge l1 r2 Add a parameter to join equal elements with the recursively merged list tails. This allows to keep both or only one elements or to add occurrences counts of multi-sets. Cheers Christian

On Fri, 03 Nov 2006, Duncan Coutts
groupBy ((==) `on` fst)
Read it as "group by equality on first".
vs groupBy (equating fst)
So do you suggest that we deprecate and remove comparing?
Yes, this seems like a good idea. (I had forgotten that comparing was added before 6.6 was released.) I can add a deprecation pragma to my patch. Any objections? -- /NAD

Nils Anders Danielsson schrieb:
On Fri, 03 Nov 2006, Duncan Coutts
wrote: groupBy ((==) `on` fst)
Read it as "group by equality on first".
vs groupBy (equating fst)
So do you suggest that we deprecate and remove comparing?
Yes, this seems like a good idea. (I had forgotten that comparing was added before 6.6 was released.) I can add a deprecation pragma to my patch. Any objections?
Yes, "comparing" is mentioned in "ThingsToAvoid". Adding "equating" does do no harm. Style choices should be left to the user. Christian

On Fri, 2006-11-03 at 18:05 +0100, Nils Anders Danielsson wrote:
On Fri, 03 Nov 2006, Duncan Coutts
wrote: groupBy ((==) `on` fst)
Read it as "group by equality on first".
vs groupBy (equating fst)
So do you suggest that we deprecate and remove comparing?
Yes, this seems like a good idea. (I had forgotten that comparing was added before 6.6 was released.) I can add a deprecation pragma to my patch. Any objections?
As I've said before, I think there is room for both the general and special cases. We're not talking about polluting the namespace here, Data.Ord and Data.Eq are pretty new and have to be imported explicitly. It's not like adding something to Data.List which many existing programs import without qualification. But mainly I think it should be consistent. We should either have all three or just `on`. Keeping comparing but not adding equating doesn't seem to make a lot of sense. We should either agree to deprecate comparing or add equating too. So now that we have `on`, is there any desire for comparing and equating. I think there is, but lets see what other people think. Duncan

I agree with Duncan here, and I'd prefer to keep all three.
On 03/11/06, Duncan Coutts
On Fri, 2006-11-03 at 18:05 +0100, Nils Anders Danielsson wrote:
On Fri, 03 Nov 2006, Duncan Coutts
wrote: groupBy ((==) `on` fst)
Read it as "group by equality on first".
vs groupBy (equating fst)
So do you suggest that we deprecate and remove comparing?
Yes, this seems like a good idea. (I had forgotten that comparing was added before 6.6 was released.) I can add a deprecation pragma to my patch. Any objections?
As I've said before, I think there is room for both the general and special cases. We're not talking about polluting the namespace here, Data.Ord and Data.Eq are pretty new and have to be imported explicitly. It's not like adding something to Data.List which many existing programs import without qualification.
But mainly I think it should be consistent. We should either have all three or just `on`. Keeping comparing but not adding equating doesn't seem to make a lot of sense. We should either agree to deprecate comparing or add equating too.
So now that we have `on`, is there any desire for comparing and equating. I think there is, but lets see what other people think.
Duncan
_______________________________________________ Libraries mailing list Libraries@haskell.org http://www.haskell.org/mailman/listinfo/libraries

On Fri, 03 Nov 2006, Duncan Coutts
But mainly I think it should be consistent. We should either have all three or just `on`. Keeping comparing but not adding equating doesn't seem to make a lot of sense. We should either agree to deprecate comparing or add equating too.
This I agree with, and having all three isn't the end of the world, so it's fine with me. Do we have a patch for equating fulfilling all the new requirements? -- /NAD

On Mon, 06 Nov 2006, Nils Anders Danielsson
Do we have a patch for equating fulfilling all the new requirements?
Apparently not. I have also just realised that equating is a bad name for this function. To equate x and y does not mean to check whether they are equal, but to treat them as equal, and that's not at all what the function does. A better name might be equalityOn, as in groupBy (equalityOn length). Or perhaps equalityOf. In light of the above points I suggest that someone else creates a new proposal for equating/equalityOn/whatever, so that it can be discussed properly. -- /NAD

On Thu, 2 Nov 2006, Nils Anders Danielsson wrote:
The function on defined by
(*) `on` f = \x y -> f x * f y
is convenient when using functions like sortBy: sortBy (compare `on` fst), for example. It also makes the code more readable.
Furthermore I consider on to be above the Fairbairn threshold, since * we get rid of two lambdas, * we get rid of the duplication of p, * on has some nice algebraic properties (documented in the patch) * and, most importantly, it is easier at a glance to understand (*) `on` p than to understand \x y -> p x * p y (assuming one knows about on).
This reminds me on an earlier discussion: http://www.haskell.org/pipermail/libraries/2005-March/003431.html I expect, that all constructs of a "*By" list function with "on" and "comparing" are only efficient, if "f" is cheap. That's why I have defined functions and called them *Key functions, which buffer the results of "f". I attached the Key suffix in order to show that these functions sort, group, remove duplicates and so on with respect to a key. I called my "on" "composeDouble": http://cvs.haskell.org/darcs/htam/src/Useful.hs
participants (13)
-
Bulat Ziganshin
-
Cale Gibbard
-
Christian Maeder
-
dons@cse.unsw.edu.au
-
Duncan Coutts
-
Henning Thielemann
-
Jan-Willem Maessen
-
kahl@cas.mcmaster.ca
-
Malcolm Wallace
-
Neil Mitchell
-
Nils Anders Danielsson
-
Simon Marlow
-
Taral