Finding/fixing stack overflow.

David Brown haskell3 at davidb.org
Sat Apr 21 20:21:02 CEST 2012


I've isolated the below small piece of code that is giving me a stack
overflow.  I'm kind of at a loss as has to fix, or even find what is
happening here.  (The real program is reading the data from a file,
and doing something more complex with it).  I'm not even sure how to
work around this issue.

It fails for me when given an argument of 1000000.

Any ideas?  I'm running 7.0.4, but I've tried this with ghc 6.12.3,
and 7.4.1.

Thanks,
David

----------------------------------------------------------------------
import Control.Applicative
import Control.Monad
import Data.Binary
import Data.Binary.Put
import Data.Binary.Get
import Data.List
import Data.Word
import System.Environment

putValues :: [Int] -> Put
putValues vals = mapM_ (putWord32le . fromIntegral) vals

getValues :: Int -> Get [Int]
getValues count = replicateM count (fromIntegral <$> getWord32le)

goofySum :: Int -> Int
goofySum count =
     let block = runPut $ putValues [1 .. count] in
     foldl' max 0 $ runGet (getValues count) block

main :: IO ()
main = do
     args <- getArgs
     let count = case args of
           [c] -> read c
           _ -> error "Invalid usage"
     putStrLn $ show $ goofySum count
----------------------------------------------------------------------



More information about the Glasgow-haskell-users mailing list