[Haskell-cafe] Stack overflow

Grzegorz grzegorz.chrupala at computing.dcu.ie
Thu May 24 14:50:55 EDT 2007


Hi all,
I have a simple piece of code which is giving me stack overflow. I guess I need
to make it stricter sowhere but I can't figure out extactly where. So I thought
I'd ask the experts.


import Data.List (foldl')
import Control.Monad.State.Strict

hammingDistance [] _ = 0
hammingDistance _ [] = 0
hammingDistance (x:xs) (y:ys) | x==y      = hammingDistance xs ys
                              | otherwise = 1 + hammingDistance xs ys

meanHammingDistanceM xss yss = evalState (mhd xss yss) (0,0)
mhd xss yss = do
    for xss $ \xs -> 
        for yss $ \ys -> do
            modify (\ (sum,count) -> ((,) $! hammingDistance xs ys + sum) $!
count + 1)
    (sum,count) <- get
    return $ fromIntegral sum/fromIntegral count
  where for = flip mapM_



--
Grzegorz



More information about the Haskell-Cafe mailing list