Re: [Haskell-cafe] k-minima in Haskell

2007-04-16 Thread Ronny Wichers Schreur

Yitz writes (in the Haskell Cafe):


This gives O(log k * (n + k)) execution in constant memory.


I guess that should be O(k) memory.


Cheers,

Ronny Wichers Schreur
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] k-minima in Haskell

2007-04-14 Thread ajb
G'day all.

I wrote:

O(log(n! / (n-k)!))
  = O(n log n - (n-k) log (n-k))
  = O(n log (n/(n-k)) + k log (n-k))
 
  That looks right to me.  If k  n, then this simplifies to
  O(n + k log n), and if k is close to n, it simplifies to
  O(n log n + k).

Quoting Ian Lynagh [EMAIL PROTECTED]:

 Hmm, is something wrong with the following?:
[...]
 Total: O(n + k log k)

The problem with with my simplifications. :-)

But as an exercise, prove:

   O(n log (n/(n-k)) + k log (n-k)) = O(n + k log k)

Cheers,
Andrew Bromage
___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] k-minima in Haskell

2007-04-13 Thread Thomas Hartman

 You may be missing a few recursive calls there :-)

Indeed.


I'm confused.

Is this a legitimate stable quicksort, or not? (My guess is, it is
indeed legit as written.)

This was also the first I have heard of stability as a sort property.

http://perldoc.perl.org/sort.html may shed some light on this...

A stable sort means that for records that compare equal, the original
input ordering is preserved. Mergesort is stable, quicksort is not. 

Is this description a fair characterization of stability for the
current discussion?

I'm a bit confused but if I understand correctly sort from the prelude
is non stable quicksort, which has O(k n^2) as the worst case, whereas
stable quicksort has O( k* log n + n).

non-stable quicksort is just sort from the prelude:

qsort [] = []
qsort (x:xs) = qsort (filter ( x) xs) ++ [x] ++ qsort (filter (= x) xs)

If any in the above was incorrect, please holler.

2007/4/12, Stefan O'Rear [EMAIL PROTECTED]:

On Wed, Apr 11, 2007 at 09:20:12PM -0700, Tim Chevalier wrote:
 On 4/11/07, Stefan O'Rear [EMAIL PROTECTED] wrote:
 
 If you want to be really explicit about it, here is a sort that will
 work:
 
 sort [] = []
 sort l@(x:_) = filter (x) l ++ filter (==x) l ++ filter (x) l
 
 (A stable quicksort, btw)

 You may be missing a few recursive calls there :-)

Indeed.

Stefan
___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe


___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] k-minima in Haskell

2007-04-13 Thread Thomas Hartman

And for reference, here is again stefan's stable quicksort from his
earlier post.


sort [] = []
sort l@(x:_) = filter (x) l ++ filter (==x) l ++ filter (x) l

(A stable quicksort, btw)


This is the code whose legitimacy I am requesting confirmation of.

2007/4/13, Thomas Hartman [EMAIL PROTECTED]:

  You may be missing a few recursive calls there :-)

 Indeed.

I'm confused.

Is this a legitimate stable quicksort, or not? (My guess is, it is
indeed legit as written.)

This was also the first I have heard of stability as a sort property.

http://perldoc.perl.org/sort.html may shed some light on this...

A stable sort means that for records that compare equal, the original
input ordering is preserved. Mergesort is stable, quicksort is not. 

Is this description a fair characterization of stability for the
current discussion?

I'm a bit confused but if I understand correctly sort from the prelude
is non stable quicksort, which has O(k n^2) as the worst case, whereas
stable quicksort has O( k* log n + n).

non-stable quicksort is just sort from the prelude:

qsort [] = []
qsort (x:xs) = qsort (filter ( x) xs) ++ [x] ++ qsort (filter (= x) xs)

If any in the above was incorrect, please holler.

2007/4/12, Stefan O'Rear [EMAIL PROTECTED]:
 On Wed, Apr 11, 2007 at 09:20:12PM -0700, Tim Chevalier wrote:
  On 4/11/07, Stefan O'Rear [EMAIL PROTECTED] wrote:
  
  If you want to be really explicit about it, here is a sort that will
  work:
  
  sort [] = []
  sort l@(x:_) = filter (x) l ++ filter (==x) l ++ filter (x) l
  
  (A stable quicksort, btw)
 
  You may be missing a few recursive calls there :-)

 Indeed.

 Stefan
 ___
 Haskell-Cafe mailing list
 [EMAIL PROTECTED]
 http://www.haskell.org/mailman/listinfo/haskell-cafe



___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] k-minima in Haskell

2007-04-13 Thread Thomas Hartman

Trying to understand this better I also came across

http://groups.google.de/group/fa.haskell/browse_thread/thread/1345c49faff85926/8f675bd2aeaa02ba?lnk=stq=%22I+assume+that+you+want+to+find+the+k%27th+smallest+element%22rnum=1hl=en#8f675bd2aeaa02ba

