llamaro25
llamaro25

Reputation: 692

How to find all minimum elements in a list of tuples?

How can I find all the minimum elements in a list? Right now I have a list of tuples, i.e.

[(10,'a'),(5,'b'),(1,'c'),(8,'d'),(1,'e')]

So I want the output which is all the minimum elements of the list, in a new list. For example

 [(1,'c'),(1,'e')]

I tried

minimumBy (comparing fst) xs

but that only returns the first minimum element.

Upvotes: 9

Views: 1486

Answers (5)

Here's a solution that works in one pass (most other answers here do two passes: one to find the minimum value and one to filter on it), and doesn't rely on how the sorting functions are implemented to be efficient.

{-# LANGUAGE ScopedTypeVariables #-}

import Data.Foldable (foldl')

minimumsBy :: forall a. (a -> a -> Ordering) -> [a] -> [a]
minimumsBy _ [] = []
minimumsBy f (x:xs) = postprocess $ foldl' go (x, id) xs
  where
    go :: (a, [a] -> [a]) -> a -> (a, [a] -> [a])
    go acc@(x, xs) y = case f x y of
      LT -> acc
      EQ -> (x, xs . (y:))
      GT -> (y, id)
    postprocess :: (a, [a] -> [a]) -> [a]
    postprocess (x, xs) = x:xs []

Note that the [a] -> [a] type I'm using here is called a difference list, aka a Hughes list.

Upvotes: 3

developer_hatch
developer_hatch

Reputation: 16224

You can do it easily too with foldr:

minimumsFst :: Ord a => [(a, b)] -> [(a, b)]
minimumsFst xs = go (minfst xs) xs
  where
  go mn ls = foldr (\(x, y) rs -> if (x ==  mn) then (x,y) : rs else rs) [] xs
  minfst ls = minimum (map fst ls)

with your example:

   minimumsFst [(10,'a'),(5,'b'),(1,'c'),(8,'d'),(1,'e')]
=> [(1,'c'),(1,'e')]

Upvotes: 2

Will Ness
Will Ness

Reputation: 71065

You tried

minimumBy (comparing fst) xs

which can also be written as

= head . sortBy (comparing fst) $ xs
= head . sortOn fst $ xs
= head . head . group . sortOn fst $ xs
= head . head . groupBy ((==) `on` fst) . sortOn fst $ xs

This returns just the first element instead of the list of them, so just drop that extra head to get what you want:

=        head . groupBy ((==) `on` fst) . sortOn fst $ xs

Of course having head is no good since it'll error out on the [] input. Instead, we can use the safe option,

= concat . take 1 . groupBy ((==) `on` fst) . sortOn fst $ xs

By the way any solution that calls minimum is also unsafe for the empty input list:

> head []
*** Exception: Prelude.head: empty list

> minimum []
*** Exception: Prelude.minimum: empty list

but takeWhile is safe:

> takeWhile undefined []
[]

edit: thanks to laziness, the overall time complexity of the final version should still be O(n) even in the worst case.

Upvotes: 2

user933161
user933161

Reputation:

Oneliner. The key is sorting.

Prelude Data.List> let a = [(1,'c'),(2,'b'),(1,'w')]
Prelude Data.List> (\xs@((m,_):_) -> takeWhile ((== m) . fst ) xs) . sortOn fst $ a
[(1,'c'),(1,'w')]

Upvotes: 3

willeM_ Van Onsem
willeM_ Van Onsem

Reputation: 476544

After you obtain the minimum of the first value, we can filter the list on these items. Because you here want to retrieve a list of minimum items, we can cover the empty list as well by returning an empty list:

minimumsFst :: Ord a => [(a, b)] -> [(a, b)]
minimumsFst [] = []
minimumsFst xs = filter ((==) minfst . fst) xs
    where minfst = minimum (map fst xs)

For example:

Prelude> minimumsFst [(10,'a'),(5,'b'),(1,'c'),(8,'d'),(1,'e')]
[(1,'c'),(1,'e')]

Upvotes: 7

Related Questions