Crash Dump from 3D morph

Boris Gaertner squeak-dev at lists.squeakfoundation.org
Tue Sep 24 19:36:20 UTC 2002


This is a multi-part message in MIME format.

------=_NextPart_000_003F_01C26412.6C05BEE0
Content-Type: text/plain;
	charset="iso-8859-1"
Content-Transfer-Encoding: 7bit


Jon Hylands <jon at huv.com> wrote:

>>As an update, I can consistantly crash my VM now when I run my demo if I
>>haven't run the B3D demo first (since I started the image) if I am in
>>software mode.

Yes, that is what I observed a few times when I tried to render
models that are built from triangles.

The work-around that I sent you earlier today should avoid the crash for
instances of  B3DSimpleMesh that contain triangular faces.
The work-around uses the observed fact that quadrangles are sucessfully 
rendered while triangles are not: The first trianlge vertex is repeated
as the fourth vertex of a quadrangle. This is certainly an ugly
trick, but it works.

The fact that everthing works fine when you first run the demo
(the rotating cube) is perhaps a hint that some initialization that
is performed by the demo is missing when the demo was not executed
before we begin our own work.

The attached change set  TriangleProblem.cs  contains (in category
 'B3DTests') two examples. Each of these examples can cause
a crash of the VM. Please read the class comments of classes
B3DSingleTriangle  and  B3DTestSimpleMesh  for further details.
The change set workaround.cs contains the work-around. You may wish
to try the examples in  TriangleProblem.cs  without that work-around first.

Regrettably I cannot tell you where the problem is. Is there a 
glitch in the renderer or are we using the renderer in a way it must
not be used? What are the opinions of the experts?

Greetings, Boris









------=_NextPart_000_003F_01C26412.6C05BEE0
Content-Type: application/octet-stream;
	name="TriangleProblem.cs"
Content-Transfer-Encoding: quoted-printable
Content-Disposition: attachment;
	filename="TriangleProblem.cs"

'From Squeak3.2 of 11 July 2002 [latest update: #4952] on 24 September =
2002 at 9:33:20 pm'!=0D"Change Set:		TriangleProblem
Date:			24 September 2002
Author:			Boris Gaertner

the VM crashes when Balloon3D tries to render triangles without having =
rendered something else before. This change set contains two examples =
that cause the VM to crash. Look at the class coments of classes =
B3DSingleTriangle and B3DTestSimpleMesh for further details. This change =
set should be used with Squeak 3.2."!=0D=0DObject subclass: =
#B3DSingleTriangle=0D	instanceVariableNames: 'scene '=0D	=
classVariableNames: ''=0D	poolDictionaries: ''=0D	category: =
'B3DTests'!=0D=0D!B3DSingleTriangle commentStamp: 'BG 9/24/2002 21:16' =
prior: 0!=0DTo see this demo, execute=0D=0D B3DSingleTriangle new =
show1=0D=0D=0DThis demo causes a crash of the VM when it=0Dis started =
before the B3DDemo (the rotating cube) was executed.=0DWhen it is =
excecuted after that demo, a single triangle with=0Dcolored vertices is =
displayed.=0D=0DThe mesh type used is B3DIndexedTriangleMesh. Meshes of =
this type=0Dare rendered without problems when they contain a greater =
number=0Dof triangles. The problem that is demonstrated by this example =
is=0Dthus not a real-life problem: An indexed triangle mesh with=0Donly =
one triangle is *very* untypical.=0D=0D=0DI have no workaround for that =
problem. =0D!=0D=0DObject subclass: #B3DTestSimpleMesh=0D	=
instanceVariableNames: 'scene '=0D	classVariableNames: ''=0D	=
poolDictionaries: ''=0D	category: 'B3DTests'!=0D=0D!B3DTestSimpleMesh =
commentStamp: 'BG 9/24/2002 21:04' prior: 0!=0DExecute=20

 B3DTestSimpleMesh new show1