where apfulmus gives an implementation of mergesort, which he claims

runs in O(n) time instead of the expected O(n log n)

Does that mean you can have the k minima in O(n) time, where n is
length of list, which would seem to be an improvement?

 mergesort []  = []
 mergesort xs  = foldtree1 merge $ map return xs

 foldtree1 f [x] = x
 foldtree1 f xs  = foldtree1 f $ pairs xs
where
pairs []= []
pairs [x]   = [x]
pairs (x:x':xs) = f x x' : pairs xs

 merge [] ys = ys
 merge xs [] = xs
 merge (x:xs) (y:ys) =
 if x = y then x:merge xs (y:ys) else y:merge (x:xs) ys


2007/4/13, Thomas Hartman [EMAIL PROTECTED]:

And for reference, here is again stefan's stable quicksort from his
earlier post.


sort [] = []
sort l@(x:_) = filter (x) l ++ filter (==x) l ++ filter (x) l

(A stable quicksort, btw)


This is the code whose legitimacy I am requesting confirmation of.

2007/4/13, Thomas Hartman [EMAIL PROTECTED]:
   You may be missing a few recursive calls there :-)
 
  Indeed.

 I'm confused.

 Is this a legitimate stable quicksort, or not? (My guess is, it is
 indeed legit as written.)

 This was also the first I have heard of stability as a sort property.

 http://perldoc.perl.org/sort.html may shed some light on this...

 A stable sort means that for records that compare equal, the original
 input ordering is preserved. Mergesort is stable, quicksort is not. 

 Is this description a fair characterization of stability for the
 current discussion?

 I'm a bit confused but if I understand correctly sort from the prelude
 is non stable quicksort, which has O(k n^2) as the worst case, whereas
 stable quicksort has O( k* log n + n).

 non-stable quicksort is just sort from the prelude:

 qsort [] = []
 qsort (x:xs) = qsort (filter ( x) xs) ++ [x] ++ qsort (filter (= x) xs)

 If any in the above was incorrect, please holler.

 2007/4/12, Stefan O'Rear [EMAIL PROTECTED]:
  On Wed, Apr 11, 2007 at 09:20:12PM -0700, Tim Chevalier wrote:
   On 4/11/07, Stefan O'Rear [EMAIL PROTECTED] wrote:
   
   If you want to be really explicit about it, here is a sort that will
   work:
   
   sort [] = []
   sort l@(x:_) = filter (x) l ++ filter (==x) l ++ filter (x) l
   
   (A stable quicksort, btw)
  
   You may be missing a few recursive calls there :-)
 
  Indeed.
 
  Stefan
  ___
  Haskell-Cafe mailing list
  [EMAIL PROTECTED]
  http://www.haskell.org/mailman/listinfo/haskell-cafe
 



___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] k-minima in Haskell

2007-04-13 Thread Thomas Hartman

Rereading this, I see in fact apfelmus explains this is

O(n + k*log n) for the first k elements, which this discussion also
maintains is the best case. So, there's no discrepancy.

I think this is a very valuable post to read for the explanation.

2007/4/13, Thomas Hartman [EMAIL PROTECTED]:

Trying to understand this better I also came across

http://groups.google.de/group/fa.haskell/browse_thread/thread/1345c49faff85926/8f675bd2aeaa02ba?lnk=stq=%22I+assume+that+you+want+to+find+the+k%27th+smallest+element%22rnum=1hl=en#8f675bd2aeaa02ba

where apfulmus gives an implementation of mergesort, which he claims

runs in O(n) time instead of the expected O(n log n)

Does that mean you can have the k minima in O(n) time, where n is
length of list, which would seem to be an improvement?

  mergesort []  = []
  mergesort xs  = foldtree1 merge $ map return xs

  foldtree1 f [x] = x
  foldtree1 f xs  = foldtree1 f $ pairs xs
 where
 pairs []= []
 pairs [x]   = [x]
 pairs (x:x':xs) = f x x' : pairs xs

  merge [] ys = ys
  merge xs [] = xs
  merge (x:xs) (y:ys) =
  if x = y then x:merge xs (y:ys) else y:merge (x:xs) ys


2007/4/13, Thomas Hartman [EMAIL PROTECTED]:
 And for reference, here is again stefan's stable quicksort from his
 earlier post.

 
 sort [] = []
 sort l@(x:_) = filter (x) l ++ filter (==x) l ++ filter (x) l

 (A stable quicksort, btw)
 

 This is the code whose legitimacy I am requesting confirmation of.

 2007/4/13, Thomas Hartman [EMAIL PROTECTED]:
You may be missing a few recursive calls there :-)
  
   Indeed.
 
  I'm confused.
 
  Is this a legitimate stable quicksort, or not? (My guess is, it is
  indeed legit as written.)
 
  This was also the first I have heard of stability as a sort property.
 
  http://perldoc.perl.org/sort.html may shed some light on this...
 
  A stable sort means that for records that compare equal, the original
  input ordering is preserved. Mergesort is stable, quicksort is not. 
 
  Is this description a fair characterization of stability for the
  current discussion?
 
  I'm a bit confused but if I understand correctly sort from the prelude
  is non stable quicksort, which has O(k n^2) as the worst case, whereas
  stable quicksort has O( k* log n + n).
 
  non-stable quicksort is just sort from the prelude:
 
  qsort [] = []
  qsort (x:xs) = qsort (filter ( x) xs) ++ [x] ++ qsort (filter (= x) xs)
 
  If any in the above was incorrect, please holler.
 
  2007/4/12, Stefan O'Rear [EMAIL PROTECTED]:
   On Wed, Apr 11, 2007 at 09:20:12PM -0700, Tim Chevalier wrote:
