
Hello everybody. I have a long list consisted of a small number (about a dozen) of elements repeating in random pattern. I know all the possible elements. I need to count number of occurences of each particular element and to do i quickly. For example quick_func Eq a => [a] -> [(a,Int)] quick_func [1,2,3,1,2,9,1,9] == [(1,3),(2,2),(3,1),(9,2)] According to profiler this function is the bottle-neck in my sluggish program so I really need to speed it up. Any proposals?

Dmitry Vyal wrote:
Hello everybody.
I have a long list consisted of a small number (about a dozen) of elements repeating in random pattern. I know all the possible elements. I need to count number of occurences of each particular element and to do i quickly.
For example quick_func Eq a => [a] -> [(a,Int)] quick_func [1,2,3,1,2,9,1,9] == [(1,3),(2,2),(3,1),(9,2)]
According to profiler this function is the bottle-neck in my sluggish program so I really need to speed it up.
What's been tried so far? Below is a snippet using arrays. You'd probably get a faster program with Unboxed arrays and unsafeAccumArray.
import Data.Array
main = print $ quick_func [1,2,3,1,2,9,1,9]
quick_func is = assocs $ accumArray (+) 0 (1,12) [(i, 1) | i<-is]

Greg Buchholz wrote:
You'd probably get a faster program with Unboxed arrays and unsafeAccumArray.
Yeah, its about 20x faster unboxed and unsafe... import Data.Array.Base main = print $ quick_func $ take 1000000 $ cycle [1,2,3,1,2,9,1,9] quick_func :: [Int] -> [(Int,Int)] quick_func is = assocs f where f :: UArray Int Int f = unsafeAccumArray (+) 0 (1,12) [(i, 1::Int) | i<-is]

I'd use a Map in GHC 6.4:
count xs = toList $ fromListWith (+) (zip xs (repeat 1))
or a FiniteMap in earlier versions:
count xs = fmToList $ addListToFM_C (+) emptyFM (zip xs (repeat 1))
both of these seem to be quite fast.
- Cale
On 4/28/05, Dmitry Vyal
Hello everybody.
I have a long list consisted of a small number (about a dozen) of elements repeating in random pattern. I know all the possible elements. I need to count number of occurences of each particular element and to do i quickly.
For example quick_func Eq a => [a] -> [(a,Int)] quick_func [1,2,3,1,2,9,1,9] == [(1,3),(2,2),(3,1),(9,2)]
According to profiler this function is the bottle-neck in my sluggish program so I really need to speed it up.
Any proposals?
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

Cale Gibbard wrote:
I'd use a Map in GHC 6.4: count xs = toList $ fromListWith (+) (zip xs (repeat 1)) or a FiniteMap in earlier versions: count xs = fmToList $ addListToFM_C (+) emptyFM (zip xs (repeat 1)) both of these seem to be quite fast.
- Cale
Thanks, this is significaly faster than variant with accumArray i've used before. By the way, how to use Unboxed arrays and unsafeAccumArray Greg Buchholz mentioned? I can't find them in GHC 6.2 documentation. And last question: When I try to compile my program with -caf-all I get these messages: % ghc -prof -caf-all mastermind.hs -o mastermind /tmp/ghc3338.hc:25: error: redefinition of `Mainmain_CAF_cc_ccs' /tmp/ghc3338.hc:24: error: `Mainmain_CAF_cc_ccs' previously defined here If I use -auto-all it works fine. I use Slackware Linux 10.1 with gcc 3.3.4 and ghc-6.2.2

Dmitry Vyal wrote:
By the way, how to use Unboxed arrays and unsafeAccumArray Greg Buchholz mentioned? I can't find them in GHC 6.2 documentation.
http://www.haskell.org/~simonmar/haddock-example/Data.Array.Base.html Greg Buchholz
participants (3)
-
Cale Gibbard
-
Dmitry Vyal
-
Greg Buchholz