to see this demo. This demo causes a crash of the VM when it=0Dis =
started before the B3DDemo (the rotating cube) was executed.=0DWhen it =
is excecuted after that demo, an icosahedron is displayed.=0D=0DTo avoid =
the crash, load the change set   workaround.cs=0Dbefore you execute this =
demo.!=0D=0D=0D!B3DSceneExplorerMorph methodsFor: 'accessing' stamp: 'BG =
12/26/2001 16:41'!=0DclearColor: aColor=0D=0D   b3DSceneMorph color: =
aColor! !=0D=0D!B3DSceneExplorerMorph methodsFor: 'actions' stamp: 'BG =
9/24/2002 20:23'!=0DtoggleAcceleration=0D	self accelerationEnabled: self =
accelerationEnabled not.! !=0D=0D!B3DSceneExplorerMorph methodsFor: =
'initialization' stamp: 'BG 12/23/2001 16:36'!=0Dinitialize=0D	| ctrl =
|=0D	super initialize.=0D	self extent: 300 at 300.=0D	self borderRaised.=0D	=
color:=3D Color gray: 0.8.=0D	frameWidth :=3D 25.=0D=0D	b3DSceneMorph =
:=3D AdvancedB3DSceneMorph new.=0D	b3DSceneMorph color: Color white.=0D	=
self addMorphFront: b3DSceneMorph.=0D	=0D	wheels :=3D Dictionary new.=0D	=
ctrl:=3D WheelMorph new.=0D	ctrl target: b3DSceneMorph.=0D	ctrl =
actionSelector: #addFovAngle:.=0D	ctrl factor: -0.07.=0D	ctrl =
setBalloonText: 'FOV'.=0D	self addMorphFront: ctrl.=0D	wheels at: #fov =
put: ctrl.=0D=0D	ctrl :=3D WheelMorph new.=0D	ctrl target: =
b3DSceneMorph.=0D	ctrl actionSelector: #addDolly:.=0D	ctrl factor: =
0.005.=0D	ctrl beVertical.=0D	ctrl setBalloonText: 'Dolly'.=0D	self =
addMorphFront: ctrl.=0D	wheels at: #dolly put: ctrl.=0D=0D	ctrl :=3D =
WheelMorph new.=0D	ctrl target: b3DSceneMorph.=0D	ctrl actionSelector: =
#rotateZ:.=0D	ctrl beVertical.=0D	ctrl setBalloonText: 'z Axis'.=0D	self =
addMorphFront: ctrl.=0D	wheels at: #rotZ put: ctrl.=0D=0D	ctrl :=3D =
WheelMorph new.=0D	ctrl target: b3DSceneMorph.=0D	ctrl actionSelector: =
#rotateY:.=0D	ctrl setBalloonText: 'y Axis'.=0D	self addMorphFront: =
ctrl.=0D	wheels at: #rotY put: ctrl.=0D=0D	ctrl :=3D WheelMorph new.=0D	=
ctrl target: b3DSceneMorph.=0D	ctrl actionSelector: #rotateX:.=0D	ctrl =
beVertical.=0D	ctrl setBalloonText: 'x Axis'.=0D	self addMorphFront: =
ctrl.=0D	wheels at: #rotX put: ctrl.=0D=0D	ctrl _ self =
acceleratorButton.=0D	self addMorphFront: ctrl.=0D	wheels at: #accel =
put: ctrl. =0D! !=0D=0D!B3DSceneExplorerMorph methodsFor: 'visual =
properties' stamp: 'BG 12/24/2001 17:15'!=0DrotateX: a=0D=0D   =
b3DSceneMorph rotateX: a! !=0D=0D=0D!B3DSceneMorph methodsFor: =
'initialize' stamp: 'BG 12/23/2001 16:06'!=0DcreateDefaultScene=0D	| =
sceneObj camera |=0D	sceneObj _ B3DSceneObject named: 'Sample Cube'.=0D	=
sceneObj geometry: "(B3DBox from: (-0.7 at -0.7@-0.7) to: (0.7 at 0.7@0.7))" =
(B3DIndexedMesh vrml97Cylinder).=0D	camera _ B3DCamera new.=0D	camera =
position: 0 at 0@-1.5.=0D	self extent: 100 at 100.=0D	scene _ B3DScene new.=0D	=
scene defaultCamera: camera.=0D	scene objects add: sceneObj.! =
!=0D=0D=0D!AdvancedB3DSceneMorph methodsFor: 'accessing' stamp: 'BG =
12/24/2001 16:51'!=0Dscene: aScene=0D	super scene: ("self =
updateSceneWithDefaults:" aScene).=0D	self updateUpVectorForCamera: self =
scene defaultCamera.=0D	self updateHeadlight.=0D	self changed! =
!=0D=0D!AdvancedB3DSceneMorph methodsFor: 'initialization' stamp: 'BG =
12/23/2001 16:20'!=0DcreateDefaultScene=0D	| camera headLight light2 =
|=0D	super createDefaultScene.=0D	camera _ B3DCamera new.=0D	camera =
position: 0 at 0@-6.=0D	camera target: 0 at 0@0.=0D	camera fov: 15.0.=0D	scene =
defaultCamera: camera.=0D	headLight :=3D B3DSpotLight new.=0D	headLight =
position: 0 at -1@0.=0D	headLight target: 0 at 0@0.=0D	headLight lightColor: =
(B3DMaterialColor color: (Color yellow)).=0D	headLight attenuation: =
(B3DLightAttenuation constant: 1.0 linear: 0.0 squared: 0.0).=0D	=
headLight minAngle: 5.=0D	headLight maxAngle: 6.=0D	scene lights add: =
headLight.=0D     light2 :=3DB3DAmbientLight new.=0D	=0D	light2 =
lightColor: (B3DMaterialColor color: (Color green)).=0D	=0D	scene lights =
add: light2.=0D	scene objects do: [ :object |=0D		object material: nil]! =
!=0D=0D!AdvancedB3DSceneMorph methodsFor: 'private' stamp: 'BG =
12/24/2001 16:30'!=0DupdateSceneWithDefaults: myScene=0D	| headLight mat =
|=0D	myScene lights "at: 'Ambient1' put:" add: (B3DAmbientLight color: =
(Color gray: 0.2)).=0D	headLight :=3D B3DSpotLight new.=0D	headLight =
position: myScene defaultCamera position.=0D	headLight target: myScene =
defaultCamera target.=0D	headLight lightColor: (B3DMaterialColor color: =
(Color gray: 0.7)).=0D	headLight attenuation: (B3DLightAttenuation =
constant: 1.0 linear: 0.0 squared: 0.0).=0D	headLight minAngle: 80.=0D	=
headLight maxAngle: 90.=0D	myScene lights "at: '$HeadLight$' put:" add: =
headLight copy.=0D	mat :=3D B3DMaterial new.=0D	mat diffusePart: (Color =
gray: 0.25).=0D	mat ambientPart: (Color gray: 0.01).=0D	myScene objects =
do: [:o|=0D		o material: mat].=0D	^myScene! !=0D=0D=0D!B3DSingleTriangle =
methodsFor: 'scene creation' stamp: 'BG 9/24/2002 =
21:33'!=0DcreateTriangleScene2

	| sceneObj camera headLight light2 light3 light4 mat |
	camera _ B3DCamera new.
	camera position: 0 at 0@-6.
	camera target: 0 at 0@0.
	camera fov: 15.0.
	scene _ B3DScene new.
	scene defaultCamera: camera.
	sceneObj _ B3DSceneObject named: 'SingleTriangle'.
	sceneObj geometry: (self computeTriangleGeometry2).

     mat :=3D B3DMaterial new.
	mat emission: (Color gray: 0.4);
          shininess: 0.3;
         diffusePart: (Color gray: 0.15).
	mat ambientPart: (Color gray: 0.05).
	sceneObj material: mat.

	scene objects add: sceneObj.

	headLight :=3D B3DSpotLight new.
	headLight position: 0 at -5@0.
	headLight target: 0 at 0@0.
	headLight lightColor: (B3DMaterialColor color: (Color green)).
	headLight attenuation: (B3DLightAttenuation constant: 1.0 linear: 1.0 =
squared: 0.0).
	headLight minAngle: 15.
	headLight maxAngle: 30.
	scene lights add: headLight.
     light2 :=3DB3DAmbientLight new.