On 4/11/07, Stefan O'Rear [EMAIL PROTECTED] wrote:

If you want to be really explicit about it, here is a sort that will
work:

sort [] = []
sort l@(x:_) = filter (x) l ++ filter (==x) l ++ filter (x) l

(A stable quicksort, btw)
   
You may be missing a few recursive calls there :-)
  
   Indeed.
  
   Stefan
   ___
   Haskell-Cafe mailing list
   [EMAIL PROTECTED]
   http://www.haskell.org/mailman/listinfo/haskell-cafe
  
 



___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] k-minima in Haskell

2007-04-13 Thread ajb
G'day all.

Quoting Thomas Hartman [EMAIL PROTECTED]:

 Does that mean you can have the k minima in O(n) time, where n is
 length of list, which would seem to be an improvement?

It's worth considering what the theoretical minimum is.

You have n elements, and you need to locate a specific k-element
permutation.  There are n! / (n-k)! such permutations.  You therefore
need log(n! / (n-k)!) bits of information.

A binary comparison provides one bit of information.  So the number of
comparisons that you need to get that much information is:

  O(log(n! / (n-k)!))
= O(n log n - (n-k) log (n-k))
= O(n log (n/(n-k)) + k log (n-k))

That looks right to me.  If k  n, then this simplifies to
O(n + k log n), and if k is close to n, it simplifies to
O(n log n + k).

Cheers,
Andrew Bromage
___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] k-minima in Haskell

2007-04-13 Thread Thorkil Naur
Hello,

My Hugs tells me this:

Prelude let sort [] = []; sort l@(x:_) = filter (x) l ++ filter (==x) l ++ 
filter (x) l in sort [1,3,2]
[1,3,2]
Prelude

So, no, this is not a working sorting function. Inserting the few missing 
recursive calls:

Prelude let sort [] = []; sort l@(x:_) = sort ( filter (x) l ) ++ filter 
(==x) l ++ sort ( filter (x) l ) in sort [1,3,2]
[1,2,3]
Prelude

Best regards
Thorkil
On Friday 13 April 2007 11:38, Thomas Hartman wrote:
 And for reference, here is again stefan's stable quicksort from his
 earlier post.
 
 
 sort [] = []
 sort l@(x:_) = filter (x) l ++ filter (==x) l ++ filter (x) l
 
 (A stable quicksort, btw)
 
 
 This is the code whose legitimacy I am requesting confirmation of.
 
 2007/4/13, Thomas Hartman [EMAIL PROTECTED]:
You may be missing a few recursive calls there :-)
  
   Indeed.
 
 ...
___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] k-minima in Haskell

2007-04-13 Thread Ian Lynagh
On Fri, Apr 13, 2007 at 07:32:20AM -0400, [EMAIL PROTECTED] wrote:
 
 Quoting Thomas Hartman [EMAIL PROTECTED]:
 
  Does that mean you can have the k minima in O(n) time, where n is
  length of list, which would seem to be an improvement?
 
 It's worth considering what the theoretical minimum is.
 
 You have n elements, and you need to locate a specific k-element
 permutation.  There are n! / (n-k)! such permutations.  You therefore
 need log(n! / (n-k)!) bits of information.
 
 A binary comparison provides one bit of information.  So the number of
 comparisons that you need to get that much information is:
 
   O(log(n! / (n-k)!))
 = O(n log n - (n-k) log (n-k))
 = O(n log (n/(n-k)) + k log (n-k))
 
 That looks right to me.  If k  n, then this simplifies to
 O(n + k log n), and if k is close to n, it simplifies to
 O(n log n + k).

Hmm, is something wrong with the following?:

Tuple each element with its position: O(n)
Find kth smallest element in linear time, as per [1]: O(n)
Filter list for elements = kth smallest: O(n)
Sort filtered list by position:   O(k log k)
map snd to get the positions: O(k)

