\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

Reply via email to