<div dir="ltr"><div>We can improve things a bit further by forcing evaluation (with seq) along the way appropriately.<br></div><div><br></div><div><br></div><div><br></div><div><div><span style="font-family:monospace,monospace">gregSortBy cmp [] = []</span><br></div><div><font face="monospace, monospace">gregSortBy cmp xs = head $ until (null.tail) reduce (pair xs)</font></div><div><font face="monospace, monospace">  where</font></div><div><font face="monospace, monospace">    pair (x:y:t) | x `cmp` y == GT  = [y, x] : pair t</font></div><div><font face="monospace, monospace">                 | otherwise        = [x, y] : pair t</font></div><div><font face="monospace, monospace">    pair [x] = [[x]]</font></div><div><font face="monospace, monospace">    pair []  = []</font></div><div><font face="monospace, monospace"><br></font></div><div><font face="monospace, monospace">    reduce (v:w:x:y:t) = merge v' x' `seq` merge v' x' : reduce t</font></div><div><font face="monospace, monospace">                         where v' = merge v w `seq` merge v w</font></div><div><font face="monospace, monospace">                               x' = merge x y `seq` merge x y</font></div><div><font face="monospace, monospace">                         </font></div><div><font face="monospace, monospace">    reduce (x:y:t) = merge x y `seq` merge x y : reduce t</font></div><div><font face="monospace, monospace">    reduce xs      = xs</font></div><div><font face="monospace, monospace"><br></font></div><div><font face="monospace, monospace">    merge xs []           = xs</font></div><div><font face="monospace, monospace">    merge []  ys          = ys</font></div><div><font face="monospace, monospace">    merge xs@(x:xs') ys@(y:ys') </font></div><div><font face="monospace, monospace">         | x `cmp` y == GT  = y : merge xs  ys'</font></div><div><font face="monospace, monospace">         | otherwise        = x : merge xs' ys</font></div><div><font face="monospace, monospace"><br></font></div><div><font face="monospace, monospace"><br></font></div><div><span style="font-family:monospace,monospace">gSortBy cmp = mergeAll . sequences</span><br></div><div><font face="monospace, monospace">  where</font></div><div><font face="monospace, monospace">    sequences (a:b:xs)</font></div><div><font face="monospace, monospace">      | a `cmp` b == GT = descending b [a]  xs</font></div><div><font face="monospace, monospace">      | otherwise       = ascending  b (a:) xs</font></div><div><font face="monospace, monospace">    sequences xs = [xs]</font></div><div><font face="monospace, monospace"><br></font></div><div><font face="monospace, monospace"><br></font></div><div><font face="monospace, monospace">    descending a as (b:bs)</font></div><div><font face="monospace, monospace">      | a `cmp` b == GT = descending b (a:as) bs</font></div><div><font face="monospace, monospace">    descending a as bs  = (a:as) `seq` (a:as) : sequences bs</font></div><div><font face="monospace, monospace"><br></font></div><div><font face="monospace, monospace"><br></font></div><div><font face="monospace, monospace">    ascending a as (b:bs)</font></div><div><font face="monospace, monospace">      | a `cmp` b /= GT = ascending b (as . (a:)) bs</font></div><div><font face="monospace, monospace">    ascending a as bs   = as [a] `seq` as [a] : sequences bs</font></div><div><font face="monospace, monospace"><br></font></div><div><font face="monospace, monospace"><br></font></div><div><font face="monospace, monospace">    mergeAll [x] = x</font></div><div><font face="monospace, monospace">    mergeAll xs  = mergeAll (mergePairs xs)</font></div><div><font face="monospace, monospace"><br></font></div><div><font face="monospace, monospace"><br></font></div><div><font face="monospace, monospace">    mergePairs (a:b:xs) = merge a b `seq` merge a b : mergePairs xs</font></div><div><font face="monospace, monospace">    mergePairs xs       = xs</font></div><div><font face="monospace, monospace"><br></font></div><div><font face="monospace, monospace"><br></font></div><div><font face="monospace, monospace">    merge as@(a:as') bs@(b:bs')</font></div><div><font face="monospace, monospace">      | a `cmp` b == GT = b : merge as  bs'</font></div><div><font face="monospace, monospace">      | otherwise       = a : merge as' bs</font></div><div><font face="monospace, monospace">    merge [] bs         = bs</font></div><div><font face="monospace, monospace">    merge as []         = as</font></div></div><div><br></div><div><br></div><div><br></div><div><br></div><div><b>Before the change:</b></div><div><br></div><div><div><font face="monospace, monospace">benchmarking random ints/ghc</font></div><div><font face="monospace, monospace">time                 3.687 s    (3.541 s .. NaN s)</font></div><div><font face="monospace, monospace">                     1.000 R²   (1.000 R² .. 1.000 R²)</font></div><div><font face="monospace, monospace">mean                 3.691 s    (3.669 s .. 3.705 s)</font></div><div><font face="monospace, monospace">std dev              21.45 ms   (0.0 s .. 24.76 ms)</font></div><div><font face="monospace, monospace">variance introduced by outliers: 19% (moderately inflated)</font></div><div><font face="monospace, monospace"><br></font></div><div><font face="monospace, monospace">benchmarking random ints/greg</font></div><div><font face="monospace, monospace">time                 2.648 s    (2.482 s .. 2.822 s)</font></div><div><font face="monospace, monospace">                     0.999 R²   (0.998 R² .. 1.000 R²)</font></div><div><font face="monospace, monospace">mean                 2.704 s    (2.670 s .. 2.736 s)</font></div><div><font face="monospace, monospace">std dev              52.68 ms   (0.0 s .. 54.49 ms)</font></div><div><font face="monospace, monospace">variance introduced by outliers: 19% (moderately inflated)</font></div><div><font face="monospace, monospace"><br></font></div><div><font face="monospace, monospace">benchmarking random ints/gSort</font></div><div><font face="monospace, monospace">time                 2.733 s    (2.682 s .. 2.758 s)</font></div><div><font face="monospace, monospace">                     1.000 R²   (1.000 R² .. 1.000 R²)</font></div><div><font face="monospace, monospace">mean                 2.707 s    (2.689 s .. 2.718 s)</font></div><div><font face="monospace, monospace">std dev              16.84 ms   (0.0 s .. 19.20 ms)</font></div><div><font face="monospace, monospace">variance introduced by outliers: 19% (moderately inflated)</font></div></div><div><br></div><div><b>After the change:</b></div><div><br></div><div><div><font face="monospace, monospace">benchmarking random ints/greg</font></div><div><font face="monospace, monospace">time                 2.576 s    (2.548 s .. 2.628 s)</font></div><div><font face="monospace, monospace">                     1.000 R²   (1.000 R² .. 1.000 R²)</font></div><div><font face="monospace, monospace">mean                 2.590 s    (2.578 s .. 2.599 s)</font></div><div><font face="monospace, monospace">std dev              12.99 ms   (0.0 s .. 14.89 ms)</font></div><div><font face="monospace, monospace">variance introduced by outliers: 19% (moderately inflated)</font></div><div><font face="monospace, monospace"><br></font></div><div><font face="monospace, monospace">benchmarking random ints/gSort</font></div><div><font face="monospace, monospace">time                 2.538 s    (2.412 s .. 2.627 s)</font></div><div><font face="monospace, monospace">                     1.000 R²   (0.999 R² .. 1.000 R²)</font></div><div><font face="monospace, monospace">mean                 2.543 s    (2.517 s .. 2.560 s)</font></div><div><font face="monospace, monospace">std dev              26.16 ms   (0.0 s .. 30.21 ms)</font></div><div><font face="monospace, monospace">variance introduced by outliers: 19% (moderately inflated)</font></div></div><div><br></div><div><br></div><div><br></div><div><br></div></div><div class="gmail_extra"><br><div class="gmail_quote">On Sun, Mar 26, 2017 at 1:54 PM, Siddhanathan Shanmugam <span dir="ltr"><<a href="mailto:siddhanathan+eml@gmail.com" target="_blank">siddhanathan+eml@gmail.com</a>></span> wrote:<br><blockquote class="gmail_quote" style="margin:0 0 0 .8ex;border-left:1px #ccc solid;padding-left:1ex"><div dir="ltr"><div><div>Theoretically, we could do better. We currently only exploit monotonic runs in merge sort, but we could also exploit bitonic runs:</div><div><br></div><div><div><font face="monospace, monospace">    dlist as = as [] `seq` as []<br></font></div><div><font face="monospace, monospace"><br></font></div><div><font face="monospace, monospace">    sequences [] = [[]]</font></div><div><font face="monospace, monospace">    sequences [a] = [[a]]</font></div><div><font face="monospace, monospace">    sequences (a:xs) = bitonic a a (a:) xs</font></div><div><font face="monospace, monospace"><br></font></div><div><font face="monospace, monospace">    bitonic min max as (b:bs)</font></div><div><font face="monospace, monospace">      | b `cmp` max /= LT = bitonic min b   (as . (b:)) bs</font></div><div><font face="monospace, monospace">      | b `cmp` min /= GT = bitonic b   max ((b:) . as) bs</font></div><div><font face="monospace, monospace">      | otherwise = dlist as : sequences (b:bs)</font></div><div><font face="monospace, monospace">    bitonic _ _ as [] = [dlist as]</font></div><div><br></div></div></div><div><br></div><div>The constant factors here might be too high to notice the difference though.</div><span class=""><div><br></div><div><span style="font-size:12.8px"><br></span></div><div><span style="font-size:12.8px">> However, still my version is more laziness-friendly, i.e. it requires fewer</span><br></div><div><span style="font-size:12.8px">> comparisons to get the</span><br style="font-size:12.8px"><span style="font-size:12.8px">> N smallest elements of a list </span><span style="font-size:12.8px">(see</span><br></div>> <a href="https://github.com/greg7mdp/ghc-sort/blob/master/src/sort_with_trace.hs" rel="noreferrer" style="font-size:12.8px" target="_blank">https://github.com/greg7mdp/<wbr>ghc-sort/blob/master/src/sort_<wbr>with_trace.hs</a><span style="font-size:12.8px">).</span><div><span style="font-size:12.8px">></span></div><div><span style="font-size:12.8px">> I wonder if this might not be a more useful trait than being able to sort</span><br></div><div><span style="font-size:12.8px">> already sorted lists super fast.</span><br></div><div><span style="font-size:12.8px"><br></span></div></span><div><span style="font-size:12.8px">This comes down to a discussion of merge sort vs natural merge sort.</span></div><div><br></div><div>Data.List.sort is an implementation of a variant of merge sort called natural merge sort. The algorithm is linearithmic in the worst case, but linear in the best case (already sorted list).</div><div><br></div><div><br></div></div><div class="HOEnZb"><div class="h5"><div class="gmail_extra"><br><div class="gmail_quote">On Sun, Mar 26, 2017 at 10:47 AM, Gregory Popovitch <span dir="ltr"><<a href="mailto:greg7mdp@gmail.com" target="_blank">greg7mdp@gmail.com</a>></span> wrote:<br><blockquote class="gmail_quote" style="margin:0 0 0 .8ex;border-left:1px #ccc solid;padding-left:1ex">Thanks again @Siddhanathan! Looks like your gSort fixes the main issue with<br>
Data.List.sort().<br>
<br>
I have updated the test programs in <a href="https://github.com/greg7mdp/ghc-sort" rel="noreferrer" target="_blank">https://github.com/greg7mdp/gh<wbr>c-sort</a> to<br>
include your new version.<br>
<br>
Here are the results (your new version looks like a definite improvement vs<br>
the current GHC one):<br>
<br>
input                        GHC sort         My Orig proposal     gSort<br>
------------------------------<wbr>------------------------------<wbr>----------------<br>
---<br>
sorted ints (ascending)      151               456                  148<br>
sorted ints (descending)     152               466                  155<br>
random ints                 2732              2006                 2004<br>
random strings              6564              5549                 5528<br>
<br>
<br>
So replacing the current GHC version with gSort is a no brainer, as it is<br>
better in all regards.<br>
<br>
However, still my version is more laziness-friendly, i.e. it requires fewer<br>
comparisons to get the<br>
N smallest elements of a list (see<br>
<a href="https://github.com/greg7mdp/ghc-sort/blob/master/src/sort_with_trace.hs" rel="noreferrer" target="_blank">https://github.com/greg7mdp/gh<wbr>c-sort/blob/master/src/sort_wi<wbr>th_trace.hs</a>).<br>
<br>
I wonder if this might not be a more useful trait than being able to sort<br>
already sorted lists super fast.<br>
<span><br>
Thanks,<br>
<br>
greg<br>
<br>
______________________________<wbr>__<br>
<br>
From: <a href="mailto:siddhanathan@gmail.com" target="_blank">siddhanathan@gmail.com</a> [mailto:<a href="mailto:siddhanathan@gmail.com" target="_blank">siddhanathan@gmail.com</a><wbr>] On Behalf Of<br>
Siddhanathan Shanmugam<br>
</span>Sent: Sunday, March 26, 2017 1:05 PM<br>
<span>To: Gregory Popovitch<br>
Cc: Haskell Libraries<br>
Subject: Re: Proposal: a new implementation for Data.List.sort and<br>
Data.List.sortBy, which has better performance characteristics and is more<br>
laziness-friendly.<br>
<br>
<br>
</span><div><div class="m_6283889194055629001h5">Interesting. You are right, performance for sorting random lists has<br>
priority over performance for sorting already-sorted lists.<br>
<br>
Ignore the numbers for my previous version. Can you compare GHC's sort, your<br>
proposal, and gSort below?<br>
<br>
<br>
gSort :: Ord a => [a] -> [a]<br>
gSort = gSortBy compare<br>
gSortBy cmp = mergeAll . sequences<br>
  where<br>
    sequences (a:b:xs)<br>
      | a `cmp` b == GT = descending b [a]  xs<br>
      | otherwise       = ascending  b (a:) xs<br>
    sequences xs = [xs]<br>
<br>
<br>
    descending a as (b:bs)<br>
      | a `cmp` b == GT = descending b (a:as) bs<br>
    descending a as bs  = (a:as) : sequences bs<br>
<br>
<br>
    ascending a as (b:bs)<br>
      | a `cmp` b /= GT = ascending b (\ys -> as (a:ys)) bs<br>
    ascending a as bs   = as [a] `seq` as [a] : sequences bs<br>
<br>
<br>
    mergeAll [x] = x<br>
    mergeAll xs  = mergeAll (mergePairs xs)<br>
<br>
<br>
    mergePairs (a:b:xs) = merge a b : mergePairs xs<br>
    mergePairs xs       = xs<br>
<br>
<br>
    merge as@(a:as') bs@(b:bs')<br>
      | a `cmp` b == GT = b : merge as  bs'<br>
      | otherwise       = a : merge as' bs<br>
    merge [] bs         = bs<br>
    merge as []         = as<br>
<br>
<br>
Thanks,<br>
Sid<br>
<br>
<br>
On Sun, Mar 26, 2017 at 9:19 AM, Gregory Popovitch <<a href="mailto:greg7mdp@gmail.com" target="_blank">greg7mdp@gmail.com</a>><br>
wrote:<br>
<br>
<br>
        Thank you @Siddhanathan! I welcome any improvement you may make, as<br>
I said I<br>
        am very far from a Haskell expert.<br>
<br>
        I just tested your change with my test project<br>
        (<a href="https://github.com/greg7mdp/ghc-sort" rel="noreferrer" target="_blank">https://github.com/greg7mdp/g<wbr>hc-sort</a><br>
</div></div><<a href="https://github.com/greg7mdp/ghc-sort" rel="noreferrer" target="_blank">https://github.com/greg7mdp/g<wbr>hc-sort</a>> )<br>
<div><div class="m_6283889194055629001h5">        and here are my results (mean times in ms):<br>
<br>
        input                        GHC sort          Orig proposal<br>
your<br>
        change<br>
<br>
------------------------------<wbr>------------------------------<wbr>----------------<br>
        ---<br>
        sorted ints (ascending)      153               467<br>
139<br>
        sorted ints (descending)     152               472<br>
599<br>
        random ints                 2824              2077<br>
2126<br>
        random strings              6564              5613<br>
5983<br>
<br>
        Your change is a definite improvement for sorted integers in<br>
ascending<br>
        order, but is worse for other cases.<br>
<br>
        Is there a real need to optimize the sort for already sorted list?<br>
Of course<br>
        it should not be a degenerate<br>
        case and take longer than sorting random numbers, but this is not<br>
the case<br>
        here. Sorting already sorted<br>
        lists is, even with my version, over 4 times faster than sorting<br>
random<br>
        lists. This sounds perfectly<br>
        acceptable to me, and I feel that trying to optimize this specific<br>
case<br>
        further, if it comes at the<br>
        detriment of the general case, is not desirable.<br>
<br>
        Thanks,<br>
<br>
        greg<br>
<br>
        ______________________________<wbr>__<br>
<br>
        From: <a href="mailto:siddhanathan@gmail.com" target="_blank">siddhanathan@gmail.com</a> [mailto:<a href="mailto:siddhanathan@gmail.com" target="_blank">siddhanathan@gmail.com</a><wbr>] On<br>
Behalf Of<br>
        Siddhanathan Shanmugam<br>
        Sent: Sunday, March 26, 2017 11:41 AM<br>
        To: Gregory Popovitch<br>
        Cc: Haskell Libraries<br>
        Subject: Re: Proposal: a new implementation for Data.List.sort and<br>
        Data.List.sortBy, which has better performance characteristics and<br>
is more<br>
        laziness-friendly.<br>
<br>
<br>
<br>
        Thank you! This identifies a space leak in base which went unnoticed<br>
for 7<br>
        years.<br>
<br>
        Your implementation can be improved further. Instead of splitting<br>
into<br>
        pairs, you could instead split into lists of sorted sublists by<br>
replacing<br>
        the pairs function with the following<br>
<br>
            pair = foldr f []<br>
              where<br>
                f x [] = [[x]]<br>
                f x (y:ys)<br>
                  | x `cmp` head y == LT = (x:y):ys<br>
                  | otherwise            = [x]:y:ys<br>
<br>
        This should give you the same performance improvements for sorting<br>
random<br>
        lists, but better performance while sorting ascending lists.<br>
<br>
        The version in base takes it one step further by using a DList to<br>
handle the<br>
        descending case efficiently as well, except there's a space leak<br>
right now<br>
        because of which it is slower.<br>
<br>
        On Sun, Mar 26, 2017 at 7:21 AM, Gregory Popovitch<br>
<<a href="mailto:greg7mdp@gmail.com" target="_blank">greg7mdp@gmail.com</a>><br>
        wrote:<br>
<br>
<br>
<br>
                Motivation:<br>
                ----------<br>
<br>
                Data.List.sort is a very important functionality in Haskell.<br>
I<br>
        believe that<br>
                the proposed implementation is:<br>
<br>
                - significantly faster than the current implementation on<br>
unsorted<br>
        lists,<br>
                typically 14% to 27% faster<br>
                - more laziness-friendly, i.e.:<br>
                    take 3 $ sort l<br>
                  will require significantly less comparisons than the<br>
current<br>
                implementation<br>
<br>
                Proposed Implementation<br>
                -----------------------<br>
<br>
                sort :: (Ord a) => [a] -> [a]<br>
                sort =  sortBy compare<br>
<br>
                sortBy cmp [] = []<br>
                sortBy cmp xs = head $ until (null.tail) reduce (pair xs)<br>
                  where<br>
                    pair (x:y:t) | x `cmp` y == GT  = [y, x] : pair t<br>
                                 | otherwise        = [x, y] : pair t<br>
                    pair [x] = [[x]]<br>
                    pair []  = []<br>
<br>
                    reduce (v:w:x:y:t) = merge v' x' : reduce t<br>
                                         where v' = merge v w<br>
                                               x' = merge x y<br>
<br>
                    reduce (x:y:t) = merge x y : reduce t<br>
                    reduce xs      = xs<br>
<br>
                    merge xs []           = xs<br>
                    merge []  ys          = ys<br>
                    merge xs@(x:xs') ys@(y:ys')<br>
                         | x `cmp` y == GT  = y : merge xs  ys'<br>
                         | otherwise        = x : merge xs' ys<br>
<br>
<br>
                Effect and Interactions<br>
                -----------------------<br>
<br>
                I have a stack project with a criterion test for this new<br>
        implementation,<br>
                available at <a href="https://github.com/greg7mdp/ghc-sort" rel="noreferrer" target="_blank">https://github.com/greg7mdp/gh<wbr>c-sort</a><br>
<<a href="https://github.com/greg7mdp/ghc-sort" rel="noreferrer" target="_blank">https://github.com/greg7mdp/g<wbr>hc-sort</a>><br>
<br>
        <<a href="https://github.com/greg7mdp/ghc-sort" rel="noreferrer" target="_blank">https://github.com/greg7mdp/g<wbr>hc-sort</a><br>
<<a href="https://github.com/greg7mdp/ghc-sort" rel="noreferrer" target="_blank">https://github.com/greg7mdp/g<wbr>hc-sort</a>> > .<br>
                I ran the tests on an Ubuntu 14.0.2 VM and GHC 8.0.2, and<br>
had the<br>
        following<br>
                results:<br>
<br>
                - sorting of random lists of integers is 27% faster<br>
                - sorting of random lists of strings is 14% faster<br>
                - sorting of already sorted lists is significantly slower,<br>
but still<br>
        much<br>
                faster than sorting random lists<br>
                - proposed version is more laziness friendly. For example<br>
this<br>
        version of<br>
                sortBy requires 11 comparisons to find<br>
                  the smallest element of a 15 element list, while the<br>
default<br>
                Data.List.sortBy requires 15 comparisons.<br>
                  (see<br>
<br>
<br>
<a href="https://github.com/greg7mdp/ghc-sort/blob/master/src/sort_with_trace.hs" rel="noreferrer" target="_blank">https://github.com/greg7mdp/gh<wbr>c-sort/blob/master/src/sort_wi<wbr>th_trace.hs</a><br>
<<a href="https://github.com/greg7mdp/ghc-sort/blob/master/src/sort_with_trace.hs" rel="noreferrer" target="_blank">https://github.com/greg7mdp/g<wbr>hc-sort/blob/master/src/sort_w<wbr>ith_trace.hs</a>><br>
<br>
<<a href="https://github.com/greg7mdp/ghc-sort/blob/master/src/sort_with_trace.hs" rel="noreferrer" target="_blank">https://github.com/greg7mdp/g<wbr>hc-sort/blob/master/src/sort_w<wbr>ith_trace.hs</a><br>
<<a href="https://github.com/greg7mdp/ghc-sort/blob/master/src/sort_with_trace.hs" rel="noreferrer" target="_blank">https://github.com/greg7mdp/g<wbr>hc-sort/blob/master/src/sort_w<wbr>ith_trace.hs</a>> ><br>
)<br>
<br>
<br>
<br>
                Test results<br>
                ------------<br>
<br>
                Criterion output (descending/ascending results are for<br>
already<br>
        sorted<br>
                lists).<br>
                I barely understand what Criterion does, and I am puzzled<br>
with the<br>
        various<br>
                "T" output - maybe there is a bug in my bench code:<br>
<br>
                vagrant@vagrant-ubuntu-trusty-<wbr>64:/vagrant$ stack exec<br>
ghc-sort<br>
                benchmarking ascending ints/ghc<br>
                TTTTTTTTTTTTTTTTTTTTTTTTTTTTTT<wbr>TTTTTTTtime<br>
160.6 ms<br>
        (153.4<br>
                ms .. 167.8 ms)<br>
                                     0.997 R²   (0.986 R² .. 1.000 R²)<br>
                mean                 161.7 ms   (158.3 ms .. 165.9 ms)<br>
                std dev              5.210 ms   (3.193 ms .. 7.006 ms)<br>
                variance introduced by outliers: 12% (moderately inflated)<br>
<br>
                benchmarking ascending ints/greg<br>
                TTTTTTTTTTTTTTTTtime                 473.8 ms   (398.6 ms ..<br>
554.9<br>
        ms)<br>
                                     0.996 R²   (0.987 R² .. 1.000 R²)<br>
                mean                 466.2 ms   (449.0 ms .. 475.0 ms)<br>
                std dev              14.94 ms   (0.0 s .. 15.29 ms)<br>
                variance introduced by outliers: 19% (moderately inflated)<br>
<br>
                benchmarking descending ints/ghc<br>
                TTTTTTTTTTTTTTTTTTTTTTTTTTTTTT<wbr>TTTTTTTtime<br>
165.1 ms<br>
        (148.2<br>
                ms .. 178.2 ms)<br>
                                     0.991 R²   (0.957 R² .. 1.000 R²)<br>
                mean                 158.7 ms   (154.0 ms .. 164.3 ms)<br>
                std dev              7.075 ms   (4.152 ms .. 9.903 ms)<br>
                variance introduced by outliers: 12% (moderately inflated)<br>
<br>
                benchmarking descending ints/greg<br>
                TTTTTTTTTTTTTTTTtime                 471.7 ms   (419.8 ms ..<br>
508.3<br>
        ms)<br>
                                     0.999 R²   (0.995 R² .. 1.000 R²)<br>
                mean                 476.0 ms   (467.5 ms .. 480.0 ms)<br>
                std dev              7.447 ms   (67.99 as .. 7.865 ms)<br>
                variance introduced by outliers: 19% (moderately inflated)<br>
<br>
                benchmarking random ints/ghc<br>
                TTTTTTTTTTTTTTTTtime                 2.852 s    (2.564 s ..<br>
3.019 s)<br>
                                     0.999 R²   (0.997 R² .. 1.000 R²)<br>
                mean                 2.812 s    (2.785 s .. 2.838 s)<br>
                std dev              44.06 ms   (543.9 as .. 44.97 ms)<br>
                variance introduced by outliers: 19% (moderately inflated)<br>
<br>
                benchmarking random ints/greg<br>
                TTTTTTTTTTTTTTTTtime                 2.032 s    (1.993 s ..<br>
2.076 s)<br>
                                     1.000 R²   (1.000 R² .. 1.000 R²)<br>
                mean                 2.028 s    (2.019 s .. 2.033 s)<br>
                std dev              7.832 ms   (0.0 s .. 8.178 ms)<br>
                variance introduced by outliers: 19% (moderately inflated)<br>
<br>
                benchmarking shakespeare/ghc<br>
                TTTTTTTTTTTTTTTTtime                 6.504 s    (6.391 s ..<br>
6.694 s)<br>
                                     1.000 R²   (1.000 R² .. 1.000 R²)<br>
                mean                 6.499 s    (6.468 s .. 6.518 s)<br>
                std dev              28.85 ms   (0.0 s .. 32.62 ms)<br>
                variance introduced by outliers: 19% (moderately inflated)<br>
<br>
                benchmarking shakespeare/greg<br>
                TTTTTTTTTTTTTTTTtime                 5.560 s    (5.307 s ..<br>
5.763 s)<br>
                                     1.000 R²   (0.999 R² .. 1.000 R²)<br>
                mean                 5.582 s    (5.537 s .. 5.607 s)<br>
                std dev              39.30 ms   (0.0 s .. 43.49 ms)<br>
                variance introduced by outliers: 19% (moderately inflated)<br>
<br>
<br>
                Costs and Drawbacks<br>
                -------------------<br>
<br>
                The only cost I see is the reduced performance when sorting<br>
already<br>
        sorted<br>
                lists. However, since this remains quite efficient, indeed<br>
over 4<br>
        times<br>
                faster than sorting unsorted lists, I think it is an<br>
acceptable<br>
        tradeoff.<br>
<br>
                Final note<br>
                ----------<br>
<br>
                My Haskell is very rusty. I worked on this a couple years<br>
ago when I<br>
        was<br>
                learning Haskell, and meant to propose it to the Haskell<br>
community,<br>
        but<br>
                never got to it at the time.<br>
<br>
                ______________________________<wbr>_________________<br>
                Libraries mailing list<br>
                <a href="mailto:Libraries@haskell.org" target="_blank">Libraries@haskell.org</a><br>
                <a href="http://mail.haskell.org/cgi-bin/mailman/listinfo/libraries" rel="noreferrer" target="_blank">http://mail.haskell.org/cgi-bi<wbr>n/mailman/listinfo/libraries</a><br>
<<a href="http://mail.haskell.org/cgi-bin/mailman/listinfo/libraries" rel="noreferrer" target="_blank">http://mail.haskell.org/cgi-b<wbr>in/mailman/listinfo/libraries</a>><br>
<br>
</div></div>        <<a href="http://mail.haskell.org/cgi-bin/mailman/listinfo/libraries" rel="noreferrer" target="_blank">http://mail.haskell.org/cgi-b<wbr>in/mailman/listinfo/libraries</a><br>
<<a href="http://mail.haskell.org/cgi-bin/mailman/listinfo/libraries" rel="noreferrer" target="_blank">http://mail.haskell.org/cgi-b<wbr>in/mailman/listinfo/libraries</a>> ><br>
<br>
<br>
<br>
<br>
<br>
<br>
<br>
<br>
</blockquote></div><br></div>
</div></div></blockquote></div><br></div>