Google "median order statistic".
E.g. this is an interesting (and colorful) discussion:
http://ocw.mit.edu/NR/rdonlyres/Electrical-Engineering-and-Computer-Science/6-046JFall-2005/60D030CD-081D-4192-9FB5-C220116E280D/0/lec6.pdf
Toby Hutton wrote:
On Wed, Oct 15, 2008 at 5:44 PM, leledumbo <[EMAIL PROTECTED]> wrote:
module Main where
import Data.List
-- quicksort of any list
qsort [] = []
qsort (x:xs) = qsort(filter(<x) xs) ++ [x] ++ qsort(filter(>=x) xs)
-- optimized quicksort, uses middle element as pivot
qsortOpt [] = []
qsortOpt x = qsortOpt less ++ [pivot] ++ qsortOpt greater
where
pivot = x !! ((length x) `div` 2)
less = filter (<pivot) (delete pivot x)
greater = filter (>=pivot) (delete pivot x)
main = do
putStr "Enter a list: "
l <- readLn
print (qsortOpt l)
-- end of code
I'm curious as to why taking the pivot from the middle is an
'optimized' version. For this to be true you must be making some
assumptions about the contents of the list.
_______________________________________________
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe
_______________________________________________
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe