
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

On Friday 25 May 2007 06:50, Grzegorz wrote:
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.
I'm not sure. A real expert from the list will probably tell you what the cause of the overflow is. As for finding the mean hamming distance, have you considered something like the following: hammingDistance xs ys = length (filter not (zipWith (==) xs ys)) meanHammingDistance xss yss = sumHDs / cntHDs where hds = map (uncurry hammingDistance) [(xs, ys) | xs <- xss, ys <- yss] sumHDs = fromIntegral (sum hds) cntHDs = fromIntegral (length hds)

Daniel McAllansmith
On Friday 25 May 2007 06:50, Grzegorz wrote:
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.
I'm not sure. A real expert from the list will probably tell you what the cause of the overflow is.
As for finding the mean hamming distance, have you considered something like the following:
hammingDistance xs ys = length (filter not (zipWith (==) xs ys))
meanHammingDistance xss yss = sumHDs / cntHDs where hds = map (uncurry hammingDistance) [(xs, ys) | xs <- xss, ys <- yss] sumHDs = fromIntegral (sum hds) cntHDs = fromIntegral (length hds)
Originally I had something like that but it was very slow (approx 40 times slower than calling out to C). Someone on #haskell advised me to manually deforest the lists: the code I posted was my attempt at that. Thanks, -- Grzegorz

Grzegorz wrote:
hammingDistance [] _ = 0 hammingDistance _ [] = 0 hammingDistance (x:xs) (y:ys) | x==y = hammingDistance xs ys | otherwise = 1 + hammingDistance xs ys
hammingDistance xs ys = h xs ys 0 where h [] _ n = n h _ [] n = n h (x:xs) (y:ys) n | x==y = h xs ys n | otherwise = h xs ys $! (n+1) It is also possible to use a bang pattern on the parameter n. I'm too lazy to look up how to do it. But that is not the end of the problem.
modify (\ (sum,count) -> ((,) $! hammingDistance xs ys + sum) $! count + 1)
modify still delays state update, i.e., its code says s <- get put (f s) therefore s nor f s is evaluated now. Loop over it, and you will accumulate a thunk equivalent to f (f (f (f (... (f s)... and that costs stack. Try your own version of modify, e.g., modifies f = do s <- get put $! f s and that does it.
participants (3)
-
Albert Y. C. Lai
-
Daniel McAllansmith
-
Grzegorz