Total: O(n + k log k)

(the filter step will take care of elements with the same value as the
kth smallest, as the filter is also comparing element positions when the
values are the same).


Thanks
Ian

[1] http://en.wikipedia.org/wiki/Selection_algorithm

___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] k-minima in Haskell

2007-04-13 Thread Colin DeVilbiss

On 4/13/07, Ian Lynagh [EMAIL PROTECTED] wrote:


Tuple each element with its position: O(n)
Find kth smallest element in linear time, as per [1]: O(n)
Filter list for elements = kth smallest: O(n)
Sort filtered list by position:   O(k log k)
map snd to get the positions: O(k)

Total: O(n + k log k)

[1] http://en.wikipedia.org/wiki/Selection_algorithm


Inspired by the above, I thought I'd see about writing it.

Note that attaching the indices prevents equal items from
comparing equal.  I didn't feel like writing the code for a
special data type that ignored a second element for the
purposes of comparisons; that just means replacing
zip and map send.

The user can add stability by selective use of reverse
within the continuation functions.

There should probably be strictness annotations somewhere,
and calls to length should probably be accumulated in
partition instead, but the idea should be sound (except for
the likelihood of a bad pivot).

partition cont _ [] lt eq gt = cont lt eq gt
partition cont p (x:xs) lt eq gt = case x `compare` p of
 LT - partition cont p xs (x:lt) eq gt
 EQ - partition cont p xs lt (x:eq) gt
 GT - partition cont p xs lt eq (x:gt)

qsort [] = []
qsort (x:xs) = partition qs' x xs [] [x] []
 where qs' lt eq gt = qsort lt ++ (eq ++ qsort gt)

findfirst _ [] = []
findfirst k (x:xs) = partition ff' x xs [] [x] []
 where
   ff' lt eq gt = let { ll = length lt; lle = ll + length eq }
  in  if k  ll   then findfirst k lt
  else if k  lle then lt ++ eq ++ findfirst (k - lle) gt
   elselt ++ take (k - ll) eq

getSmallest k = qsort . findfirst k
getSmallestIndices k = map snd . getSmallest k . flip zip [0..]
___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] k-minima in Haskell

2007-04-12 Thread ajb
G'day all.

Quoting raghu vardhan [EMAIL PROTECTED]:

 So, any algorithm that sorts is no good (think of n as huge, and k small).

The essence of all the answers that you've received is that it doesn't
matter if k is small, sorting is still the most elegant answer in Haskell.

The reason is that in Haskell, a function which sort function will produce the
sorted
list lazily.  If you don't demand the while list, you don't perform
the whole sort.

Some algorithms are better than others for minimising the amount of
work if not all of the list is demanded, but ideally, producing the
first k elements will take O(n log k + k) time.

Cheers,
Andrew Bromage
___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] k-minima in Haskell

2007-04-12 Thread Nicolas Frisby

[sorry for the double, ajb]

Since there seemed to be a disconnect between the expectation and
the previous answers, I thought an alternative suggestion might help
out. This sort of thing (haha) usually isn't my cup o' tea, so please
point out any blunders.

RM, is this more like what you had in mind? It leans more towards an
iterative approach. If so, I encourage you to compare this to the
other solutions and try understand how those solutions rely upon
laziness. Stefan and Andrew, feel free to point out the drawbacks to
this approach that I'm probably overlooking.


kminima n l = map fst (foldr insert' (List.sort pre) suf)
   where (pre, suf) = (splitAt n . zip [0..]) l

-- I think this insertion sort could be
-- O(log k) with a better data structure.
insert' x [] = []
insert' x (y : ys) | snd x  snd y = x : y : dropLast ys'
  | otherwise = y : insert' x ys
   where dropLast ys = take (length ys - 1) ys

We grab the first k elements and sort them, this list is our first
approximation to the k-minima. We then process the rest of the list,
checking if the current element is smaller than any of the minima of
the current approximation. If the current element is smaller, we
improve the current approximation by inserting the new element and
dropping the biggest (i.e. last) minimum from the minima accumulator.

The worst behavior is: sort(k) + (n-k) * k comparisons. This could be
improved (to: sort(k) + (n-k) * log k comparisons, I think) with a
better data structure for the minima approximation.

On 4/12/07, [EMAIL PROTECTED] [EMAIL PROTECTED] wrote:

G'day all.

Quoting raghu vardhan [EMAIL PROTECTED]:

 So, any algorithm that sorts is no good (think of n as huge, and k small).

The essence of all the answers that you've received is that it doesn't
matter if k is small, sorting is still the most elegant answer in Haskell.

The reason is that in Haskell, a function which sort function will produce the
sorted
list lazily.  If you don't demand the while list, you don't perform
the whole sort.

Some algorithms are better than others for minimising the amount of
work if not all of the list is demanded, but ideally, producing the
first k elements will take O(n log k + k) time.

Cheers,
Andrew Bromage
___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe


___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] k-minima in Haskell

2007-04-12 Thread Dino Morelli

On Thu, 12 Apr 2007, raghu vardhan wrote:



What's the best way to implement the following function in haskell:
Given a list and an integer k as input return the indices of the least k
elements in the list. The code should be elegant and also, more importantly, 
must not make more than the minimum O(k*length(list)) number of operations.

R M




I don't know about performance, but trying this problem I was struck
again by the gorgeous, terse code that can be created:


import Data.List
import Data.Ord

kminima :: (Enum a, Num a, Ord b) = Int - [b] - [a]
kminima k lst = take k $ map fst $ sortBy (comparing snd) $ zip [0 ..] lst


commented:

   kminima k lst =
  take k -- We want k items off the front
  $ map fst  -- Just the list of indices
  $ sortBy (comparing snd)   -- Sort the pairs by their snd
  $ zip [0 ..] lst   -- Preserve indices in tuples


Prelude :l kminima.hs
[1 of 1] Compiling Main ( kminima.lhs, interpreted )
Ok, modules loaded: Main.
*Main kminima 3 [71,71,17,14,16,91,18,71,58,75,65,79,76,18,4,45,87,51,93,36]
[14,3,4]
*Main kminima 4 [10,9,8,7,6,5,4,3,2,1]
[9,8,7,6]


--
 .~.Dino Morelli
 /V\email: [EMAIL PROTECTED]
/( )\   irc: dino-
^^-^^   preferred distro: Debian GNU/Linux  http://www.debian.org
___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] k-minima in Haskell

2007-04-12 Thread Kurt Hutchinson

On 4/12/07, [EMAIL PROTECTED] [EMAIL PROTECTED] wrote:

To get the indices, use the Schwartzian transform:

sortWith :: (Ord b) = (a - b) - [a] - [a]
sortWith f = mergeRuns . runs
  where
runs = map (:[])

mergeRuns [] = []
mergeRuns [xs] = xs
mergeRuns xss = mergeRuns (mergeRun xss)

mergeRun (xs1:xs2:xss) = mergeOne xs1 xs2 : mergeRun xss
mergeRun xss = xss

mergeOne [] ys = ys
mergeOne xs [] = xs
mergeOne xs'@(x:xs) ys':(y:ys)
= case compare (f x) (f y) of
LT - x : mergeOne xs ys'
GT - y : mergeOne xs' ys
EQ - x : y : mergeOne xs ys

getKMinima :: (Ord a) = [a] - [Int]
getKMinima k = map fst . take k . sortWith snd . zip [0..]


For my own edification, what is the benefit of this sortWith over sortBy?

f `on` g = \ x y - f ( g x ) ( g y )
kminima k = map fst . take k . sortBy ( compare `on` snd ) . zip [0..]
___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] k-minima in Haskell

2007-04-12 Thread Vincent Kraeutler
Kurt Hutchinson wrote:
 On 4/12/07, [EMAIL PROTECTED] [EMAIL PROTECTED] wrote:
 To get the indices, use the Schwartzian transform:

 sortWith :: (Ord b) = (a - b) - [a] - [a]
 sortWith f = mergeRuns . runs
   where
 runs = map (:[])

 mergeRuns [] = []
 mergeRuns [xs] = xs
 mergeRuns xss = mergeRuns (mergeRun xss)

 mergeRun (xs1:xs2:xss) = mergeOne xs1 xs2 : mergeRun xss
 mergeRun xss = xss

 mergeOne [] ys = ys
 mergeOne xs [] = xs
 mergeOne xs'@(x:xs) ys':(y:ys)
 = case compare (f x) (f y) of
 LT - x : mergeOne xs ys'
 GT - y : mergeOne xs' ys
 EQ - x : y : mergeOne xs ys

 getKMinima :: (Ord a) = [a] - [Int]
 getKMinima k = map fst . take k . sortWith snd . zip [0..]

 For my own edification, what is the benefit of this sortWith over sortBy?

 f `on` g = \ x y - f ( g x ) ( g y )
 kminima k = map fst . take k . sortBy ( compare `on` snd ) . zip [0..]


possibly related (newbie question):

pairs are instances of Ord, why not directly sort those (implying the
item to be sorted is fst):

 kminima k = \list - map snd $ take k $ sort $ zip list [0..]





signature.asc
Description: OpenPGP digital signature
___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] k-minima in Haskell

2007-04-12 Thread R M

 The link pretty much answers my question, though you probably require a
little bit more book keeping to get the indices out. Compared to the
iterative version or the matlab version, this definitely is more elegant,
but also is trickier. 


