[Haskell-beginners] Stack overflow, but hard to understand
Michael Mossey
mpm at alumni.caltech.edu
Tue Oct 20 00:33:37 EDT 2009
Okay, beginner encountering first major bug.
I'm getting a stack overflow on a program that uses a lot of laziness to
construct and modify lists---but the overflow happens even if I take just
one element from the final list! The overflow seems to have started when I
added the functions 'gauss' and 'gaussList' below, but I am at a loss to
know why---these functions work perfectly in test cases and can even
generate a long list.
The following program is distilled (with a lot of work!) down to the
essence of what triggers the problem.
import Control.Monad
import Control.Monad.Random
import Data.List
-- Here I put a moderate-sized list of filenames which just generic
-- text or code. The longer the list,
-- the more likely to overflow stack. Which is curious, because if IO were
-- lazy here, it shouldn't be reading more than the first character of the
-- first file. Methinks a hint to the problem.
fileList = ...
data TextGroup = Single Char Float
deriving (Show)
textGroup_addDelay :: TextGroup -> Float -> TextGroup
textGroup_addDelay (Single c del) del2 = Single c (del+del2)
mkTextGroup :: Char -> Rand StdGen TextGroup
mkTextGroup c = liftM (Single c) gauss
-- Here's the kinda weird thing I'm doing with Rand. I want to
-- use fromList as the first computation to randomly choose
-- a second Rand computation. It turns out if you replace
-- this funkiness with
-- gauss = getRandomR (0,1)
-- the whole thing works.
gaussList :: Rand StdGen (Rand StdGen Float)
gaussList =
fromList [ (getRandomR( -1.0 ,-0.8 ), 2)
, (getRandomR( -0.8 ,-0.6 ), 2)
, (getRandomR( -0.6 ,-0.4 ), 4)
, (getRandomR( -0.4 ,-0.2 ), 8)
, (getRandomR( -0.2 , 0.0 ), 12)
, (getRandomR( 0.0 , 0.2 ), 12)
, (getRandomR( 0.2 , 0.4 ), 8)
, (getRandomR( 0.4 , 0.6 ), 4)
, (getRandomR( 0.6 , 0.8 ), 2)
, (getRandomR( 0.8 , 1.0 ), 2)
]
gauss :: Rand StdGen Float
gauss = do
m <- gaussList
m
main = do
gen0 <- newStdGen
bufs <- mapM readFile fileList
let buf = concat bufs
let tgs = evalRand (do orig <- mapM mkTextGroup buf
addBreaks orig) gen0
writeFile "output.ank" (show $ take 1 tgs)
More information about the Beginners
mailing list