GC bug

John Hughes john.hughes@swipnet.se
Sat, 9 Nov 2002 01:46:28 +0100


This is a multi-part message in MIME format.

------=_NextPart_000_00E0_01C28791.D1DD63B0
Content-Type: text/plain;
	charset="iso-8859-1"
Content-Transfer-Encoding: 8bit

The attached program (needs the Hugs Graphics Library) reveals what I
presume is a GC bug in the Dec 2001 hugs.

John

----- Original Message -----
From: "John Hughes" <john.hughes@swipnet.se>
To: "Alastair Reid" <alastair@reid-consulting-uk.ltd.uk>
Sent: Friday, November 08, 2002 2:58 PM
Subject: Re: HGL


>
> >
> > > Alastair, Just for a bit of fun, I solved the first programming lab
> > > on our Java course using HGL instead. You might like to run the
> > > attached program to see the result!
> >
> > That's pretty cool.  Thanks.
> >
> > > Give it a BIG heap, or you'll hit the same GC bug in Hugs that I did.
> >
> > I do indeed need a big heap.
> >
> > How do you know it's a GC bug and not just a space leak?
> > If we can, I'd like to fix it if it's a bug (or even if it's not a 'bug'
> > but can be fixed.)
> >
>
> Well, I get different behaviour depending on the heap size. For example,
> with a heap size of 250000,
>
> Main> main
>
> Thread raised exception: {{Cell ...}}
> Uncaught Error: {{Cell ...}}
>
> or, in a fresh winhugs,
>
> Main> foldr1 (.+) (take 10000 (points ()))
>
> Program error: {primIntegerToInt (-2147483648)}
>
> Repeating that, by the way, gives
>
> Main> foldr1 (.+) (take 10000 (points ()))
>
> ERROR - Garbage collection fails to reclaim sufficient space
>
> With a heap size of 249999, I get¨
>
> Main> main
>
> ERROR - Garbage collection fails to reclaim sufficient space
>
> Main> foldr1 (.+) (take 10000 (points ()))
>
> Program error: {primIntegerToInt 352126429244364}
>
> Behaviour that depends on the heap size looks like a GC bug to me.
>
> I would have liked to pare the program down to a small one exhibiting the
> same problem, but that proved difficult. What I did discover is that the
> type signature on transform is crucial: removing it changes the behaviour,
> for reasons which are not at all clear to me.
>
> Good luck with bug-hunting!
>
> John
>
>

------=_NextPart_000_00E0_01C28791.D1DD63B0
Content-Type: application/octet-stream;
	name="Lab1.hs"
Content-Transfer-Encoding: quoted-printable
Content-Disposition: attachment;
	filename="Lab1.hs"

-- This program solves the first laboratory exercise on our introductory
-- Java course: see=20
-- =
http://www.cs.chalmers.se/ComputingScience/Education/Courses/d1pt/d1ptb/l=
ab1/index.html

import List
import Random
import GraphicsUtils

-- We represent vectors as lists, rather than as a new type. This is =
more
-- general: we can represent vectors of any dimension. It also =
simplifies
-- the programming. It is slightly less efficient for 2D vectors, but =
who
-- cares?

type Vector =3D [Double]

vector2 x y =3D [x,y]
getX [x,y] =3D x
getY [x,y] =3D y

v1 .* v2 =3D sum (zipWith (*) v1 v2)		-- scalar product
v1 .+ v2 =3D zipWith (+) v1 v2			-- vector addition

type Matrix =3D [Vector]

matrix2 a b c d =3D [vector2 a b, vector2 c d]
rows m =3D m
cols m =3D transpose m

det [] =3D 1
det rs =3D foldr (-) 0 [a * det m | (a:_, m) <- zip rs (minors (map tail =
rs))]

minors (x:xs) =3D xs:map (x:) (minors xs)
minors [] =3D []

m #* v =3D map (.* v) m				-- matrix-vector multiplication

-- Define a symbolic expression type for testing matrix operations.
-- This isn't part of the lab exercise, but it's fun.
-- Example:=20
-- Main> det (matrix2 (var"a") (var"b") (var"c") (var"d"))
-- a*d - b*c =20

data Polynomial =3D Poly [(Int,[String])] deriving Eq

instance Show Polynomial where
  show (Poly []) =3D "0"
  show (Poly terms) =3D foldr1 join (map showTerm terms)
    where join s1 ('-':s2) =3D s1 ++ " - " ++=20
				if take 2 s2=3D=3D"1*" then drop 2 s2 else s2
	  join s1 s2 =3D s1 ++ " + " ++ s2
	  showTerm (k,[]) =3D show k
	  showTerm (1,vars) =3D showVars vars
	  showTerm (k,vars) =3D show k ++ "*" ++ showVars vars
	  showVars =3D foldr1 (\v v' -> v++"*"++v')

instance Num Polynomial where
  fromInt 0 =3D Poly []
  fromInt n =3D Poly [(n,[])]
  negate (Poly terms) =3D Poly [(-k,vs) | (k,vs) <- terms]
  Poly ts + Poly ts' =3D Poly (merge ts ts')
    where merge [] ts' =3D ts'
	  merge ts [] =3D ts
	  merge ((k,vs):ts) ((k',vs'):ts')
	    | vs < vs' =3D (k,vs):merge ts ((k',vs'):ts')
	    | vs =3D=3D vs' =3D if k+k'=3D=3D0 then merge ts ts'=20
			  else (k+k',vs):merge ts ts'
	    | vs > vs' =3D (k',vs'):merge ((k,vs):ts) ts'
  Poly ts * Poly ts' =3D Poly (sortBy (\(_,vs) (_,vs') -> compare vs =
vs')
				[(k*k',sort(vs++vs'))=20
				| (k,vs) <- ts, (k',vs') <- ts'])

var s =3D Poly [(1,[s])]

-- Now for the picture: we define transformations corresponding to the
-- four parts of the image.

blue, red, green, yellow :: (Matrix, Vector)
blue =3D (matrix2 0.2 (-0.25) 0.25 0.2, vector2 0 64)
red =3D (matrix2 0.64 0.04 (-0.04) 0.84, vector2 0 64)
yellow =3D (matrix2 (-0.19) 0.29 0.29 0.19, vector2 0 18)
green =3D (matrix2 0 0 0 0.17, vector2 0 0)

chooseTransformation p =3D
  alts !! length (takeWhile (<p) (scanl1 (+) probs))
  where alts =3D [blue, red, yellow, green]
	probs=3D [0.1,  0.75,0.1,    0.05]

--transform :: (Matrix,Vector) -> Vector -> Vector
transform (m,b) v =3D m #* v .+ b

-- convert a random integer to a probability.

probability n =3D fromInt (n `mod` 1000) / 999

-- the list of points to fill (avoid storing the entire list)

points () =3D generate (map (chooseTransformation.probability)=20
		          (randoms (StdGen 0 1)))
		     (vector2 0 0)
  where generate (t:ts) v =3D v : generate ts (transform t v)

-- it only remains to draw the points.

pointGraphic v =3D withColor Green$ polygon =
[(x,y),(x+1,y),(x+1,y+1),(x,y+1)]
  where (x,y) =3D (round (getX v) + 200, round (getY v))

main =3D runGraphics$ do
  w <- openWindow "Fractal" (400,400)
  sequence_ [drawInWindow w (pointGraphic p) | p <- take 10000 (points =
())]
  getKey w
  closeWindow w

------=_NextPart_000_00E0_01C28791.D1DD63B0--