apfelmus wrote:
 
 raghu vardhan [EMAIL PROTECTED]:
 So, any algorithm that sorts is no good (think of n as huge, and k
 small).
 
 With lazy evaluation, it is!
 
   http://article.gmane.org/gmane.comp.lang.haskell.general/15010
 
 
 [EMAIL PROTECTED] wrote:
 The essence of all the answers that you've received is that it doesn't
 matter if k is small, sorting is still the most elegant answer in
 Haskell.
 
 (It's not only most elegant, it can even be put to work.)
 
 The reason is that in Haskell, a function which sort function will
 produce the
 sorted list lazily. If you don't demand the while list, you don't perform
 the whole sort.
 
 Some algorithms are better than others for minimising the amount of
 work if not all of the list is demanded, but ideally, producing the
 first k elements will take O(n log k + k) time.
 
 You mean O(k * log n + n) of course.
 
 Regards,
 apfelmus
 
 ___
 Haskell-Cafe mailing list
 [EMAIL PROTECTED]
 http://www.haskell.org/mailman/listinfo/haskell-cafe
 
 

-- 
View this message in context: 
http://www.nabble.com/k-minima-in-Haskell-tf3563220.html#a9964572
Sent from the Haskell - Haskell-Cafe mailing list archive at Nabble.com.

___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] k-minima in Haskell

2007-04-12 Thread Yitzchak Gale

\begin{code}

kmin :: Ord a = Int - [a] - [Int]
kmin k x = map snd $ Set.toList $ foldl' insertIfSmall (Set.fromList h) t
 where
   (h, t) = splitAt k $ zip x [0..]

insertIfSmall :: Ord a = Set.Set a - a - Set.Set a
insertIfSmall s e
| e  mx= Set.insert e s'
| otherwise = s
where
  (mx, s') = Set.deleteFindMax s

\end{code}

This gives O(log k * (n + k)) execution in constant memory.
If you need the result indices to be in order, you can put in
a sort at the end without changing the complexity.

This could be improved by a significant constant factor
by using a priority queue instead of Set. Any Edison people
out there?

Regards,
Yitz
___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] k-minima in Haskell

2007-04-12 Thread Yitzchak Gale

\begin{code}

kmin :: Ord a = Int - [a] - [Int]
kmin k x = map snd $ Set.toList $ foldl' insertIfSmall (Set.fromList h) t
 where
   (h, t) = splitAt k $ zip x [0..]

insertIfSmall :: Ord a = Set.Set a - a - Set.Set a
insertIfSmall s e
| e  mx= Set.insert e s'
| otherwise = s
where
  (mx, s') = Set.deleteFindMax s

\end{code}

This gives O(log k * (n + k)) execution in constant memory.
If you need the result indices to be in order, you can put in
a sort at the end without changing the complexity.

This could be improved by a significant constant factor
by using a priority queue instead of Set. Any Edison people
out there?

Regards,
Yitz
___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] k-minima in Haskell

2007-04-12 Thread ajb
G'day all.

Quoting Kurt Hutchinson [EMAIL PROTECTED]:

 For my own edification, what is the benefit of this sortWith over sortBy?

None.  I wanted to write my own sort, illustrating how the lazy
evaluation thing works, and I didn't want a name clash with an
existing library function.

Cheers,
Andrew Bromage
___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] k-minima in Haskell

2007-04-11 Thread raghu vardhan

What's the best way to implement the following function in haskell:
Given a list and an integer k as input return the indices of the least k
elements in the list. The code should be elegant and also, more importantly, 
must not make more than the minimum O(k*length(list)) number of operations.

R M




  Send a FREE SMS to your friend's mobile from Yahoo! Messenger. Get it now 
at http://in.messenger.yahoo.com/___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] k-minima in Haskell

2007-04-11 Thread Donald Bruce Stewart
mrvr84:
 
What's the best way to implement the following function in
haskell: Given a list and an integer k as input return the
indices of the least k elements in the list. The code should
be elegant and also, more importantly, must not make more
than the minimum O(k*length(list)) number of operations.
R M

Is this a homework question?

-- Don
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] k-minima in Haskell

2007-04-11 Thread Stefan O'Rear
On Thu, Apr 12, 2007 at 08:58:33AM +0530, raghu vardhan wrote:
 What's the best way to implement the following function in haskell:
 Given a list and an integer k as input return the indices of the least
 k elements in the list. The code should be elegant and also, more
 importantly, must not make more than the minimum O(k*length(list))
 number of operations. 

Go read and thoroughly understand Why Functional Programming
Matters.

Also, your asyptotic complexity bound is just plain wrong.  I'd give
faster code, but Don is suspicious (and I can never tell these things
myself).

Stefan
___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] k-minima in Haskell

