我想知道是否有办法计算列表中的不同元素并将计数分组为元组,例如
[4,4,4,2,2,2,2,1,1,3]
或
[4,2,4,4,2,1,2,2,1,3]
会产生
[(4,3),(2,4),(1,2),(3,1)]
同时保留原始列表的顺序。
This question提到保留评论中的顺序,但从未解决过问题。
这是我迄今为止的尝试:
import Data.List (nub)
countOccurance :: (Eq a) => a -> [a] -> Int
countOccurance x = length . filter (==x)
naiveCounter :: (Eq a) => [a] -> [(a, Int)]
naiveCounter l = map (\x -> (x, countOccurance x l)) $ nub l
但这似乎效率很低。有没有办法更有效地构建它(例如,通过仅遍历列表一次)?
感谢。
答案 0 :(得分:5)
您可以使用Data.Map.Ordered
。
import Data.Map.Ordered (OMap)
import qualified Data.Map.Ordered as OMap
-- insert L L With
-- ^ ^
-- | `----- insert combined elements on the left of the sequence
-- `-------- insert new elements on the left of the sequence
insertLLWith :: Ord k => (v -> v -> v) -> (k, v) -> OMap k v -> OMap k v
insertLLWith f (k, v) m = case OMap.lookup k m of
Nothing -> (k, v) OMap.|< m
Just v' -> (k, f v v') OMap.|< m
武装insertLLWith
(应该可能会进入带有一些变体的库 - 看起来通常很有用!),我们可以编写一个相当直接的文章:
multisetFromList :: Ord a => [a] -> OMap a Int
multisetFromList = foldr (\x -> insertLLWith (+) (x, 1)) OMap.empty
在ghci:
> multisetFromList [4,4,4,2,2,2,2,1,1,3]
fromList [(4,3),(2,4),(1,2),(3,1)]
> multisetFromList [2,1,2] -- works with ungrouped lists, too
fromList [(2,2),(1,1)]
答案 1 :(得分:2)
另一种选择是两个正确的折叠:
import Prelude hiding (lookup)
import Data.Map (empty, lookup, delete, insertWith)
count :: (Foldable t, Ord k, Num a) => t k -> [(k, a)]
count xs = foldr go (const []) xs $ foldr (\k -> insertWith (+) k 1) empty xs
where
go x f m = case lookup x m of
Nothing -> f m
Just i -> (x, i): f (delete x m)
然后,
\> count [4,2,4,4,2,1,2,2,1,3]
[(4,3),(2,4),(1,2),(3,1)]
答案 2 :(得分:1)
正如sepp2k评论的那样,您可以在按元素分组后按索引排序。我想用广义的列表推导来表达这一点。
{-# LANGUAGE TransformListComp #-}
import GHC.Exts
countOccurrences :: (Ord a) => [a] -> [(a, Int)]
countOccurrences list =
[ (the x, length x)
| (i, x) <- zip [0..] list
, then group by x using groupWith
, then sortWith by minimum i
]
其他选择包括随时更新计数器列表
countOccurrences :: (Eq a) => [a] -> [(a, Int)]
countOccurrences = foldl incrementCount [] where
incrementCount [] x = [(x, 1)]
incrementCount (count@(y, n):counts) x
| x == y = (y, n+1):counts
| otherwise = count:incrementCount counts x
或生成包含所有部分计数的列表,然后过滤到最终计数
import Data.Function
import Data.List
countOccurrences :: (Eq a) => [a] -> [(a, Int)]
countOccurrences = nubBy ((==) `on` fst) . foldr addCount [] where
addCount x counts = (x, maybe 1 succ $ lookup x counts) : counts
虽然效率都不高。