[Haskell-cafe] qsort

Daniel Fischer daniel.is.fischer at web.de
Sat Aug 15 12:09:38 EDT 2009


Am Samstag 15 August 2009 10:09:28 schrieb Peter Verswyvelen:
> I was reading the introduction at
> http://www.haskell.org/haskellwiki/Introduction
> where the typical Haskell version of qsort is given
>
> qsort [] = []
> qsort (x:xs) = qsort
> (filter<http://haskell.org/ghc/docs/latest/html/libraries/base/Prelude.html
>#v:filter> (< x) xs)
> ++<http://haskell.org/ghc/docs/latest/html/libraries/base/Prelude.html#v:.>
> [x]
> ++<http://haskell.org/ghc/docs/latest/html/libraries/base/Prelude.html#v:.>
>qsort
> (filter<http://haskell.org/ghc/docs/latest/html/libraries/base/Prelude.html
>#v:filter>
> (>=<http://haskell.org/ghc/docs/latest/html/libraries/base/Prelude.html#v:&
>gt;=>x ) xs
>
> which is then compared to the inplace C version, showing off how much
> shorter the Haskell version is.
>
> However, the page also has a link to a "semi-direct" translation of the C
> version, which then brings the user to all kinds of confusing threads and
> texts, like
>
> *"**Unfortunately none of the above "real" quicksorts seems to compile as
> given, when copy/pasted into ghci. Can someone fix? The "parallel"
> quicksort gave error "unknown package concurrent" when I ran make in
> quicksort/gransim. Has anyone got a functioning "real" quicksort that works
> on copy/paste? The program below is working very very slowly. It's probably
> slowsort... :o)"*
> *
> *
> Furthermore the inplace versions of qsort in Haskell are IMO less readable
> than the C version.
>
> I'm not sure but if I would be a beginner I might get confused by this.

Okay, the more direct translation of the C code

----------------------------------------------------------
import Data.Array.Base (unsafeRead, unsafeWrite)
import Data.Array.ST
import Control.Monad.ST

myqsort :: STUArray s Int Int -> Int -> Int -> ST s ()
myqsort a lo hi
    | lo < hi   = do
        let lscan p h i
                | i < h = do
                    v <- unsafeRead a i
                    if p < v then return i else lscan p h (i+1)
                | otherwise = return i
            rscan p l i
                | l < i = do
                    v <- unsafeRead a i
                    if v < p then return i else rscan p l (i-1)
                | otherwise = return i
            swap i j = do
                v <- unsafeRead a i
                unsafeRead a j >>= unsafeWrite a i
                unsafeWrite a j v
            sloop p l h
                | l < h = do
                    l1 <- lscan p h l
                    h1 <- rscan p l1 h
                    if (l1 < h1) then (swap l1 h1 >> sloop p l1 h1) else return l1
                | otherwise = return l
        piv <- unsafeRead a hi
        i <- sloop piv lo hi
        swap i hi
        myqsort a lo (i-1)
        myqsort a (i+1) hi
    | otherwise = return ()
----------------------------------------------------------------------------------------

doesn't sacrifice performance for polymorphism (the C code isn't polymorphic either) - in 
my tests, it took less than twice the time the C code took to sort the same array, not too 
bad.

It compiles as is, and if it satisfies readability requirements, somebody can put it on 
the wiki.

>
> It is often claimed that compiler technology will make it possible to
> compile high level code into efficient low level code that is almost as
> efficient as the C or asm routines. How does this apply to qsort today?

If you give it a chance to optimise, it isn't too bad.
The code from the wiki takes about three times as long as the code above,
** if it's compiled
a) with -O2 and
b) in a setting where it specialises to the appropriate unboxed array type, be it by 
giving {-# SPECIALISE #-} pragmas or by having the code in the same module as the use 
(with a good type, e.g. STUArray s Int Int) **.

If you disable optimisations by requiring fully polymorphic code and only that, the factor 
is about 80.

>
> Cheers,
> Peter Verswyvelen



More information about the Haskell-Cafe mailing list