2007-04-11 Thread Stefan O'Rear
On Wed, Apr 11, 2007 at 08:38:48PM -0700, Stefan O'Rear wrote:
 On Thu, Apr 12, 2007 at 08:58:33AM +0530, raghu vardhan wrote:
  What's the best way to implement the following function in haskell:
  Given a list and an integer k as input return the indices of the least
  k elements in the list. The code should be elegant and also, more
  importantly, must not make more than the minimum O(k*length(list))
  number of operations. 
 
 Go read and thoroughly understand Why Functional Programming
 Matters.
 
 Also, your asyptotic complexity bound is just plain wrong.  I'd give
 faster code, but Don is suspicious (and I can never tell these things
 myself).
 
 Stefan

Don tells me (in #haskell) that you are legitimate, so here is the
example:

kminima k lst = take k $ sort lst

If you want to be really explicit about it, here is a sort that will
work:

sort [] = []
sort l@(x:_) = filter (x) l ++ filter (==x) l ++ filter (x) l

(A stable quicksort, btw)

Note that this is FASTER than your bound - somewhere between O(n) and
O(n*log n).

Ain't lazy evaluation great? :)

Stefan
___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] k-minima in Haskell

2007-04-11 Thread Stefan O'Rear
On Wed, Apr 11, 2007 at 09:20:12PM -0700, Tim Chevalier wrote:
 On 4/11/07, Stefan O'Rear [EMAIL PROTECTED] wrote:
 
 If you want to be really explicit about it, here is a sort that will
 work:
 
 sort [] = []
 sort l@(x:_) = filter (x) l ++ filter (==x) l ++ filter (x) l
 
 (A stable quicksort, btw)
 
 You may be missing a few recursive calls there :-)

Indeed.

Stefan
___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] k-minima in Haskell

2007-04-11 Thread raghu vardhan
And just to remind people, the question is to find the indices and not
the numbers themselves. For example on input '3, [10,9,8,..., 3,2,1]'
the output must be '[9,8,7]'. 

- Original Message 
From: Stefan O'Rear [EMAIL PROTECTED]
To: raghu vardhan [EMAIL PROTECTED]
Sent: Wednesday, 11 April, 2007 11:17:15 PM
Subject: Re: [Haskell-cafe] k-minima in Haskell

On Thu, Apr 12, 2007 at 09:30:22AM +0530, raghu vardhan wrote:
 Hmmm.  That's not something I was looking for. I'm not sure the
 running time is good enough (think of k as being 2 - then you should
 not make more than 2n comparisons) - even with lazy evaluation,
 quick sort won't have a bound of O(k*n). 

Muahahahaha!
Muahahahahahahahahahaha!
Muahaha!

Actually it DOES.

(this list courtesy of a ghci one-liner)

find the 3 minima of 
[71,71,17,14,16,91,18,71,58,75,65,79,76,18,4,45,87,51,93,36]



take 3 (sort [71,71,17,14,16,91,18,71,58,75,65,79,76,18,4,45,87,51,93,36])



take 3 (sort (filter (71) 
[71,71,17,14,16,91,18,71,58,75,65,79,76,18,4,45,87,51,93,36]) ++ a bunch of 
stuff I won't track because it won't be evaluated)

  (comparisons so far: 20)

take 3 (sort [17, 14, 16, 18, 58, 65, 18, 4, 45, 51, 36])

take 3 (sort (filter (17) [17, 14, 16, 18, 58, 65, 18, 4, 45, 51, 36]) ++ 
filter (==17) [17, 14, 16, 18, 58, 65, 18, 4, 45, 51, 36] ++
sort (filter (17) [17, 14, 16, 18, 58, 65, 18, 4, 45, 51, 36]))

 (31)

take 3 (sort [14, 16, 18, 4] ++ 
filter (==17) [17, 14, 16, 18, 58, 65, 18, 4, 45, 51, 36] ++
sort (filter (17) [17, 14, 16, 18, 58, 65, 18, 4, 45, 51, 36]))

take 3 (sort (filter (14) [14, 16, 18, 4]) ++ sort (filter (==14) [14, 16, 18, 
4]) ++ sort (filter (14) [14, 16, 18, 4]) ++ 
filter (==17) [17, 14, 16, 18, 58, 65, 18, 4, 45, 51, 36] ++
sort (filter (17) [17, 14, 16, 18, 58, 65, 18, 4, 45, 51, 36]))

 (39)

take 3 (sort [4] ++ sort [14] ++ sort (filter (14) [14, 16, 18, 4]) ++ 
filter (==17) [17, 14, 16, 18, 58, 65, 18, 4, 45, 51, 36] ++
sort (filter (17) [17, 14, 16, 18, 58, 65, 18, 4, 45, 51, 36]))

take 3 (4 : 14 : sort (filter (14) [14, 16, 18, 4]) ++ 
filter (==17) [17, 14, 16, 18, 58, 65, 18, 4, 45, 51, 36] ++
sort (filter (17) [17, 14, 16, 18, 58, 65, 18, 4, 45, 51, 36]))