=09
	light2 lightColor: (B3DMaterialColor color: (Color white)).
=09
	scene lights add: light2.
     light3 :=3D B3DPositionalLight new.
     light3 position: 0 @0  @ 0;
             setColor: (Color white).
    light3  attenuation: (B3DLightAttenuation constant: 0.9 linear: 0.9 =
squared: 0.0).
    scene lights add: light3.=20
    light4 :=3D B3DPositionalLight new.
    light4 position: -1 @ 0 @ -1;
             setColor: (Color white).
    light4  attenuation: (B3DLightAttenuation constant: 1.2 linear: 1.1 =
squared: 1.1).
	scene lights add: light4.
! !=0D=0D!B3DSingleTriangle methodsFor: 'as yet unclassified' stamp: 'BG =
12/27/2001 12:26'!=0DcomputeTriangleGeometry2

 " this mesh contains one single triangle "
	| vtx  c  vertices faces  mesh |
	vtx _ WriteStream on: (B3DVector3Array new).
     c :=3D WriteStream on: B3DColor4Array new.
     vtx nextPut: (B3DVector3 x: 0.0 y: 0.0  z: -1.0).
     c nextPut: (B3DColor4 r: 1.0 g: 0.0 b: 0.0 a: 1.0).

     vtx nextPut: (B3DVector3 x: 1.0 y: 0.0  z: 0.0).
     c nextPut: (B3DColor4 r: 0.0 g: 1.0 b: 0.0 a: 1.0).

     vtx nextPut: (B3DVector3 x: 0.0 y: 1.0  z: 0.0).
     c nextPut: (B3DColor4 r: 0.0 g: 0.0 b: 1.0 a: 1.0).

	vertices _ vtx contents.
  =20
	faces _ B3DIndexedTriangleArray new: 1.
    faces at: 1 put: (B3DIndexedTriangle=20
						with: 1
						with: 2
						with: 3).



  mesh :=3D B3DIndexedTriangleMesh new.
   mesh vertices: vertices;
          faces: faces;
          vertexColors: c contents.
  ^mesh! !=0D=0D!B3DSingleTriangle methodsFor: 'testing' stamp: 'BG =
