[Haskell-cafe] Debugging Haskell code

Paul Moore p.f.moore at gmail.com
Sun Sep 27 15:50:25 EDT 2009


I'm still playing round with my random dieroll generation program. In
doing so, I just hit a segmentation fault (I didn't think Haskell
could *cause* a segfault!) I'm sure it's my code - I got this to
compile by fiddling with types until the errors (which I didn't
understand) went away. Certainly not the right way to code, I know,
but never mind.

The problem is that I have *no idea* how to begin debugging this. In
C, Python, or any other imperative language, I'd put traces in, etc.
But in Haskell, I don't even know where to start.

I attach the code below. While help in the form of pointers to what I
did wrong would of course be appreciated, what I'm really looking for
is a pointer on how I'd find out for myself. (Hey! I just read the bit
in the ghc manual which says if I am not using foreign or unsafe
functions, a crash is a compiler bug. Did I find a compiler bug?)

My code is below. All I did is ghc --make hist_3d6.hs, then run
hist_3d6.exe. This is ghc 6.10.4 on Windows Vista Home 32-bit.

Thanks for any help,
Paul.

import System.Random.Mersenne
import qualified Data.Map as Map
import Data.Map (Map)
import Data.List

takes :: Int -> [a] -> [[a]]
takes n [] = []
takes n xs = take n xs : takes n (drop n xs)

sums :: Num a => Int -> [a] -> [a]
sums n xs = map sum (takes n xs)

simulate :: Int -> IO [Double]
simulate count = do
  gen <- newMTGen Nothing
  dice <- (randoms gen :: IO [Double])
  return (take count dice)

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
 return lst
 --return (histogram lst)

main = do
 s <- simulation
 putStrLn (show s)


More information about the Haskell-Cafe mailing list