{-# LANGUAGE TupleSections #-}
module Data.Multiset ( Multiset
, null, size, distinctSize
, empty, singleton, fromMap, fromMap'
, fromList, fromCountsList, fromCountsList'
, member, notMember
, (!), count
, incr, incr', insert, remove, remove'
, filter, filterCounts
, map, mapCounts
, max, min, sum, unionWith, difference, intersectionWith
, toList, toCountsList, toAscCountsList, toDescCountsList
, elems, mostCommon
) where
import Prelude hiding (filter, foldr, map, max, min, null, sum)
import qualified Prelude as Prelude
import Control.Monad (guard)
import Data.Foldable (foldl', foldr)
import Data.List (sortOn)
import Data.Map.Strict (Map)
import qualified Data.Map.Strict as Map
import Data.Maybe (fromMaybe)
import Data.Semigroup (Semigroup, (<>))
import Data.Set (Set)
import qualified Data.Set as Set
import Data.Traversable (traverse)
newtype Multiset v = Multiset { getMultiset :: Map v Int
} deriving (Eq, Ord, Read, Show)
instance (Ord v) => Semigroup (Multiset v) where
(<>) = sum
instance (Ord v) => Monoid (Multiset v) where
mempty = empty
mappend = sum
instance Foldable Multiset where
foldMap f (Multiset m) = Map.foldMapWithKey go m where
go v n = mconcat $ replicate n (f v)
null :: Multiset v -> Bool
null = Map.null . getMultiset
size :: Multiset v -> Int
size = Map.foldl' (\a c -> a + c) 0 . getMultiset
distinctSize :: Multiset v -> Int
distinctSize = Map.size . getMultiset
empty :: Multiset v
empty = Multiset Map.empty
singleton :: v -> Multiset v
singleton v = Multiset $ Map.singleton v 1
fromMap :: (Integral a, Ord v) => Map v a -> Multiset v
fromMap = Multiset . Map.map fromIntegral . Map.filter (> 0)
fromMap' :: (Integral a, Ord v) => Map v a -> Maybe (Multiset v)
fromMap' m = fromMap <$> traverse go m where
go n = if n < 0 then Nothing else Just (fromIntegral n)
fromList :: (Ord v) => [v] -> Multiset v
fromList vs = Multiset $ Map.fromListWith (+) (fmap (,1) vs)
fromCountsList :: (Integral a, Ord v) => [(v,a)] -> Multiset v
fromCountsList = fromMap . Map.fromListWith (+)
fromCountsList' :: (Integral a, Ord v) => [(v,a)] -> Maybe (Multiset v)
fromCountsList' = fromMap' . Map.fromListWith (+)
member :: (Ord v) => v -> Multiset v -> Bool
member v = Map.member v . getMultiset
notMember :: (Ord v) => v -> Multiset v -> Bool
notMember v = Map.notMember v . getMultiset
count :: (Ord v) => v -> Multiset v -> Int
count v = Map.findWithDefault 0 v . getMultiset
(!) :: (Ord v) => Multiset v -> v -> Int
(!) = flip count
incr :: (Ord v) => Int -> v -> Multiset v -> Multiset v
incr n v (Multiset m) = Multiset $ Map.alter (wrap . (+n) . unwrap) v m where
unwrap = fromMaybe 0
wrap n = if n <= 0 then Nothing else Just n
incr' :: (Ord v) => Int -> v -> Multiset v -> Maybe (Multiset v)
incr' n v mm@(Multiset m) = Multiset <$> do
let n' = (count v mm) + n
guard $ n' >= 0
return $ (if n' == 0 then Map.delete v else Map.insert v n') m
insert :: (Ord v) => v -> Multiset v -> Multiset v
insert = incr 1
remove :: (Ord v) => v -> Multiset v -> Multiset v
remove = incr (-1)
remove' :: (Ord v) => v -> Multiset v -> Maybe (Multiset v)
remove' = incr' (-1)
filter :: (Ord v) => (v -> Bool) -> Multiset v -> Multiset v
filter f (Multiset m) = Multiset $ Map.filterWithKey (\v _ -> f v) m
filterCounts :: (Ord v) => (Int -> Bool) -> Multiset v -> Multiset v
filterCounts f (Multiset m) = Multiset $ Map.filter f m
map :: (Ord v1, Ord v2) => (v1 -> v2) -> Multiset v1 -> Multiset v2
map f (Multiset m) = Multiset $ Map.mapKeys f m
mapCounts :: (Ord v) => (Int -> Int) -> Multiset v -> Multiset v
mapCounts f (Multiset m) = fromMap $ Map.map f m
sum :: (Ord v) => Multiset v -> Multiset v -> Multiset v
sum = unionWith' (+)
max :: (Ord v) => Multiset v -> Multiset v -> Multiset v
max = unionWith' Prelude.max
min :: (Ord v) => Multiset v -> Multiset v -> Multiset v
min = intersectionWith Prelude.min
unionWith :: (Ord v) => (Int -> Int -> Int) -> Multiset v -> Multiset v -> Multiset v
unionWith f ms1@(Multiset m1) ms2@(Multiset m2) = fromMap m' where
vs = Set.union (Map.keysSet m1) (Map.keysSet m2)
go v = (v, f (count v ms1) (count v ms2))
m' = Map.fromList $ fmap go $ Set.toList vs
intersectionWith :: (Ord v) => (Int -> Int -> Int) -> Multiset v -> Multiset v -> Multiset v
intersectionWith f (Multiset m1) (Multiset m2) = fromMap $ Map.intersectionWith f m1 m2
difference :: (Ord v) => Multiset v -> Multiset v -> Multiset v
difference (Multiset m1) (Multiset m2) = Multiset $ Map.differenceWith go m1 m2 where
go n1 n2 = let n = n1 - n2 in if n > 0 then Just n else Nothing
toMap :: Multiset v -> Map v Int
toMap (Multiset m) = m
toList :: Multiset v -> [v]
toList = concat . fmap (uncurry (flip replicate)) . Map.toList . getMultiset
toCountsList :: Multiset v -> [(v,Int)]
toCountsList = Map.toList . getMultiset
toAscCountsList :: Multiset v -> [(v,Int)]
toAscCountsList = sortOn snd . toCountsList
toDescCountsList :: Multiset v -> [(v,Int)]
toDescCountsList = sortOn (negate . snd) . toCountsList
elems :: Multiset v -> Set v
elems = Map.keysSet . getMultiset
mostCommon :: Multiset v -> [v]
mostCommon ms = case toDescCountsList ms of
[] -> []
((v, c) : ts) -> v : (fmap fst . takeWhile ((== c) . snd) $ ts)
unionWith' :: (Ord v) => (Int -> Int -> Int) -> Multiset v -> Multiset v -> Multiset v
unionWith' f (Multiset m1) (Multiset m2) = fromMap $ Map.unionWith f m1 m2