[Haskell-cafe] Efficient functional idiom for histogram
Pekka Karjalainen
p3k at iki.fi
Sat Aug 1 10:58:15 EDT 2009
On Sat, Aug 1, 2009 at 4:44 PM, Paul Moore<p.f.moore at gmail.com> wrote:
> PS I know my code is probably fairly clumsy - I'd appreciate style
> suggestions, but my main interest here is whether a beginner, with a
> broad programming background, a basic understanding of Haskell, and
> access to Google, put together a clear, efficient, program (ie, the
> case where my usual scripting language is too slow and I want to knock
> something up quickly in a high-level, high-performance language).
Here is one way to rewrite your program. It improved the speed
somewhat for me. I timed both programs on my computer. I suppose one
could try using an array for calculating the histogram as well, but I
only tried the simples thing here. I hope someone can weigh in with a
more thorough analysis.
Please note how I've avoided including the IO Monad in some type
signatures by extracting the data from it locally (with <-). It is
quite possible to apply the histogram function to the data before
going through the IO Monad as well, but it doesn't appear to change
the execution speed much here.
Caveat: My testing wasn't extensive. I just compiled with -O and timed
the programs a couple of times.
import System.Random
import qualified Data.Map as Map
import Data.Map (Map)
import Data.List
diceRolls :: Int -> IO [Int]
diceRolls highVal = do
generator <- getStdGen
return (randomRs (1, highVal) generator)
groupDice :: Int -> [Int] -> [[Int]]
groupDice chunk rolls = map (take chunk) $ iterate (drop chunk) rolls
simulate :: Int -> Int -> Int -> IO [Int]
simulate count m n = do
rolls <- diceRolls n
let sums = map sum $ groupDice m rolls
return (take count sums)
histogram :: Ord a => [a] -> [(a,Int)]
histogram = Map.assocs . foldl f Map.empty
where
f m k = Map.insertWith (+) k 1 m
simulation = do
lst <- simulate 100000 3 6
return (histogram $ lst)
main = do
s <- simulation
putStrLn (show s)
More information about the Haskell-Cafe
mailing list