4 : 14 : take 1 (sort (filter (14) [14, 16, 18, 4]) ++ 
filter (==17) [17, 14, 16, 18, 58, 65, 18, 4, 45, 51, 36] ++
sort (filter (17) [17, 14, 16, 18, 58, 65, 18, 4, 45, 51, 36]))

 (43)

4 : 14 : take 1 (sort [16, 18] ++ 
filter (==17) [17, 14, 16, 18, 58, 65, 18, 4, 45, 51, 36] ++
sort (filter (17) [17, 14, 16, 18, 58, 65, 18, 4, 45, 51, 36]))

 (47)

[4, 14, 16]

47 close enough to O(n*k) for you?  (remember this is quicksort we are
dealing with, O(n^2) worst case)

Stefan







  Send a FREE SMS to your friend's mobile from Yahoo! Messenger. Get it now 
at http://in.messenger.yahoo.com/___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] k-minima in Haskell

2007-04-11 Thread ajb
G'day all.

Quoting raghu vardhan [EMAIL PROTECTED]:

 What's the best way to implement the following function in haskell:
 Given a list and an integer k as input return the indices of the least k
 elements in the list. The code should be elegant and also, more importantly,
 must not make more than the minimum O(k*length(list)) number of operations.

Pretty much like everyone has says, although it's best to use a real
lazy O(n log n) sort, not quicksort-with-dumbest-pivot.  To get the
indices, use the Schwartzian transform:

sortWith :: (Ord b) = (a - b) - [a] - [a]
sortWith f = mergeRuns . runs
  where
runs = map (:[])

mergeRuns [] = []
mergeRuns [xs] = xs
mergeRuns xss = mergeRuns (mergeRun xss)

mergeRun (xs1:xs2:xss) = mergeOne xs1 xs2 : mergeRun xss
mergeRun xss = xss

mergeOne [] ys = ys
mergeOne xs [] = xs
mergeOne xs'@(x:xs) ys':(y:ys)
= case compare (f x) (f y) of
LT - x : mergeOne xs ys'
GT - y : mergeOne xs' ys
EQ - x : y : mergeOne xs ys

getKMinima :: (Ord a) = [a] - [Int]
getKMinima k = map fst . take k . sortWith snd . zip [0..]

Cheers,
Andrew Bromage
___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] k-minima in Haskell

2007-04-11 Thread raghu vardhan

There seems to be some confusion about the question. There are two key things 
to keep in mind here:
1) You must make at most O(k*n) comparisons (in the worst case) if the list has 
length n.
2) The output must be the indices and not the numbers themselves. 

So, any algorithm that sorts is no good (think of n as huge, and k small). 
Another interesting caveat to this is that if k=2, you can actually solve the 
problem with just (n+log n) comparisons in worst case(instead of 2*n, that you 
get by a naive approach), and it's a nice exercise to do this.

As a further clarification, this is not a homework question. I genereally do 
whatever programming I do in Matlab, as I work with matrices (huge ones) and 
use this function a lot. I just wanted to see how different an implementation 
you can get in Haskell (I am new to Haskell so I might not be able to come up 
with the best way to do this). 

- Original Message 
From: Stefan O'Rear [EMAIL PROTECTED]
To: raghu vardhan [EMAIL PROTECTED]
Cc: [EMAIL PROTECTED]
Sent: Wednesday, 11 April, 2007 10:47:08 PM
Subject: Re: [Haskell-cafe] k-minima in Haskell

On Wed, Apr 11, 2007 at 08:38:48PM -0700, Stefan O'Rear wrote:
 On Thu, Apr 12, 2007 at 08:58:33AM +0530, raghu vardhan wrote:
  What's the best way to implement the following function in haskell:
  Given a list and an integer k as input return the indices of the least
  k elements in the list. The code should be elegant and also, more
  importantly, must not make more than the minimum O(k*length(list))
  number of operations. 
 
 Go read and thoroughly understand Why Functional Programming
 Matters.
 
 Also, your asyptotic complexity bound is just plain wrong.  I'd give
 faster code, but Don is suspicious (and I can never tell these things
 myself).
 
 Stefan

Don tells me (in #haskell) that you are legitimate, so here is the
example:

kminima k lst = take k $ sort lst

If you want to be really explicit about it, here is a sort that will
work:

sort [] = []
sort l@(x:_) = filter (x) l ++ filter (==x) l ++ filter (x) l

(A stable quicksort, btw)

Note that this is FASTER than your bound - somewhere between O(n) and
O(n*log n).

Ain't lazy evaluation great? :)

Stefan







  Send a FREE SMS to your friend's mobile from Yahoo! Messenger. Get it now 
at http://in.messenger.yahoo.com/___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe