Balloon3D problem

David Duke D.Duke at bath.ac.uk
Tue Jul 2 14:04:27 UTC 2002


Hello,

I'm having a problem involving Balloon3D; I'm a relative newcomer to 
using squeak, and I'm not sure if its the system, or my assumptions!

Background: I want to do some experiments with 3D interactions, and so I 
started exploring the Balloon3D and Wonderland implementations to try 
and understand the protocol needed to build and render 3D objects.  I 
set up what seemed like a simple test to render a cone, using the 
classes B3DSceneMorph and B3DBox as models.  The result was that squeak 
crashed with a segmentation fault!

Using the debugger, I narrowed the problem down to the message 
primAddObject invoked on self in 
B3DPrimitiveRasterizer>>addPrimitiveObject:ofSize:
I wanted to understand what the parameters to this method _should_ look 
like (so I could compare with what was being passed through from my 
code).  B3DSceneMorph seems to work okay, so I edited 
addPrimitiveObject:ofSize: and added `self halt' at the start of the 
method, after the temporary variables are defined.  I then ran 
`B3DSceneMorph new openInWorld' from the transcript, with the hope of 
getting a debugger that would let me explore the objects were being used 
in rendering the B3DBox used in the demo.

Now the problem: I get not one, but two debugger windows opening, 
neither of which will respond to user input.  In fact, the entire squeak 
application seems to lock up.

Any comments on the problem invoking the debugger would be appreciated. 
  I've been using the 3.2gamma image, change set 4881.  I've had the 
same problem with 3.1beta and 3.2gamma4 images, all running under linux.


Also, if someone who is familiar with Balloon3D has a moment to look at 
the two attached classes, I would appreciate any comments on what I'm 
doing (or rather failing to do) in these.  Any pointers to other 
examples and/or documentation on Balloon3D would be helpful.

	thanks,
	David


-- 
Dr. David Duke                        Email: D.Duke at bath.ac.uk
Department of Computer Science        Web:   www.bath.ac.uk/~masdad/
University of Bath                    Tel:   +44 1225 323 407
Bath, BA2 7AY U.K.                    Fax:   +44 1225 323 493
-------------- next part --------------
'From Squeak3.2gamma of 15 January 2002 [latest update: #4881] on 2 July 2002 at 2:47:34 pm'!
B3DGeometry subclass: #B3DCone
	instanceVariableNames: 'vertices normals bbox '
	classVariableNames: 'Colors Faces '
	poolDictionaries: ''
	category: 'DJD - Balloon3D'!
!B3DCone commentStamp: 'DJD 7/2/2002 14:47' prior: 0!
Build a cone, approximated by a 6-sided pyramid, i.e. 6 triangular faces and a hexagonal base.
Allow the cone to be rendered via Balloon3D.

Instance variables:
vertices		Array of B3DVector3			-- 7 vertices of the cone, 1-6 around the base, 7 is the apex.
normals		Array of B3DVector3			-- 7 normal vectors, one per face.  
bbox		Rectangle					-- bounding box for the cone.

Class variables:
Faces		Array of Array of Number	-- per-face indexes into vertex array
Colors		Array of Color				-- per-face color.

Construction:
B3DCone radius: R height: H builds cone with base inscribed in a circle of radius R, and with height H.

Note:
Class variables (Faces and Colors) need to be initialized.  This is done in the class method "initialize". Q: who invokes this?
!


!B3DCone methodsFor: 'as yet unclassified' stamp: 'DJD 7/2/2002 13:01'!
boundingBox
	^ bbox! !

!B3DCone methodsFor: 'as yet unclassified' stamp: 'DJD 7/2/2002 14:32'!
buildWithRadius: r height: h
	"Make a 6-sided cone with base radius r and height h.  The base is in the x-y plane, the apex is
      along the positive z-axis."

	vertices _ Array new: 7.
	"Define the vertices for the base - vertex numbers 1-6"
	1 to: 6 do: [:i |
		vertices at: i put: B3DVector3 new.
		(vertices at: i) x: (r * ((i * Float pi / 3.0) cos)) y: (r * ((i * Float pi / 3.0) sin)) z: 0.0.
	].
	"Cone apex is vertex 7."
	vertices at: 7 put: B3DVector3 new.
	(vertices at: 7) x: 0.0 y: 0.0 z: h.

	"Calculate normals for the triangular sides."
	normals _ Array new: 7.
	1 to: 6 do: [:i | | vecA vecB |
		vecA _ (vertices at: ((Faces at: i) at: 1)) - (vertices at: ((Faces at: i) at: 2)).
		vecB _ (vertices at: ((Faces at: i) at: 1)) - (vertices at: ((Faces at: i) at: 3)).
		normals at: i put: (vecA cross: vecB) normalized.
	].
	"Base normal is unit vector along negative z axis."
	normals at: 7 put: B3DVector3 new.
	(normals at: 7) x: 0.0 y: 0.0 z: (1.0 negated).

	"Calculate bounding box for the cone.  In fact, the box returned is slightly larger
	 than required."
	bbox _ Rectangle origin: (r @ r @ 0) corner: ((r negated) @ (r negated) @ h).
	
! !

!B3DCone methodsFor: 'as yet unclassified' stamp: 'DJD 7/2/2002 14:35'!
renderOn: aRenderer 
	"Render the cone using aRenderer; code based on B3DBox>>renderOn."
	"Render the triangular sides."
	1 to: 6 do: [:i | 
		aRenderer 
			trackEmissionColor: true;
			normal: (normals at: i);
			color:   (Colors at: i);
			drawPolygonAfter: [
				1 to: 3 do: [:v |
					aRenderer
						vertex: (vertices
							at: ((Faces at: i) at: v)).
				]
			]
		].
	"Render the base."
	aRenderer 
		trackEmissionColor: true;
		color: (Colors at: 7);
		drawPolygonAfter: [
			1 to: 6 do: [:v | aRenderer vertex: (vertices at: ((Faces at: 7) at: v)) ]
		].
! !

"-- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- "!

B3DCone class
	instanceVariableNames: ''!

!B3DCone class methodsFor: 'as yet unclassified' stamp: 'DJD 7/2/2002 10:58'!
initialize
	"B3DCone initialize"
	Faces _ #((1 2 3) (1 3 4) (1 4 5) (1 5 6) (1 6 7) (1 7 2) (2 3 4 5 6 7)).
	Colors _ #(red green blue yellow gray cyan white) collect: [:s | (Color perform: s) alpha: 0.5].! !

!B3DCone class methodsFor: 'as yet unclassified' stamp: 'DJD 7/1/2002 17:03'!
radius: rad height: ht
	"Create a cone with the given height and radius."
	^self new buildWithRadius: rad height: ht.

! !


B3DCone initialize!
-------------- next part --------------
'From Squeak3.2gamma of 15 January 2002 [latest update: #4881] on 2 July 2002 at 2:47:42 pm'!
Morph subclass: #SimpleTest
	instanceVariableNames: 'scene renderer camera '
	classVariableNames: ''
	poolDictionaries: ''
	category: 'DJD - Balloon3D'!
!SimpleTest commentStamp: 'DJD 7/2/2002 14:44' prior: 0!
Simple morph subclass to hold the image of a scene rendered via Balloon3D.
Based on B3DSceneMorph.

Instance variables:
scene			B3DScene		-- scene to be rendered, here consisting of a single cone.
renderer		B3DEnginePart?	
camera			B3DCamera
!


!SimpleTest methodsFor: 'as yet unclassified' stamp: 'DJD 7/1/2002 16:56'!
createScene
	| coneObj |
	scene _ B3DScene new.
	camera _ B3DCamera new.
	camera position: 0 @ 0 @ -10.
	self extent: 100 @ 100.
	coneObj _ B3DSceneObject named: 'cone'.
	coneObj
		geometry: (B3DCone radius: 1.0 height: 2.0).
	scene defaultCamera: camera.
	scene objects add: coneObj.! !

!SimpleTest methodsFor: 'as yet unclassified' stamp: 'DJD 7/2/2002 14:37'!
drawOn: aCanvas
	"Draw the scene on aCanvas, using whatever renderer is available."
	| myRect |
	myRect _ (self bounds: bounds in: nil)
				intersect: (0 @ 0 extent: DisplayScreen actualScreenSize).
	(renderer notNil and: [renderer isAccelerated])
		ifFalse: [
			renderer ifNotNil: [renderer destroy].
			renderer _ nil
		].
	renderer ifNotNil: [renderer _ renderer bufferRect: myRect].
	renderer 
		ifNil: [
			renderer _ B3DHardwareEngine newIn: myRect.
			renderer ifNil: [^ self drawSimulatedOn: aCanvas]
		]
		ifNotNil: [
			renderer reset
		].
	renderer viewportOffset: aCanvas origin.
	renderer clipRect: aCanvas clipRect.
	self renderOn: renderer.
	Display addExtraRegion: myRect for: self
! !

!SimpleTest methodsFor: 'as yet unclassified' stamp: 'DJD 7/2/2002 10:26'!
drawSimulatedOn: aCanvas 
	"Draw the receiver using the builtin software renderer"
	(renderer notNil and: [renderer isOverlayRenderer])
		ifTrue: [
			"Dump it. We may just being dragged around by the hand."
			renderer destroy.
			renderer _ nil
		].
	aCanvas asBalloonCanvas render: self! !

!SimpleTest methodsFor: 'as yet unclassified' stamp: 'DJD 7/1/2002 15:50'!
initialize
	super initialize.
	self createScene.! !

!SimpleTest methodsFor: 'as yet unclassified' stamp: 'DJD 7/2/2002 11:05'!
renderOn: aRenderer 
	(color isTransparent
			or: [color isTranslucent])
		ifTrue: [aRenderer restoreMorphicBackground: self bounds under: self].
	aRenderer viewport: self bounds.
	aRenderer clearDepthBuffer.
	color isTransparent
		ifFalse: [aRenderer clearViewport: color].
	aRenderer loadIdentity.
	scene renderOn: aRenderer.
	aRenderer restoreMorphicForeground: self bounds above: self! !

!SimpleTest methodsFor: 'as yet unclassified' stamp: 'DJD 7/2/2002 10:19'!
scene
	^ scene.
! !

!SimpleTest methodsFor: 'as yet unclassified' stamp: 'DJD 7/2/2002 10:19'!
scene: aScene
	^ scene _ aScene.
! !


More information about the Squeak-dev mailing list