Help: Stack-overflow and tail-recursive functions

Hal Daume t-hald@microsoft.com
Thu, 19 Jun 2003 09:53:09 -0700


The problem here is actually in the rmat function, not the forpaintbdry
or whatever.  The problem is that, afaik, the listArray function doesn't
deforest the list argument (someone can correct me here, though).  That
is, you write:

  rmat n =3D listArray ... [a big list]

and then this list is first built, then the array is filled in.  You can
see that this is a problem by replacing your main with:

  main =3D print (m ! snd (bounds m))
     where m =3D rmat 800

This will stack overflow too.

Solution: use mutable arrays and fill them in by hand :).

--
 Hal Daume III                                   | hdaume@isi.edu
 "Arrest this man, he talks in maths."           | www.isi.edu/~hdaume


> -----Original Message-----
> From: Koji Nakahara [mailto:yu-@div.club.ne.jp]=20
> Sent: Wednesday, June 18, 2003 7:41 PM
> To: Hal Daume; haskell-cafe@haskell.org
> Subject: Re: Help: Stack-overflow and tail-recursive functions
>=20
>=20
> On Wed, 18 Jun 2003 17:36:28 -0700
> "Hal Daume" <t-hald@microsoft.com> wrote:
>=20
> > Note that there is essentially no difference between f1 and=20
> f2.  When
> > you $! in f2, all it does is ensure that the argument isn't=20
> undefined.
> > It doesn't evaluate any of the list.  Try $!! from the=20
> DeepSeq module or
> > write your own list-forcing function.
>=20
> Thank you very much.  I understand.
>=20
> However my original program still (or maybe from the=20
> beginning) stack-overflows
> at another point, in the middle of the evaluation of "forpaintbdry".
>=20
> Please give me some advice.
> -----------
> -- snippet of the program for painting a random matrix from=20
> its boundary.=20
> module Main  where
> import System
> import Random
> import Array
> import Ix
> import List
>=20
> main =3D putStrLn $ show $ forpaintbdry $ rmat 200
>=20
> forpaintbdry m =3D [(pos, Live) | pos <- (uncurry bdryidxlist)=20
> $ bounds m , isUnknown $ m ! pos ]
>=20
> bdryidxlist :: (Int, Int) -> (Int, Int) -> [(Int, Int)]
> bdryidxlist (a1, a2) (b1, b2) =3D nub $ [(ab, j) | ab <- [a1,=20
> b1], j <- [a2..b2]] ++=20
> 				[(i, ab) | ab <- [a2, b2], i <-=20
> [a1..b1]]
>=20
> rmat n =3D    listArray ((1,1),(n,n)) $ map ct (randoms=20
> (mkStdGen 1) ::[Bool])=20
> 	    where   ct True =3D Unknown
> 		    ct False =3D Dead
>=20
> data CellColor =3D Live | Unknown | Dead
>=20
> isUnknown Unknown =3D True
> isUnknown _ =3D False
>=20
> instance Show CellColor where
>     show Live =3D "Live"
>     show Unknown =3D "Unknown"
>     show Dead =3D "Dead"
>=20
>=20