9/24/2002 21:04'!=0Dshow1

    " B3DSingleTriangle new show1"

     | view |

  self createTriangleScene2.
  (view :=3D B3DSceneExplorerMorph new)
     scene: scene.
 view clearColor: (Color gray: 0.5).
  view rotateX: 25.4.
  view
     openInWorld.
  ! !=0D=0D=0D!B3DSingleTriangle class methodsFor: 'examples' stamp: 'BG =
9/24/2002 21:06'!=0Dexample

   "B3DSingleTriangle example "

   B3DSingleTriangle new show1

   " One single trinangle.
     The example demonstrates coloring.
   =20
     Triangle meshes and lights are used "
   " Do not try this example as the first one. For unknown reasons the =
VM crashes when this example is tried before another example was tried. =
"! !=0D=0D=0D!B3DTestSimpleMesh methodsFor: 'as yet unclassified' stamp: =
'BG 9/24/2002 12:56'!=0DcomputeEssentialPoints20

  " return the six essential points of a icosahedron.=20
The solid is point symmetric to the origin of the coordinate system. It =
is therefore sufficient to compute 6 of its 12 vertices. The other =
vertices are obtained by multiplication with -1.  "
   | points  |

   points :=3D Array new: 6.
   1 to: 5 do:=20
         [:idx | =20
         points at: idx put: (B3DVector3
               x: (Float pi * idx * 2 / 5) cos * 5.0 sqrt * 2 / 5
               y: (Float pi * idx * 2 / 5) sin * 5.0 sqrt * 2 / 5
               z: 5.0 sqrt / 5).
         ].
   points at: 6 put: (B3DVector3 x: 0.0 y: 0.0 z: 1.0).
   ^points
! !=0D=0D!B3DTestSimpleMesh methodsFor: 'as yet unclassified' stamp: 'BG =
9/24/2002 13:27'!=0DcreateBody

  " return a B3DSimpleMesh that represents an icosahedron
    The solid is point symmetric to the origin of the coordinate system. =
It is therefore sufficient to compute 6 of its 12 vertrices. The other =
vertices are obtained by multiplication with -1. "
   | points meshFaces vertices  |

 =20
  points :=3D self computeEssentialPoints20.
  vertices :=3D Array new: 12.
  1 to: points size do:=20
     [:idx | vertices at: idx put: (points at: idx).
            vertices at: idx + 6 put: (points at: idx) negated].
   meshFaces :=3D OrderedCollection new: 20.

	1 to: 5
		do:=20
		  [ :idx |  | a p n |
              a :=3D Array with: 6 with: idx with: idx \\ 5 + 1.
              p :=3D a collect: [:i | vertices at: i].
              n :=3D self normalForFace: p.
              meshFaces add: (B3DSimpleMeshFace
                           withAll: (p collect: [:x | =
(B3DSimpleMeshVertex new) position: x; normal: n])).


              a :=3D Array with: idx \\5 + 1 with: idx with: idx + 2 \\5 =
+ 1 + 6.
              p :=3D a collect: [:i | vertices at: i].
              n :=3D self normalForFace: p.
              meshFaces add: (B3DSimpleMeshFace
                           withAll: (p collect: [:x | =
(B3DSimpleMeshVertex new) position: x; normal: n])).

              a :=3D Array with: idx + 6 with: idx \\5 + 1 + 6 with: idx =
+ 2 \\5 + 1.
              p :=3D a collect: [:i | vertices at: i].
              n :=3D self normalForFace: p.
              meshFaces add: (B3DSimpleMeshFace
                           withAll: (p collect: [:x | =
(B3DSimpleMeshVertex new) position: x; normal: n])).

              a :=3D Array with: idx \\ 5 + 1 + 6 with: idx + 6 with: =
12.
              p :=3D a collect: [:i | vertices at: i].
              n :=3D self normalForFace: p.
              meshFaces add: (B3DSimpleMeshFace
                           withAll: (p collect: [:x | =
(B3DSimpleMeshVertex new) position: x; normal: n])).
           ].
  ^B3DSimpleMesh withAll: meshFaces! !=0D=0D!B3DTestSimpleMesh =
methodsFor: 'as yet unclassified' stamp: 'BG 9/24/2002 =
13:21'!=0DnormalForFace: vi=20

  "  vi  is a collection of vertex indices. Only the first three =
vertices are used to compute the normal. For planar faces this is =
correct. "

  | v1 v2 v3 d1 d2 |
    v1 _ vi at: 1.
    v2 _ vi at: 2.
    v3 _ vi at: 3.
    d1 _ v3 - v1.
    d2 _ v2 - v1.
    d1 safelyNormalize.
    d2 safelyNormalize.
    ^(d1 cross: d2) safelyNormalize.! !=0D=0D!B3DTestSimpleMesh =
methodsFor: 'demo1' stamp: 'BG 9/24/2002 =
12:12'!=0DcreateLightsForScene1: aScene

	| light1 light2 light3 |

	light1 :=3D B3DDirectionalLight new.
	light1 direction: 100 @ 0 @ 0.
     light1 lightColor: (B3DMaterialColor color: (Color r: 0.8 g: 0.15 =
b: 0.15)).
	aScene lights add: light1.

	light2 :=3D B3DDirectionalLight new.
	light2 direction: (120 degreesToRadians cos) * 100  @ (120 =
degreesToRadians sin * 100) @ 0.
     light2 lightColor: (B3DMaterialColor color: (Color r: 0.15 g: 0.8 =
b: 0.15)).
	aScene lights add: light2.

	light3 :=3D B3DDirectionalLight new.
	light3 direction: (240 degreesToRadians cos) * 100  @ (240 =
degreesToRadians sin * 100) @ 0.
     light3 lightColor: (B3DMaterialColor color: (Color r: 0.15 g: 0.15 =
b: 0.8)).
	aScene lights add: light3.! !=0D=0D!B3DTestSimpleMesh methodsFor: =
'demo1' stamp: 'BG 9/24/2002 12:11'!=0DcreateScene1

	| camera |

	camera _ B3DCamera new.
	camera position: 0 at 0@-6.
	camera target: 0 at 0@0.
	camera fov: 15.0.

	scene _ B3DScene new.
	scene defaultCamera: camera.

     self createSolidsForScene1: scene;
          createLightsForScene1: scene.! !=0D=0D!B3DTestSimpleMesh =
methodsFor: 'demo1' stamp: 'BG 9/24/2002 =
13:44'!=0DcreateSolidsForScene1: aScene

	| sceneObj mat |

	sceneObj _ B3DSceneObject named: 'Polyhedron'.
	sceneObj geometry: self createBody.
     mat :=3D B3DMaterial new.
	mat shininess: 0.9;
          specularPart: (Color gray: 0.99).=20

	sceneObj material: mat.

	aScene objects add: sceneObj.! !=0D=0D!B3DTestSimpleMesh methodsFor: =
'demo1' stamp: 'BG 9/24/2002 12:15'!=0Dshow1


    " B3DTestSimpleMesh new show1"

     | view |

  self createScene1.
  (view :=3D B3DSceneExplorerMorph new)
     scene:  scene.
 view clearColor: (Color gray: 0.5).
  view rotateX: 25.4.
  view
     openInWorld.! !=0D=0D
------=_NextPart_000_003F_01C26412.6C05BEE0
Content-Type: application/octet-stream;
	name="workaround.cs"
Content-Transfer-Encoding: quoted-printable
Content-Disposition: attachment;
	filename="workaround.cs"

'From Squeak3.2 of 11 July 2002 [latest update: #4952] on 24 September =
2002 at 8:28:47 pm'!=0D"Change Set:		workaround=0DDate:			24 September =
2002=0DAuthor:			Boris Gaertner=0D=0Da workaround to avoid a VM chrash =
when triangles are rendered."!=0D=0D=0D!B3DSimpleMeshFace methodsFor: =
'rendering' stamp: 'BG 9/24/2002 13:43'!=0DrenderOn: aRenderer
	^aRenderer" trackEmissionColor: true;"		"Turn on pre-lit colors"
			drawPolygonAfter:[
		aRenderer normal: self normal.
		1 to: self size do:[:i| (self at: i) renderOn: aRenderer].
          self size =3D 3
            ifTrue: [(self at: 1) renderOn: aRenderer]
	].! !=0D=0D
------=_NextPart_000_003F_01C26412.6C05BEE0--




More information about the Squeak-dev mailing list