
Dear All I'm learning Haskell from a background in Python, and I'm just looking at the sort and sortBy functions in Data.List. In Python, the decorate-sort-undecorate pattern is a popular alternative to using an explicit compare function. For example, to sort a list of lists by length: def sortByLength(xs): dec_xs = [(len(x), x) for x in xs] dec_xs.sort() undec_xs = [x[1] for x in dec_xs] return undec_xs This is often preferred to something like: xs.sort(lambda x,y: len(x) > len(y)) # just used lambda so it fits on one line I think the reasoning is that plain sort() is done at C speed, whereas sort(func) is done in Python, so, depending on the list I suppose, dsu can be worth the trouble. (Sorry for vagueness). Anyway, I was wondering if dsu is popular in Haskell, and whether or when it would make sense to use dsu rather than sortBy. Here's a verbose dsu I wrote myself: sortDSU decFunc a = undecorate (sort (decorate decFunc a)) decorate decFunc [] = [] decorate decFunc (x:xs) = ( ((decFunc x), x) : decorate decFunc xs ) undecorate [] = [] undecorate ( (_, y) :xs) = ( y : undecorate xs ) Here's a terser and perhaps more idiomatic (but I think equivalent) dsu which I then found in a comment at the Real World Haskell website: dsuSort decFunc a = map snd (sort (zip (map decFunc a) a)) I have tested both functions with length and sum in ghci. So, do Haskell programmers use the decorate-sort-undecorate pattern? If not, why not? If so, when? Thanks and best wishes Ivan -- ============================================================ Ivan A. Uemlianin Speech Technology Research and Development ivan@llaisdy.com www.llaisdy.com llaisdy.wordpress.com www.linkedin.com/in/ivanuemlianin "Froh, froh! Wie seine Sonnen, seine Sonnen fliegen" (Schiller, Beethoven) ============================================================

Am Montag 22 Juni 2009 12:03:02 schrieb Ivan Uemlianin:
Dear All
I'm learning Haskell from a background in Python, and I'm just looking at the sort and sortBy functions in Data.List. In Python, the decorate-sort-undecorate pattern is a popular alternative to using an explicit compare function. For example, to sort a list of lists by length:
def sortByLength(xs): dec_xs = [(len(x), x) for x in xs] dec_xs.sort() undec_xs = [x[1] for x in dec_xs] return undec_xs
This is often preferred to something like:
xs.sort(lambda x,y: len(x) > len(y)) # just used lambda so it fits on one line
I think the reasoning is that plain sort() is done at C speed, whereas sort(func) is done in Python, so, depending on the list I suppose, dsu can be worth the trouble. (Sorry for vagueness).
Anyway, I was wondering if dsu is popular in Haskell, and whether or when it would make sense to use dsu rather than sortBy.
It's moderately popular. It makes much sense to use it, if the decoration function is expensive. From http://www.haskell.org/haskellwiki/Blow_your_mind : map snd . sortBy (comparing fst) . map (length &&& id) -- the so called "Schwartzian Transform" for computationally more expensive -- functions. it even has a name :) If you used sortBy (comparing f) f x would be recalculated each time you compare x, it's only calculated once with the Schwartzian transform
Here's a verbose dsu I wrote myself:
sortDSU decFunc a = undecorate (sort (decorate decFunc a))
decorate decFunc [] = [] decorate decFunc (x:xs) = ( ((decFunc x), x) : decorate decFunc xs )
undecorate [] = [] undecorate ( (_, y) :xs) = ( y : undecorate xs )
Here's a terser and perhaps more idiomatic (but I think equivalent) dsu which I then found in a comment at the Real World Haskell website:
dsuSort decFunc a = map snd (sort (zip (map decFunc a) a))
more general: dsuSort decFun a = map snd . sortBy (comparing fst) $ zip (mp decFun a) a
I have tested both functions with length and sum in ghci.
So, do Haskell programmers use the decorate-sort-undecorate pattern? If not, why not? If so, when?
Sometimes. It's used if the decorating function is expensive, not if constructing and deconstructing tuples costs more than recalculating it (consider sortBy (comparing snd) as an extreme case).
Thanks and best wishes
Ivan

On Jun 22, 2009, at 06:03 , Ivan Uemlianin wrote:
I'm learning Haskell from a background in Python, and I'm just looking at the sort and sortBy functions in Data.List. In Python, the decorate-sort-undecorate pattern is a popular alternative to using an explicit compare function. For example, to sort a list of lists by
It's fairly common, considering that decorate-sort-undecorate is a functional programming idiom dating back to Lisp. In Haskell it's usually expressed with the decoration in a tuple such that the default sort can be used.
map snd . sort . map (\x -> (x,decorate x))
Fancier versions use arrows to make the decorate part cleaner:
map snd . sort . map (decorate &&& id)
-- brandon s. allbery [solaris,freebsd,perl,pugs,haskell] allbery@kf8nh.com system administrator [openafs,heimdal,too many hats] allbery@ece.cmu.edu electrical and computer engineering, carnegie mellon university KF8NH

