Reputation: 613
I am trying to write a solution for one of the Hackerrank problems. The challenge is to count elements in a list, the elements vary from 0 to 99, so it is possible to count them in linear time. Here is what I got:
{-# LANGUAGE BangPatterns #-}
{-# OPTIONS_GHC -O3 #-}
module Main where
import Data.STRef
import Data.Foldable
import Control.Monad
import Control.Monad.ST
main = do
line1 <- getLine
line2 <- getLine
let
!ns = map read $ words line2 :: [Int]
res = runST $ do
refs <- forM [0..99] $ \i ->
newSTRef (0 :: Int)
traverse_ (\x -> modifySTRef' (refs !! x) (+1) ) ns
mapM (\ref -> readSTRef ref) refs
putStrLn . unwords . map show $ res
This code works but not fast enough to pass the last test case. Can someone recommend an improvement to it? (link to the problem)
Upvotes: 2
Views: 332
Reputation: 27023
This can be done as a one-liner using accumArray
from Data.Array
. Something like accumArray (+) 0 (0,99) . zip values $ repeat 1
where values
is the input.
It appears to still not be fast enough, which is somewhat vexing. accumArray
is more or less as efficient as possible for what it does. Testing on my system reveals the time for processing 1,000,000 input values to be about 1 second, even without compiling it, and that time is dominated by generating the random inputs. That's a far cry from the 5 seconds on the test site.. I have to wonder how overloaded that system is.
Upvotes: 6
Reputation: 74374
One problem you have is that you're looking up your STRef
s in a list which means that you'll have to traverse O(n)
steps for every lookup and modification. This can be alleviated by using something like Data.Map.Map
which has O(log(n))
lookup and modification time.
You could also use a mutable Array
or Vector
for O(1)
lookup/modification time in the ST
monad. This is probably the fastest method.
Upvotes: 3