Skip to content

Commit

Permalink
Add special grouping functions
Browse files Browse the repository at this point in the history
Problem: it is an often need to have a function of
`[(a, b)] -> [(a, [b])]` signature that would group elements by the
first element of the pair, and return the element we grouped by and the
associated second elements of the pairs.

Solution: add this function, and a more generic one that does not
necessarily work with pairs.

Also, we in-parallel work on making `group` function return `NonEmpty`,
not lists, so I implement it via `NonEmpty` here too.

Special thanks to @treeowl for providing elaborate implementations and
advanced variations for special cases.
  • Loading branch information
Martoon-00 committed Apr 23, 2022
1 parent 5c36955 commit 6a3b987
Show file tree
Hide file tree
Showing 2 changed files with 68 additions and 0 deletions.
2 changes: 2 additions & 0 deletions CHANGES.md
Original file line number Diff line number Diff line change
Expand Up @@ -4,6 +4,8 @@ Unreleased
1.7.3
=====

* [#255](https://github.com/serokell/universum/issues/255):
Add `groupByFst` and `groupByKey`.
* [#236](https://github.com/serokell/universum/issues/236):
Add `updateMVar'` and `updateTVar'`.
* [#244](https://github.com/serokell/universum/issues/244)
Expand Down
66 changes: 66 additions & 0 deletions src/Universum/Container/Utils.hs
Original file line number Diff line number Diff line change
@@ -0,0 +1,66 @@
{-# LANGUAGE Trustworthy #-}

-- | Utility functions on top of 'Container' typeclass.

module Universum.Container.Utils
( groupByFst
, groupByKey
, groupByKeyBy
) where

import Data.Function (id, (.))
import Data.List.NonEmpty (NonEmpty (..))

import Universum.Base
import Universum.Container.Class

-- $setup
-- >>> import Data.Function
-- >>> import GHC.Num
-- >>> import Data.Text (toLower)

-- | Variation of 'groupByKey' that accepts the comparison function on keys
-- explicitly.
--
-- Among multiple keys appearing in the same group it will pick the leftmost
-- one as the representer of the equivalence class.
--
-- >>> groupByKeyBy ((==) `on` toLower) id [("A", 1), ("a", 2), ("b", 3)]
-- [("A",1 :| [2]),("b",3 :| [])]
groupByKeyBy
:: Container t
=> (k -> k -> Bool) -> (Element t -> (k, v)) -> t -> [(k, NonEmpty v)]
groupByKeyBy kcmp split = start . toList
where
start [] = []
start (a : as)
| (k, v) <- split a
, let (ys, zs) = go k as
= (k, v :| ys) : zs

go _ [] = ([], [])
go ko (a : as)
| (kn, v) <- split a
= if ko `kcmp` kn
then let (vs, ws) = go ko as
in (v : vs, ws)
else let (vs, ws) = go kn as
in ([], (kn, v :| vs) : ws)

-- | Operates like 'groupByFst', but uses the provided getters
-- for the key to group by and the value.
--
-- >>> groupByKey (\x -> (x `mod` 5, x)) [1, 6, 7, 2, 12, 11]
-- [(1,1 :| [6]),(2,7 :| [2,12]),(1,11 :| [])]
groupByKey
:: (Container t, Eq k)
=> (Element t -> (k, v)) -> t -> [(k, NonEmpty v)]
groupByKey = groupByKeyBy (==)

-- | Operates similarly to 'group', grouping by the first element
-- of the pair and returning that element in pair with each group.
--
-- >>> groupByFst [(1, "a"), (1, "b"), (2, "c"), (1, "d")]
-- [(1,"a" :| ["b"]),(2,"c" :| []),(1,"d" :| [])]
groupByFst :: Eq a => [(a, b)] -> [(a, NonEmpty b)]
groupByFst = groupByKey id

0 comments on commit 6a3b987

Please sign in to comment.