On Tue, 23 Jun 2009 14:58:11 +0200, Brandon S. Allbery KF8NH
On Jun 22, 2009, at 06:03 , Ivan Uemlianin wrote:
I'm learning Haskell from a background in Python, and I'm just looking at the sort and sortBy functions in Data.List. In Python, the decorate-sort-undecorate pattern is a popular alternative to using an explicit compare function. For example, to sort a list of lists by
It's fairly common, considering that decorate-sort-undecorate is a functional programming idiom dating back to Lisp. In Haskell it's usually expressed with the decoration in a tuple such that the default sort can be used.
map snd . sort . map (\x -> (x,decorate x))
Fancier versions use arrows to make the decorate part cleaner:
map snd . sort . map (decorate &&& id)
The simplest form for e.g. sorting by length is:
sortByLength = sortBy (comparing length)
-- Met vriendelijke groet, Henk-Jan van Tuyl -- http://functor.bamikanarie.com http://Van.Tuyl.eu/ --

Am Dienstag 23 Juni 2009 15:42:59 schrieb Henk-Jan van Tuyl:
On Tue, 23 Jun 2009 14:58:11 +0200, Brandon S. Allbery KF8NH
wrote: On Jun 22, 2009, at 06:03 , Ivan Uemlianin wrote:
I'm learning Haskell from a background in Python, and I'm just looking at the sort and sortBy functions in Data.List. In Python, the decorate-sort-undecorate pattern is a popular alternative to using an explicit compare function. For example, to sort a list of lists by
It's fairly common, considering that decorate-sort-undecorate is a functional programming idiom dating back to Lisp. In Haskell it's usually expressed with the decoration in a tuple such that the default sort can be used.
map snd . sort . map (\x -> (x,decorate x))
Typo: map snd . sort . map (\x -> (decorate x,x))
Fancier versions use arrows to make the decorate part cleaner:
map snd . sort . map (decorate &&& id)
The simplest form for e.g. sorting by length is:
sortByLength = sortBy (comparing length)
But that is an example where the decoration really shines, except all lists are very short: Prelude> :set +s Prelude> let lens :: [Int]; lens = [(k^2+3*k-2) `mod` 5431 | k <- [1 .. 500]] (0.04 secs, 6184112 bytes) Prelude> let lists = map (flip replicate ()) lens (0.00 secs, 609084 bytes) Prelude> :m +Data.List Prelude Data.List> :m +Data.Ord Prelude Data.List Data.Ord> let srtl1 = sortBy (comparing length) lists (0.00 secs, 0 bytes) Prelude Data.List Data.Ord> let srtl2 = map snd . sortBy (comparing fst) $ map (\l -> (length l, l)) lists (0.02 secs, 5975640 bytes) Prelude Data.List Data.Ord> length (srtl2 !! 420) 4471 (0.19 secs, 37089168 bytes) Prelude Data.List Data.Ord> length (srtl1 !! 420) 4471 (1.09 secs, 542788 bytes) simpler is not always better.

Daniel Fischer wrote:
Prelude> :set +s Prelude> let lens :: [Int]; lens = [(k^2+3*k-2) `mod` 5431 | k <- [1 .. 500]] (0.04 secs, 6184112 bytes) Prelude> let lists = map (flip replicate ()) lens (0.00 secs, 609084 bytes) Prelude> :m +Data.List Prelude Data.List> :m +Data.Ord Prelude Data.List Data.Ord> let srtl1 = sortBy (comparing length) lists (0.00 secs, 0 bytes) Prelude Data.List Data.Ord> let srtl2 = map snd . sortBy (comparing fst) $ map (\l -> (length l, l)) lists (0.02 secs, 5975640 bytes) Prelude Data.List Data.Ord> length (srtl2 !! 420) 4471 (0.19 secs, 37089168 bytes) Prelude Data.List Data.Ord> length (srtl1 !! 420) 4471 (1.09 secs, 542788 bytes)
Profiling too! Excellent. So this shows that with these long lists of lists, the dsu version was about ten times faster. I'll report back once I've written up. Thanks to everyone for your comments. Ivan -- ============================================================ Ivan A. Uemlianin Speech Technology Research and Development ivan@llaisdy.com www.llaisdy.com llaisdy.wordpress.com www.linkedin.com/in/ivanuemlianin "Froh, froh! Wie seine Sonnen, seine Sonnen fliegen" (Schiller, Beethoven) ============================================================

On Jun 23, 2009, at 10:13 , Daniel Fischer wrote:
Typo: map snd . sort . map (\x -> (decorate x,x))
Yeh, as usual I realized that about 5 minutes after I sent the message. :/ -- brandon s. allbery [solaris,freebsd,perl,pugs,haskell] allbery@kf8nh.com system administrator [openafs,heimdal,too many hats] allbery@ece.cmu.edu electrical and computer engineering, carnegie mellon university KF8NH

Dear All
I'll report back once I've written up. I hope this doesn't count as blog spam.
I've written up the new Haskell language features from the responses to my query on decorate-sort-undecorate: http://llaisdy.wordpress.com/2009/07/11/decorate-sort-undecorate-in-haskell-... dot (function composition) and dollar look very handy, and of course lambda. The Arrow robot &&& I think I shall leave aside for now.
Thanks to everyone for your comments. And best wishes
Ivan -- ============================================================ Ivan A. Uemlianin Speech Technology Research and Development ivan@llaisdy.com www.llaisdy.com llaisdy.wordpress.com www.linkedin.com/in/ivanuemlianin "Froh, froh! Wie seine Sonnen, seine Sonnen fliegen" (Schiller, Beethoven) ============================================================
participants (4)
-
Brandon S. Allbery KF8NH
-
Daniel Fischer
-
Henk-Jan van Tuyl
-
Ivan Uemlianin