-----------------------------------------------------------------------------
TSpace subclass: #GridParcelSpace
	instanceVariableNames: 'master gridConfig things gridCoordinate croquetRadius'
	classVariableNames: ''
	poolDictionaries: ''
	category: 'Grid-Croquet'!
-----------------------------------------------------------------------------
!GridParcelSpace commentStamp: '<historical>' prior: 0!
GridParcelSpace is the square unit of rendering.  9 of them are displayed (the one you are in, and 8 neighbors)
when you are in a GridParcelSpace.

It could also be the unit of island connection, but right now it is shared in island with GridWorld.

master		-- currently unused.   points back to the GridWorld.
gridConfig	-- currently immutable.  copied from GridWorld.
things		-- a TGroup with localTransformtion to convert from Grid To Croquet coordinates
gridCoordinate -- the 2D integer coordinate of this parcel in the world
croquetRadius -- cached radius of the parcel in Croquet, not Grid coordinates.

We need to add two transform methods to convert between Croquet and Grid coordinates (or give the matrix).
-----------------------------------------------------------------------------
TObject subclass: #TFrame
	instanceVariableNames: 'objectName objectID objectOwner ownedObjects localTransform globalTransform frameRoot frameParent frameChildren frameChanged visible solid oglid currentUser eventMask test hiliteColor'
	classVariableNames: 'EventBlockRecurse EventKeyboard EventMaskBits EventNone EventPointerDown EventPointerOver'
	poolDictionaries: 'OpenGLConstants GLExtConstants'
	category: 'Croquet-Objects'!
-----------------------------------------------------------------------------
!TFrame commentStamp: 'das 1/22/2006 17:07' prior: 0!
The TFrame class is designed as a heirarchical transformation frame. The rendering engine walks through the frame, performing the appropriate transformation associated with it, then it calls the render methods of the tObjects. Two passes are made through the frame heirarchy. The first is for non-alpha objects, the second for alpha. The base frame is owned by a TSpace object. We render from the root up because we want to minimize setting transforms.


" ***** This is how you rotate an object using a quaternion ball. The base position is stored in the selectedPoint and compared with the pointer selectedPoint.
	pointer event2D shiftPressed ifTrue:[
		pointer frame: self pickSphere: Vector3 new radiusSquared: selectedRadiusSquared.
		spin _ self rotFromBallPoints: selectedPoint to: pointer selectedPoint.
		trans _ self translation.
		self translationX: 0.0 y:0.0 z:0.0.
		self localTransform: (self localTransform composeWith: spin).
		self translation: trans.
		]"
" ***** This is how you move an object relative to a specified plane. In this case, it is the plane determined by either the camera or the surface normal when the object is selected. 
	- cameraNorm defines the plane perpendicular to the line of sight of the camera
	- selectedNorm defines the norm of the selected surface of the object.
	- slab frontNorm forces a normal to the front of the slab (for example).
	ifFalse:[
	(pointer frame: self pickPlane: selectedPoint normal: cameraNorm) ifTrue:[
		delta _ selectedPoint - pointer selectedPoint.
		self translation: (self translation - (self orientation localPointToGlobal: delta)).
		^ true.].]."
	^ false.

objectName - a name that can be given to any TFrame by the programmer. This is used by mesh importers to set the corresponding node names.
objectID - a unique value generated by TObjectID. This is used as the default name of the TFrame when we register it with the Island.
objectOwner - this is the TFrame that "owns" this TFrame. In this case, ownership is which frame processes events that are sent to this frame.
ownedObjects - this is a dictionary of all of the objects that this TFrame is referenced by. It utilizes the TFrame objectID as the key.
localTransform - the 4x4 matrix transform of this frame relative to it's parent frame.
globalTransform - the transform relative to the global coordinates (the root).
globalPosition - the position of the frame in global coordinates. This is for faster access.
frameRoot - this is the root frame of the heirarchy, usually a TSpace. The root of a TSpace is self.
frameParent - the parent frame of this TFrame.
frameChildren - an OrderedCollection of children frames.
frameChanged - this flag is set when any change occurs to the transform (among other things). This forces a recalculation of the globalTransform.
visible - boolean flag indicating that this object is (or isn't) visible.
solid - boolean flag indicating that this object is solid, that is, can be picked and walked on.
oglid - a TObjectID used by the renderer to maintain a link between the TFrame and its display lists (if any).
currentUser - probably a bad idea ...
test - used for testing

#start/#stop are called when a TFrame is inserted into a hierarchy. They can be used to start and stop future messages.
DAS!


-----------------------------------------------------------------------------
Object subclass: #TObject
	instanceVariableNames: 'myProperties'
	classVariableNames: ''
	poolDictionaries: ''
	category: 'Croquet-Kernel-Objects'!
-----------------------------------------------------------------------------
!TObject commentStamp: '<historical>' prior: 0!
A base class for dealing with some unpleasantness of registries etc.

Instance variables:
	myProperties	<TObjectProperties>	The extra properties for this object.
-----------------------------------------------------------------------------
TFrame subclass: #TSpace
	instanceVariableNames: 'color lightFrames portalFrames rayFrames tframes updateFrames alphaObjects cullBackFaces fogOn fogStart fogEnd fogDensity ambientSound testRays savedAlphaObjects defaultAvatar scriptContext defaultMaterial defaultLaserColors'
	classVariableNames: ''
	poolDictionaries: ''
	category: 'Croquet-Objects'!
-----------------------------------------------------------------------------
!TSpace commentStamp: 'das 6/8/2006 17:00' prior: 0!
A TSpace object acts as the root render frame. It is the ultimate container, and is the entry point to a render tree. TSpace objects are contained in CroquetPlace objects, and can be linked via portals. 

croquetPlace - the CroquetPlace object that this TSpace belongs to.
color - the default color of the space. This is the color you see when there are no objects to render.
lightFrames - an OrderedCollection of all of the TLights in the hierarchy inside of this space.
portalFrames - an OrderedCollection of all ofthe TPortals in the hierarchy inside ofthis space.
rayFrames - an OrderedCollection of all of the TRays in the hierarchy inside of this space.
alphaObjects - a temporay OrderedCollection of the alpha objects to be drawn in each rendered frame.
currentParent - the current parent object of the frame being rendered. This is used for instanced objects.
currentTransform - the current transform of the frame.
cullBackFaces - this is a flag to turn this on and off for everything in the space.
fogOn fogStart fogEnd fogDensity - fog state variables.
ambientSound - current local sound - to be deprecated.
locator - url object.
dropInFrame - drop the TAvatar at this location when we enter the TSpace.
testRays - turn ray testing on and off (e.g. for portal rendering)
savedAlphaObjects - push the alpha objects list onto this stack if we ever recurse into the space WHILE we are rendering it. This actually happens with the TPortal3D.
viewingParticipants - participants currently viewing (rendering) the space, directly or
	through portals they view the space from.
	viewingParticipants should be members of the tea party of every object in the space
	and all of the spaces visible through portals.  When a new viewingParticipant is added
	we walk through all the frames in the space, telling them about the new participant.
	When a new child is added, we first tell it about all of the participants that are viewing
	the space containing it, so it can ensure that participant is in its tea party. 
defaultMaterial - if a TFrame object does not specify a material when it is rendering, it will use this material defined by the TSpace.

DAS!


addAlpha:

TSpace {accessing}
addAlpha: ao alphaObjects class == Array ifTrue:[^self]. alphaObjects add: ao.

addAlphaObject: transform: distance: parent: transparency:

TSpace {accessing}
addAlphaObject: anObject transform: aTransform distance: aDistance parent: aParent transparency: trans alphaObjects class == Array ifTrue:[^self]. alphaObjects add: (TRenderAlpha object: anObject transform: aTransform distance: aDistance parent: aParent transparency: trans).! !

addChild:

TFrame {hierarchy}
addChild: child frameChildren ifNil:[frameChildren := OrderedCollection new.]. "We can not add this frame until we have removed it from a previous parent." child isFrame ifTrue:[ child parent ifNotNil:[child parent removeChild: child]. "Register the child if it can handle events. It remains its own object owner." child eventMask~=EventNone ifTrue:[child register.] ifFalse:[ objectOwner eventMask ~= EventNone ifTrue:[ objectOwner addOwnership: child.]. ]. "make sure child and all its subframes are informed of all viewers so they can be added to their tea parties" frameChildren add: child. child root: self root. child parent: self. child addLightFrames. child addPortalFrames. child addRayFrames. self signal: #structureChanged. child frameChanged. self root ifNotNil:[self root doStart:child. ]. ] ifFalse:[ child isPostcard ifTrue:[ frameChildren add: child. ].].! !

addChild: byUser:

TFrame {*Wisconsin-SDK}
addChild: aTFrame byUser: anAvatar "Adding an object by a user. Might position relative to the user, or might provide some visual indication of who it came from." self addChild: aTFrame.! !
TSpace {*Wisconsin-SDK}
addChild: aTFrame byUser: anAvatar | transform | transform := anAvatar globalTransform copy. transform translation: (transform translation - (5 * (anAvatar lookAt))). aTFrame localTransform: transform. super addChild: aTFrame byUser: anAvatar.! !

addFrame:

TSpace {accessing}
addFrame: frame tframes at: frame objectID put: frame.! !

addLightFrame:

TFrame {frameManagement}
addLightFrame: litefrm frameParent ifNotNil:[frameParent addLightFrame: litefrm.]! !
TSpace {frameManagement}
addLightFrame: ltfrm lightFrames add: ltfrm.! !

addLightFrames

TFrame {frameManagement}
addLightFrames " When a frame is added as a child, any lights included in the heirarchy are reported to the base TRoom." self isLight ifTrue:[ self addLightFrame: self]. frameChildren ifNotNil: [frameChildren do:[ :fc | fc addLightFrames ].]. ! !

addOwnership:

TFrame {ownership}
addOwnership: frame frame = self ifTrue:[ ^self ]. "we don't add ourselves to the list" frame eventMask~=EventNone ifTrue:[ ^self ]. "don't add components" ownedObjects ifNil:[ ownedObjects := Dictionary new.]. ownedObjects at: frame objectID put: frame. frame forceObjectOwner: self. frame frameChildrenDo:[:child | self addOwnership: child. ].

addPortalFrame:

TFrame {frameManagement}
addPortalFrame: prtlFrm frameParent ifNotNil:[frameParent addPortalFrame: prtlFrm.]! !
TSpace {frameManagement}
addPortalFrame: prtlFrm portalFrames add: prtlFrm.! !

addPortalFrames

TFrame {frameManagement}
addPortalFrames " When a frame is added as a child, any portals included in the heirarchy are reported to the base TRoom." self isPortal ifTrue:[ self addPortalFrame: self]. frameChildren ifNotNil: [frameChildren do:[ :fc | fc addPortalFrames ].]. ! !

addRayFrame:

TFrame {frameManagement}
addRayFrame: rayfrm frameParent ifNotNil:[frameParent addRayFrame: rayfrm.]! !
TSpace {frameManagement}
addRayFrame: rayfrm rayFrames add: rayfrm.! !

addRayFrames

TFrame {frameManagement}
addRayFrames " When a frame is added as a child, any rays included in the heirarchy are reported to the base TSpace." self isRay ifTrue:[ self addRayFrame: self]. frameChildren ifNotNil: [frameChildren do:[ :fc | fc addRayFrames ].]. ! !

addRotationAroundX:

TFrame {transform}
addRotationAroundX: anAngle localTransform addRotationAroundX: anAngle. self frameChanged. ^ localTransform.! !

addRotationAroundY:

TFrame {transform}
addRotationAroundY: anAngle localTransform addRotationAroundY: anAngle. self frameChanged. ^ localTransform.! !

addRotationAroundZ:

TFrame {transform}
addRotationAroundZ: anAngle localTransform addRotationAroundZ: anAngle. self frameChanged. ^ localTransform.! !

addUpdate:

TSpace {rootService}
addUpdate: frame updateFrames ifNotNil:[ updateFrames do:[ :uf | uf update. ]. updateFrames := nil. ].! !

addYaw:

TFrame {transform}
addYaw: y self yaw: self yaw + y.! !

alphaObjects

TSpace {accessing}
alphaObjects ^ alphaObjects.! !

alphaObjects:

TSpace {accessing}
alphaObjects: ao alphaObjects := ao.! !

ambientSound

TSpace {ambient sound}
ambientSound ^ambientSound! !

ambientSound:

TSpace {ambient sound}
ambientSound: aSound ambientSound := aSound.

ambientSoundFadeFrom: to: duration:

TSpace {ambient sound}
ambientSoundFadeFrom: startVolume to: endVolume duration: msec | steps stepSize | steps := (msec / 20.0) asInteger. steps <= 0 ifTrue: [^self]. stepSize := (endVolume - startVolume) / steps. stepSize = 0.0 ifTrue: [^self]. self ambientSoundFadeVolume: startVolume stepSize: stepSize forSteps: steps finalVolume: endVolume.

ambientSoundFadeVolume: stepSize: forSteps: finalVolume:

TSpace {ambient sound}
ambientSoundFadeVolume: startVolume stepSize: stepSize forSteps: steps finalVolume: endVolume steps = 0 ifTrue: [ ambientSound volume: endVolume. ^self ]. ambientSound volume: startVolume. self future: 20.0 deferRelative: 20.0 perform: #ambientSoundFadeVolume:stepSize:forSteps:finalVolume: withArguments: { startVolume + stepSize . stepSize . steps - 1 . endVolume }.

ambientSoundPauseComplete

TSpace {ambient sound}
ambientSoundPauseComplete ambientSound pause. ambientSound volume: 0.0.

ambientSoundPlaying

TSpace {ambient sound}
ambientSoundPlaying ambientSound ifNotNil:[^ambientSound isPlaying.]. ^ false.

asFarRef

TFrame {Islands}
asFarRef ^ Processor activeIsland asFarRef:self.! !

at:

TFrame {accessing}
at: index ^ frameChildren at: index.! !

attachBehavior:

TFrame {scripts}
attachBehavior: aBehavior aBehavior target == self ifFalse:[^aBehavior attachTo: self]. self myBehaviors: (self myBehaviors copyWith: aBehavior).! !

attachScript: named: owner:

TFrame {scripts}
attachScript: scriptCode named: scriptName owner: avatar "Attach the given script to the receiver" | mgr | mgr := self root scriptManager. mgr ifNotNil:[mgr attachScript: scriptCode named: scriptName to: self owner: avatar].! !

avatars

TSpace {accessing}
avatars "Answer an array of avatars in this space. Only searches top-level right now." ^Array streamContents:[:s| self frameChildren do:[:fc| fc isAvatar ifTrue:[s nextPut: fc]] ].! !

baseMaterial:

TFrame {accessing}
baseMaterial: mat frameChildren ifNil:[^self]. frameChildren do:[:each| each material: mat].! !

billboard:

TFrame {transform}
billboard: cam | mat pos out target dir sin angle | mat := self globalTransform. pos := mat a14 @ mat a34. out := (mat a13 @ mat a33) normalized. mat := cam globalTransform. target := mat a14 @ mat a34. dir := (target - pos) normalized. sin := dir crossProduct: out. angle := ((dir dotProduct: out)*0.9999999) arcCos radiansToDegrees. mat := Matrix4x4 identity. mat rotationAroundY: angle * sin sign. localTransform := localTransform composedWithLocal: mat. globalTransform := globalTransform composedWithLocal: mat.

boundSphere

TFrame {accessing}
boundSphere " This will return a render bounds object if one exists. This is a TBoundSphere (location + radius), which is used to determine if a particular object is inside the clipping planes or for collision detection tests. Otherwise, the object will be assumed to have a local coordinate location of 0,0,0 and a radius of 1.0." ^ nil.

boundSpheresDo:

TFrame {hierarchy}
boundSpheresDo: aBlock | bSphere | bSphere := self boundSphere. bSphere ifNotNil:[^aBlock value: bSphere]. frameChildren ifNil:[^self]. self frameChildren do:[:each| each boundSpheresDo: aBlock].

boundingBox

TFrame {accessing}
boundingBox "Answer the bounding box for the receiver and its children" ^ self boundingBox: Matrix4x4 identity.

boundingBox:

TFrame {accessing}
boundingBox: trans "Answer the bounding box for the receiver and its children" | box childBox | box := self frameBox. self frameChildrenDo:[:child| childBox := child boundingBox transformedBy: (trans * child localTransform). box := box merge: childBox. ]. ^box! !

boundsChanged

TFrame {accessing}
boundsChanged " Does nothing"

boundsDepth:

TFrame {accessing}
boundsDepth: depth frameChildren ifNotNil:[ frameChildren do:[:fc | fc boundsDepth: depth].].! !

changed:

TFrame {accessing}
changed: frame " Does nothing, just forward on to parent." self parent ifNotNil:[self parent changed: frame.]

checkMotion: forAvatar:

TSpace {accessing}
checkMotion: aVector forAvatar: anAvatar "A filtering opportunity for subclasses to enforce motion constraints on avatars (such as confining the avatars to a particular region, or particular paths.) The input is a vector motion to apply to the avatar; the return value is the resulting translation for the avatar. All avatar replica driving operations should be filtered through this method. The base implementation simply allows the motion, unaltered. Note that 'goTo' operations (such as are used for landmarks) are not filtered; this allows the creation of viewpoints outside the drivable bounds of a space. As soon as an avatar at such an outside location is moved, it will be warped back into a space if the space confines the avatar." ^ anAvatar localTransform translation + aVector! !

child:

TFrame {hierarchy}
child: index ^frameChildren at: index.! !

childAt:

TFrame {accessing}
childAt: index ^ frameChildren at: index.! !

childChanged

TFrame {accessing}
childChanged self childChanged: self.! !

childChanged:

TFrame {accessing}
childChanged: frame " Does nothing, just forward on to parent." self parent ifNotNil:[self parent changed: frame.]

clearCurrentUser:

TFrame {*Wisconsin-SDK}
clearCurrentUser: userID | event | "There can be only one. No sense going further." currentUser = userID ifTrue: [ event := CroquetEvent new userID: userID. event selection: TSelection new. event selection frame: self. self doPointerLeave: event. "currentUser := nil. " ^self ]. self frameChildrenDo: [:child | (child clearCurrentUser: userID) ifNotNilDo: [:x | ^x]]. ^nil.! !

clipPlane

TFrame {accessing}
clipPlane ^Vector3 x: 0.0 y:0.0 z:-1.0.

collapse

TFrame {hierarchy}
collapse "Forces all frames to identity transform while retaining translation, and pushes the previous transform to the frame children. This is used primarily for meshes and their supporting groups." | orient trans | trans := self translation. orient := self orientation. frameChildren ifNotNil:[ frameChildren do:[ :fc | fc localTransform: (orient * fc localTransform). fc collapse. ]. ]. self localTransform: Matrix4x4 identity. self translation: trans.

collidesInto:

TFrame {events}
collidesInto: aFrame "Answer whether I collide into the given frame" | mySphere itsSphere | mySphere := self compositeBoundSphere ifNil:[^false]. itsSphere := aFrame compositeBoundSphere ifNil:[^false]. ^mySphere collideSphere: itsSphere! !

collision:

TFrame {enterExit}
collision: frame ^ false.! !

color

TSpace {accessing}
color ^ color.! !

color:

TSpace {accessing}
color: clr color := clr asVectorColor.! !

colorize:

TFrame {accessing}
colorize: color "Use the given color to paint the frame and its children as both their ambient and diffuse colors."! !

compositeBoundSphere

TFrame {accessing}
compositeBoundSphere "Answer either my own or a composition of my children's bound spheres" | children bSphere | children := OrderedCollection new. self boundSpheresDo:[:bs| bSphere := bs union: bSphere. children add: bs. ]. children size = 0 ifTrue:[^nil]. children size = 1 ifTrue:[^children first]. bSphere children: children. bSphere frame: self. bSphere transform: self globalTransform. ^bSphere

connectContentsFrom: intoContainer:

TFrame class {*Wisconsin-SDK}
connectContentsFrom: input intoContainer: myInstance ^myInstance future contents: input.! !

costume

TFrame {accessing}
costume ^ self.! !

cullBackFaces

TSpace {accessing}
cullBackFaces ^ cullBackFaces.! !

cullBackFaces:

TSpace {accessing}
cullBackFaces: bool cullBackFaces := bool.! !

cullFace:

TFrame {accessing}
cullFace: bool frameChildren ifNotNil:[frameChildren do:[:fc | fc cullFace: bool]].! !

currentHiliteColor

TFrame {accessing}
currentHiliteColor "If this frame is currently hilit, return the hilighting color in use; otherwise return nil." ^ hiliteColor! !

currentParent:

TFrame {hierarchy}
currentParent: fParent frameParent := fParent.! !

cut:

TFrame {*Wisconsin-SDK}
cut: event self island controller clipboard copyToClipboard: self by: event userID. self destroy. self scheduleSelfDestruct.! !

deepRegisterIntoIsland:

TFrame {*Wisconsin-SDK}
deepRegisterIntoIsland: anIsland | index | anIsland lookup: objectID ifAbsent:[ anIsland register: self name: objectID. index := self class instSize. [index > 0] whileTrue: [ (self instVarAt: index) deepRegisterIntoIsland: anIsland. index := index - 1. ]. ].! !

defaultAvatar

TSpace {accessing}
defaultAvatar ^defaultAvatar! !

defaultAvatar:

TSpace {accessing}
defaultAvatar: atarData defaultAvatar := atarData! !

defaultMaterial

TSpace {accessing}
defaultMaterial ^ defaultMaterial.! !

defaultMaterial:

TSpace {accessing}
defaultMaterial: dm defaultMaterial := dm.! !

defaultObjectName

TFrame class {accessing}
defaultObjectName "Answer the default object name for instances: TWindow defaultObjectName -> 'TWindow' TCube defaultObjectName -> 'TCube' " ^self name asString! !

delete

TFrame {hierarchy}
delete self destroy.! !

destroy

TFrame {hierarchy}
destroy frameParent ifNotNil:[frameParent removeChild: self].

detachBehavior:

TFrame {scripts}
detachBehavior: aBehavior aBehavior target == nil ifFalse:[ aBehavior target == self ifFalse:[^self error:'Behavior is not owned by me']. ^aBehavior detach]. self myBehaviors: (self myBehaviors copyWithout: aBehavior).! !

disableClipPlane:

TFrame {render}
disableClipPlane: ogl ogl glDisable: GLClipPlane0.

distanceTo:

TFrame {accessing}
distanceTo: aFrame ^(self globalPosition - aFrame globalPosition) length! !

do:

TFrame {accessing}
do: block block value: self. frameChildren ifNotNil:[ frameChildren do:[ :fc | fc do: block].].

doForPick:

TFrame {accessing}
doForPick: block "This is essentially a #do: method that stops at a TQuadTree instead of traversing its hierarchy as well. This is to prevent the #pick: methods from being called multiple times for the same TFrame." block value: self. frameChildren ifNotNil:[ frameChildren do:[ :fc | fc doForPick: block].].

doKeyDown:

TFrame {events}
doKeyDown: event (self eventMask anyMask: EventKeyboard) ifTrue:[ event selection frame ifNil:[ event selection frame: (self getOwnedObject: event selection frameID). ]. self keyDown: event. self signal: #keyDown with: event. ] ifFalse:[ "otherwise recurse up the hierarchy" frameParent ifNotNil:[ frameParent objectOwner doKeyDown: event. ]. ].! !

doKeyStroke:

TFrame {events}
doKeyStroke: event (self eventMask anyMask: EventKeyboard) ifTrue:[ event selection frame ifNil:[ event selection frame: (self getOwnedObject: event selection frameID). ]. self keyStroke: event. self signal: #keyStroke with: event. ] ifFalse:[ "otherwise recurse up the hierarchy" frameParent ifNotNil:[ frameParent objectOwner doKeyStroke: event. ]. ].! !

doKeyUp:

TFrame {events}
doKeyUp: event (self eventMask anyMask: EventKeyboard) ifTrue:[ event selection frame ifNil:[ event selection frame: (self getOwnedObject: event selection frameID). ]. self keyUp: event. self signal: #keyUp with: event. ] ifFalse:[ "otherwise recurse up the hierarchy" frameParent ifNotNil:[ frameParent objectOwner doKeyUp: event. ]. ].! !

doPointerDown:

TFrame {events}
doPointerDown: event (self eventMask anyMask: EventPointerDown) ifTrue:[ (currentUser isNil or:[currentUser = event userID]) ifTrue:[ event selection frame ifNil:[ event selection frame: (self getOwnedObject: event selection frameID). ]. self pointerDown: event. currentUser := event userID. self signal: #pointerDown with: event. ]. ] ifFalse:[ "now recurse up the hierarchy" frameParent ifNotNil:[ frameParent objectOwner doPointerDown: event. ]. ].! !

doPointerEnter:

TFrame {events}
doPointerEnter: event (self eventMask anyMask: EventPointerOver) ifTrue:[ currentUser ifNil:[ event selection frame ifNil:[ event selection frame: (self getOwnedObject: event selection frameID). ]. currentUser := event userID. self pointerEnter: event. self signal: #pointerEnter with: event. ]. ]. (self eventMask anyMask: EventBlockRecurse)ifFalse:[ "now (always) recurse up the hierarchy" frameParent ifNotNil:[ frameParent objectOwner doPointerEnter: event. ]. ].! !

doPointerLeave:

TFrame {events}
doPointerLeave: event (self eventMask anyMask: EventPointerOver) ifTrue:[ currentUser = event userID ifTrue:[ event selection frame ifNil:[ event selection frame: (self getOwnedObject: event selection frameID). ]. self signal: #pointerLeave with: event. self pointerLeave: event. currentUser := nil. ]. ]. (self eventMask anyMask: EventBlockRecurse)ifFalse:[ "now (always) recurse up the hierarchy" frameParent ifNotNil:[ (frameParent objectOwner getAllEventsHandled anyMask: EventPointerOver) ifTrue:[ frameParent objectOwner doPointerLeave: event. ]. ]. ].! !

doPointerMove:

TFrame {events}
doPointerMove: event (self eventMask anyMask: EventPointerDown) ifTrue:[ currentUser = event userID ifTrue:[ event selection frame ifNil:[ event selection frame: (self getOwnedObject: event selection frameID). ]. self pointerMove: event. self signal: #pointerMove with: event. ]. ] ifFalse:[ "now recurse up the hierarchy" frameParent ifNotNil:[ frameParent objectOwner doPointerMove: event. ]. ].! !

doPointerOver:

TFrame {events}
doPointerOver: event (self eventMask anyMask: EventPointerOver) ifTrue:[ currentUser = event userID ifTrue:[ event selection frame ifNil:[ event selection frame: (self getOwnedObject: event selection frameID). ]. self pointerOver: event. self signal: #pointerOver with: event. ]. ]. (self eventMask anyMask: EventBlockRecurse)ifFalse:[ "now (always) recurse up the hierarchy" frameParent ifNotNil:[ frameParent objectOwner doPointerOver: event. ]. ].! !

doPointerUp:

TFrame {events}
doPointerUp: event (self eventMask anyMask: EventPointerDown) ifTrue:[ currentUser = event userID ifTrue:[ event selection frame ifNil:[ event selection frame: (self getOwnedObject: event selection frameID). ]. self pointerUp: event. self signal: #pointerUp with: event. ]. ] ifFalse:[ "now recurse up the hierarchy" frameParent ifNotNil:[ frameParent objectOwner doPointerUp: event. ]. ].! !

doRenderAlpha:

TFrame {render}
doRenderAlpha: ogl "This is used to render transparent ( alpha blended ) objects." | hilite | hilite := false. self currentHiliteColor ifNotNil: [ hilite := ogl forceHilite: self currentHiliteColor. hilite ifTrue: [ ogl pushFog. ]. ]. ogl transparency < 1.0 ifTrue:[ self render: ogl. ]. self renderAlpha: ogl. hilite ifTrue: [ ogl forceHilite: nil. ogl popFog. ].! !

doStart:

TSpace {frameManagement}
doStart: frame frame do:[:f | (f future: f stepTime)start.].

doStop:

TSpace {frameManagement}
doStop: frame frame do:[:f | f stop.].! !

doUpdate

TFrame {frameManagement}
doUpdate frameRoot ifNotNil:[ frameRoot addUpdate: self. ].! !

dropFiles: pointer:

TFrame {events}
dropFiles: aFileStream pointer: pointer self signal: #dropFiles with: pointer with: aFileStream! !

enableClipPlane:

TFrame {render}
enableClipPlane: ogl "------ enableClipPlane is used to clip the TSpace to the front face of the portal. This ensures that objects don't get rendered in front of the portal, which would look bad and be confusing.------" | equation ov | "------ We need to do it this way, because Squeak does not directly support doubles and gllClipPlane requires an array of same. ------" ov := self clipPlane. equation := ExternalData fromHandle: (ExternalAddress allocate: 8*4) type:ExternalType double. equation getHandle doubleAt: 1 put: ov x. equation getHandle doubleAt: 9 put: ov y. equation getHandle doubleAt: 17 put: ov z. equation getHandle doubleAt: 25 put: 0.0. ogl glPushMatrix; glMultTransposeMatrixf: self globalTransform; glClipPlane: GLClipPlane0 with: equation; glEnable: GLClipPlane0; glPopMatrix. equation free.! !

event2D: !

TFrame {events}
event2D: event2D! !

eventBlockRecurse

TFrame class {accessing}
eventBlockRecurse ^ EventBlockRecurse.! !

eventKeyboard

TFrame class {accessing}
eventKeyboard ^ EventKeyboard.! !

eventMask

TFrame {events}
eventMask "Answer the receiver's event mask" ^eventMask ifNil:[EventNone] "There are three kinds of events - EventKeyboard, EventPointerOver, and EventPointerDown. If this TFrame can handle any combination of events it must return the bitOr combination of the event types, hence, if you handle all three kinds of events, you return: ^ EventKeyboard bitOr: EventPointerOver bitOr: EventPointerDown. If you handle just the keyboard event, return: ^ EventKeyboard. The default is no event or EventNone which we return here."

eventMask:

TFrame {events}
eventMask: newMask "The object owner magic in addChild sets up objectOwner links if the child has a 0 event mask. So, when non-zeroing a mask, we have to undo that situation." (eventMask = EventNone & (newMask ~= EventNone)) ifTrue: [ objectOwner removeOwnership: self. "My kids may have been disowned while I had no mask... so reclaim them." self frameChildrenDo: [:child | self addOwnership: child]. ]. eventMask := newMask.

eventNone

TFrame class {accessing}
eventNone ^ EventNone.! !

eventPointerDown

TFrame class {accessing}
eventPointerDown ^ EventPointerDown.! !

eventPointerOver

TFrame class {accessing}
eventPointerOver ^ EventPointerOver.! !

eventsGenerated

TFrame {yellow-scripts-support}
eventsGenerated "Answer a list of events generated by the receiver" ^#( pointerDown pointerMove pointerUp pointerEnter pointerOver pointerLeave keyDown keystroke keyUp frameChanged ).
TSpace {properties}
eventsGenerated ^super eventsGenerated, #( objectEnter objectLeave )! !

extent

TFrame {accessing}
extent "Answer the bounding box for the receiver and its children" ^ self boundingBox extent.

extent:

TFrame {accessing}
extent: ext "Does nothing"! !

extraProperties

TObject {accessing}
extraProperties "This will always create the properties if they do not exist" ^myProperties ifNil:[myProperties := self newExtraProperties].! !

find:

TFrame {accessing}
find: blockTest | list | blockTest ifNil:[^ nil]. list := OrderedCollection new. self find: blockTest into: list. ^ list.! !

find: into:

TFrame {accessing}
find: blockTest into: list frameChildren ifNotNil:[ frameChildren do:[ :fc | fc find: blockTest into: list].]. (blockTest value: self) ifTrue:[ list add: self].

findFrame:

TSpace {accessing}
findFrame: key ^ tframes at: key.! !

fogColor

TSpace {fog properties}
fogColor ^color! !

fogColor:

TSpace {fog properties}
fogColor: newColor self color: newColor.! !

fogDensity

TSpace {fog properties}
fogDensity ^ fogDensity.! !

fogDensity:

TSpace {fog properties}
fogDensity: fd fogDensity := fd.! !

fogEnd

TSpace {fog properties}
fogEnd ^ fogEnd.! !

fogEnd:

TSpace {fog properties}
fogEnd: fe fogEnd := fe.! !

fogOn

TSpace {fog properties}
fogOn ^ fogOn.! !

fogOn:

TSpace {fog properties}
fogOn: bool fogOn := bool.! !

fogStart

TSpace {fog properties}
fogStart ^ fogStart.! !

fogStart:

TSpace {fog properties}
fogStart: fs fogStart:= fs.! !

forceAlpha

TSpace {render}
forceAlpha ^ false.! !

forceGlobalToLocal

TFrame {frameManagement}
forceGlobalToLocal "This is used by TMesh when the imported vertices are pre-transformed, and all of the nodes are in global coordinates and we want to put them back into their untransformed state. This occurs with the 3DS Max ASE files." frameChildren ifNotNil:[ frameChildren do:[ :fc | fc forceGlobalToLocal.]]. frameParent ifNotNil:[ self localTransform: ( frameParent localTransform orthoNormInverse * self localTransform). ].! !

forceObjectOwner:

TFrame {ownership}
forceObjectOwner: oOwner objectOwner := oOwner.! !

forwardBy: duration: style: rate:

TFrame {yellow-scripts}
forwardBy: aDistance duration: aDuration style: aStyle rate: aSamplingRate ^self move: #forward distance: aDistance duration: aDuration style: aStyle rate: aSamplingRate! !

frameBox

TFrame {accessing}
frameBox "Answer the local bounding box of this frame" self boundSphere ifNotNil:[ ^ self boundSphere box.]. ^TBox origin: 0@0@0 corner: 0@0@0! !

frameChanged

TFrame {accessing}
frameChanged " This guarantees that if we make a change in a parent frame, all of the children are aware and can deal with it properly." frameChanged := true. frameChildren ifNotNil:[ frameChildren do:[ :child | child frameChanged ].]. myProperties ifNotNil:[self signal: #frameChanged]. "to inform interested parties"
TSpace {accessing}
frameChanged " do nothing - frameChanged must always be false "! !

frameChildren

TFrame {accessing}
frameChildren ^ frameChildren.! !

frameChildrenDo:

TFrame {accessing}
frameChildrenDo: aBlock frameChildren ifNil:[^self]. ^frameChildren do: aBlock! !

frameLookAt:

TFrame {transform}
frameLookAt: frame " used to put my lookAt vector into the frame of the argument" ^ frame inverseGlobalOrientation localPointToGlobal: self lookAt negated.

fullBright:

TFrame {accessing}
fullBright: bool frameChildren ifNotNil:[frameChildren do:[:fc | fc fullBright: bool]].! !

getAllEventsHandled

TFrame {events}
getAllEventsHandled " this finds the entire hierarchical event list. Even though this child may not handle an event, it's parent might" frameParent ifNotNil:[ ^self eventMask bitOr:frameParent objectOwner getAllEventsHandled. ] ifNil:[ ^ self eventMask.]. ! !

getOwnedObject:

TFrame {ownership}
getOwnedObject: id id = objectID ifTrue:[^self]. ownedObjects ifNil:[^nil]. ^ id ifNotNil:[ownedObjects at:id ifAbsent:[nil]] ifNil:[nil].! !

getPopupMenuScript: target: openIn: at: carrying: harness:

TFrame class {*Wisconsin-SDK}
getPopupMenuScript: avatar target: target openIn: world at: position carrying: carrying harness: harness "This is the default right click popup menu script, may be overridden by sub classes" ^ [ | menu clipbrd | " Build the menu. " menu := CMenu new. menu add: 'Information' target: KMenuBar action: #showInformationOnFarRef: argument: target. menu add: 'Explore' target: target action: #explore. menu addSeparator. clipbrd := harness clipboard. menu add: 'Cut' target: clipbrd action: #cutToClipboard: argument: target. menu add: 'Copy' target: clipbrd action: #copyToClipboard: argument: target. menu add: 'Copy Material' target: clipbrd action: #copyMaterialToClipboard: argument: target. menu add: 'Copy Contents' target: clipbrd action: #copyContentsToClipboard: argument: target disabled: (target send: [:obj | obj respondsTo: #serializeContents]) not. menu add: 'Paste' target: clipbrd action: #pasteOnto: argument: target disabled: clipbrd isEmpty. menu addSeparator. carrying ifFalse: [ menu add: 'Grab' target: avatar action: #grab: argument: target. ] ifTrue: [ menu add: 'Release' target: avatar action: #release: argument: target. ]. " Open the popup menu. " menu openIn: world at: position. ].

globalMatrixOut

TFrame {transform}
globalMatrixOut " This simply reverses the direction of the matrix for TPortals (see TPortal>>#globalMatrixOut). Otherwise, we just use the globalTransform." ^self globalTransform copy.

globalOrientation

TFrame {transform}
globalOrientation "This is used to return just the orientation part of the matrix.The translation part is 0.0." | mat | mat := self globalTransform clone. mat translationX: 0.0 y: 0.0 z: 0.0. ^ mat.! !

globalPitch

TFrame {transform}
globalPitch ^self globalPitchYawRoll x! !

globalPitchYawRoll

TFrame {transform}
globalPitchYawRoll globalTransform ifNil:[^ 0.0@0.0@0.0]. ^globalTransform pitchYawRoll! !

globalPosition

TFrame {transform}
globalPosition ^ self globalTransform translation.! !

globalPosition:

TFrame {transform}
globalPosition: gp self translation: (frameParent ifNil:[gp] ifNotNil:[frameParent globalToLocal: gp]). ! !

globalRoll

TFrame {transform}
globalRoll ^self globalPitchYawRoll z! !

globalToLocal:

TFrame {accessing}
globalToLocal: anObject ^self globalTransform inverseTransformation localPointToGlobal: anObject! !

globalTransform

TFrame {transform}
globalTransform " This is the global transform of the frame - its location and orientation in global world coordinates. We only calculate this when we have to, which is only when a local coordinate frame has been changed AND when someone asks for it. " frameChanged ifTrue:[ frameParent ifNotNil: [ self globalTransform: ((frameParent globalTransform) * self localTransform)] ifNil:[ self globalTransform: self localTransform.]. ]. ^ globalTransform. " NOT ^ self globalTransform - this causes bad recursion error!!"

globalTransform:

TFrame {transform}
globalTransform: gTrans frameChanged := false. globalTransform := gTrans. self globalTransformUpdate. ^ globalTransform.! !

globalTransformUpdate

TFrame {transform}
globalTransformUpdate " This is called when a new global transfom is calculated. It is designed to be extended by other frame sub-classes, such as TRigidBody, that would have variables that should be updated once when the frame gets changed." self boundSphere ifNotNil:[ self boundSphere transform: globalTransform.].

globalYaw

TFrame {transform}
globalYaw ^self globalPitchYawRoll y! !

gotoFrame:

TFrame {*Wisconsin-SDK}
gotoFrame: event "Mostly copied from #gotoWindow: (only one line changed)" | front distance trans dy aspect atar | atar := event avatar ifNil:[^self]. (self hasAncestor: atar) ifTrue:[^ self]. "don't go there" (self root = atar root) ifFalse:[^self]. "don't go there either" dy := self extent y. dy := dy/2.0. distance := dy/((atar viewAngle degreesToRadians/2.0) tan). aspect := self extent x/self extent y. aspect > atar viewAspect ifTrue:[ distance := aspect*distance/atar viewAspect.]. distance := distance + self frameBox radius. front := Vector3 x: 0 y: 0 z: distance. front := self orientation localPointToGlobal: front. front := self translation + front. trans := self localTransform copy. trans translation: front. atar goto: trans count: 6. ! !

grabFrame:

TFrame {*Wisconsin-SDK}
grabFrame: event "see #grabWindow:" self grabbedBy: event avatar.! !

grabbedBy:

TFrame {*Wisconsin-SDK}
grabbedBy: avatar | trans | avatar ifNil:[^nil]. "Is is a bug that #carrying: doesn't fix the transform? No matter. This will work regardless." trans := avatar globalTransform orthoNormInverse composeWith: self globalTransform. avatar carrying: self. self localTransform: trans.! !

grabbedState:

TFrame {*Wisconsin-SDK}
grabbedState: aBoolean "ignore"! !

gridCoordinate

GridParcelSpace {as yet unclassified}
gridCoordinate ^ gridCoordinate! !

gridScale

GridParcelSpace {as yet unclassified}
gridScale ^ gridConfig gridScale

handlesEvent2D

TFrame {events}
handlesEvent2D ^ false.! !

hasAlpha

TFrame {accessing}
hasAlpha " Does this object have an alpha channel to render? Return true if it does." ^ false.! !

hasAlpha:

TFrame {accessing}
hasAlpha: ogl ^ self hasAlpha or:[ogl transparency < 1.0].! !

hasAlphaObjectsToRender

TSpace {render}
hasAlphaObjectsToRender ^(alphaObjects size ~= 0 or: [self forceAlpha])! !

hasAncestor:

TFrame {hierarchy}
hasAncestor: ancestor "Determines if ancestor is one of our parents, parents parents, etc..." frameParent = ancestor ifTrue:[^ true]. frameParent ifNil:[^ false]. ^ frameParent hasAncestor: ancestor.

hasAncestorOrMe:

TFrame {hierarchy}
hasAncestorOrMe: ancestor "Determines if ancestor is one of our parents, parents parents, etc..." self = ancestor ifTrue:[^ true]. ^ self hasAncestor: ancestor.

hasChild:

TFrame {hierarchy}
hasChild: child frameChildren ifNotNil:[ frameChildren do:[:fc | fc = child ifTrue:[^ true ].].]. ^ false.

hasOpaque

TFrame {accessing}
hasOpaque ^ true.! !

hasOpaque:

TFrame {accessing}
hasOpaque: ogl ^ self hasOpaque and:[ogl transparency = 1.0].! !

hilite

TFrame {accessing}
hilite "Hilight this frame and its children. The effect lasts until the state is cleared with 'frame unhilite.' " hiliteColor := Color white asVectorColor.! !

hilite:

TFrame {accessing}
hilite: aColor "Hilight this frame and its children with a default hilite color. The effect lasts until the state is cleared with 'frame unhilite.' " aColor ifNil: [ self unhilite. "self hilite:nil == self unhilite." ] ifNotNil: [ hiliteColor := aColor asVectorColor ].! !

homeTransform:

TSpace {accessing}
homeTransform: avatar "Return the transform used to return an avatar to a safe place." ^ Matrix4x4 identity.! !

inPortal

TSpace {accessing}
inPortal " returns a portal s.t. the space itself is the viewPoint. This is useful for fixed camera position portals." | portal | portal := TPortal new. portal postcardLink: self postcard. ^ portal.

inertiaTensor

TFrame {accessing}
inertiaTensor ^ nil.! !

initBounds

TFrame {initialize}
initBounds frameChildren ifNotNil:[ frameChildren do:[:fc | fc initBounds].].! !

initialAvatarTranslation:

TSpace {accessing}
initialAvatarTranslation: avatar "Return the initial position for the given avatar. Avatars added to the space with addToNewSpace: will be placed here." ^ nil! !

initialAvatarYaw:

TSpace {accessing}
initialAvatarYaw: avatar "Return the initial yaw for the given avatar. Avatars added to the space with addToNewSpace: will be rotated to this yaw." ^ nil! !

initialize

TFrame class {class initialization}
initialize "TFrame initialize" EventNone := 0. EventKeyboard := 1. EventPointerDown := 2. EventPointerOver := 4. EventBlockRecurse := 32. "EventMaskBits map event names to their required eventMask bits. E.g., for getting notifications about the pointerOver event we need to set the EventPointerOver bit and in this dictionary provides that mapping." EventMaskBits := IdentityDictionary new. { {EventKeyboard. #keyDown. #keyStroke. #keyUp }. {EventPointerDown. #pointerDown. #pointerUp. #pointerMove }. {EventPointerOver. #pointerEnter. #pointerLeave. #pointerOver }. } do:[:spec| spec allButFirst do:[:evtName| EventMaskBits at: evtName put: spec first]. ].! !
TFrame {initialize}
initialize super initialize. frameChanged := true. localTransform := Matrix4x4 identity. globalTransform := Matrix4x4 identity. frameChildren := nil. frameRoot := nil. eventMask := EventNone. self solid: true. self visible: true. objectOwner := self. objectID := TObjectID for: self. objectName := 'a', self class asString. self register. test := nil. ^self
TSpace {initialize}
initialize super initialize. self color: 0.7@0.9@1.0@1.0. lightFrames := OrderedCollection new: 0. portalFrames := OrderedCollection new: 0. rayFrames := OrderedCollection new: 0. savedAlphaObjects := OrderedCollection new: 0. "alpha save stack" alphaObjects := OrderedCollection new: 0. cullBackFaces := true. fogOn := false. fogStart := 1.0. fogEnd := 100.0. fogDensity := 0.05. testRays := true. frameChanged := false. alphaObjects := OrderedCollection new: 0. tframes := Dictionary new. self register. defaultMaterial := TMaterial new. (self future:100)primitiveStep. defaultLaserColors := ReadStream on: (#( (0.95 0.1 0.1) (0.85 0.85 0.1) (0.1 0.9 0.2) (0.1 0.9 0.9) (0.2 0.1 1.0) (0.9 0.04 0.9) (0.6 0.25 0.05) (0.95 0.5 0.05) ) collect:[:each| each asVectorColor]) shuffled.

initializeWithMaster: atGridCoordinate:

GridParcelSpace {as yet unclassified}
initializeWithMaster: m atGridCoordinate: aPoint " Some day master might be a FarRef? " master := m. gridConfig := m gridConfig. gridCoordinate := aPoint. croquetRadius := gridConfig parcelRadius * gridConfig gridScale. "in croq coor system" "For things, Z is up. The following rotation maps things to Croquet's system, where Y is up." things := TGroup new. things localTransform: (things localTransform scalingX: gridConfig gridScale y: gridConfig gridScale z: gridConfig gridScale). things addRotationAroundX: 270. things translationX: croquetRadius negated y: 0 z: croquetRadius. self addChild: things. "==== The following is unused, now that we use 3D portals ===" "Postcards (really, empty TGroups) for Entrances from the four edge neighbors" "<<<<<<<<<< inWest := TGroup new. inNorth := TGroup new. inEast := TGroup new. inSouth := TGroup new. inEast addRotationAroundY: 90. inNorth addRotationAroundY: 180. inWest addRotationAroundY: 270. inEast translationX: croquetRadius y: 0 z: 0. inWest translationX: croquetRadius negated y: 0 z: 0. inNorth translationX: 0 y: 0 z: croquetRadius negated. inSouth translationX: 0 y: 0 z: croquetRadius. self addChild: inWest. self addChild: inNorth. self addChild: inEast. self addChild: inSouth. Transcript cr; print: (self asString, ' <===initWithMaster: ', m asString, ' atGP: ', Point asString ). >>>>>>>>>>"! !

insertFrame:

TFrame {hierarchy}
insertFrame: frm | parent | " Insert this frame between the target frame and its parent. " self parent ifNotNil:[ parent := self parent. parent removeChild: self. parent addChild: frm. ]. frm addChild: self.

inverseGlobalOrientation

TFrame {transform}
inverseGlobalOrientation ^ self globalOrientation orthoNormInverse.! !

inverseGlobalTransform

TFrame {transform}
inverseGlobalTransform ^ self globalTransform orthoNormInverse.! !

isAvatar

TFrame {testing}
isAvatar ^ false.! !

isBrowser

TFrame {testing}
isBrowser ^ false.! !

isCamera

TFrame {testing}
isCamera ^ false.! !

isChild:

TFrame {hierarchy}
isChild: parent ^ parent hasChild: self.

isDropTarget:

TFrame {private}
isDropTarget: aPayload "Will this TFrame handle 'acceptDrop: aPayload' ? This can be replaced in the fullness of time (once there is an Interface formalism and an Object #supports: Interface method that works quickly). For now, the method stands for 'self respondsTo:#acceptDrop:', and is needed because 'respondsTo:' is far too slow to use in interactive mouse loops." ^ false! !

isFrame

TFrame {testing}
isFrame ^ true.! !

isFrameChanged

TFrame {accessing}
isFrameChanged ^ frameChanged.! !

isGroup

TFrame {testing}
isGroup ^ false.! !

isLight

TFrame {testing}
isLight ^ false.! !

isMesh

TFrame {testing}
isMesh ^ false.! !

isOrContains:

TFrame {hierarchy}
isOrContains: aFrame "Is the given frame either myself or a descendant of myself?" ^ (aFrame == self) or: [ aFrame hasAncestor: self ].

isPortal

TFrame {testing}
isPortal ^ false.! !

isPostcard

TFrame {testing}
isPostcard ^ false.! !

isRay

TFrame {testing}
isRay ^ false.! !

isRigidBody

TFrame {testing}
isRigidBody ^ false.! !

isSolid

TFrame {testing}
isSolid ^ solid! !

isSpace

TFrame {testing}
isSpace ^ false.! !
TSpace {testing}
isSpace ^ true.! !

isTexture

TFrame {testing}
isTexture ^ false.! !

isWindow

TFrame {testing}
isWindow ^ false.! !

islandViolation:

TFrame {Islands}
islandViolation: txt "code flagged with this needs to be moved"! !

jump:

TFrame {toys}
jump: dist self translation: self translation + (Vector3 x: 0 y: dist z: 0).

justPastedOnto: byUser:

TFrame {*Wisconsin-SDK}
justPastedOnto: target byUser: userAvtrRep "Subclasses should extend this method." self frameChildrenDo: [:fc | fc justPastedOnto: target byUser: userAvtrRep]! !

keyDown:

TFrame {events}
keyDown: event

keyStroke:

TFrame {events}
keyStroke: event

keyUp:

TFrame {events}
keyUp: event

localCenter

TFrame {transform}
localCenter "Return a translation to the visual center of this object. By default, this is just the local translation. This is the basis of various Go-To operations, so objects whose visual center is different from the frame origin may override this." ^ self translation! !

localToGlobal:

TFrame {accessing}
localToGlobal: anObject ^self globalTransform localPointToGlobal: anObject! !

localTransform

TFrame {transform}
localTransform ^localTransform.! !

localTransform:

TFrame {transform}
localTransform: m4x4 localTransform := m4x4. self frameChanged. ^ localTransform.! !

locator

TFrame {accessing}
locator "Return a locator telling us where to find this guy on the net" ^nil! !

lookAt

TFrame {accessing}
lookAt "Return a normalized global-space vector pointing along the orientation of this frame." ^ self globalTransform column3 normalized.! !

lookAt: up:

TFrame {transform}
lookAt: frame up: u | at side m up | "vector between frames in global coordinates" at := frame globalPosition - self globalPosition. at length = 0.0 ifTrue:[^ 0]. "remove my transform from the point" at:=frameParent orientation orthoNormInverse localPointToGlobal: at. at normalize. up := u. up ifNil:[ at y abs = 1.0 ifFalse:[ up := Vector3 x: 0 y: 1 z: 0.] ifTrue:[ up := Vector3 x:0 y:0 z:-1].]. side := (at cross: up) normalized negated. up := (side cross: at) normalized negated. m := Matrix4x4 identity. m a11: side x. m a21: side y. m a31: side z. m a12: up x. m a22: up y. m a32: up z. m a13: at x. m a23: at y. m a33: at z. m translation: self translation. self localTransform: m.

lookSide

TFrame {accessing}
lookSide ^ self globalTransform column1.! !

lookUp

TFrame {accessing}
lookUp ^ self globalTransform column2.! !

make: x: y: z: radius: color:

GridParcelSpace {as yet unclassified}
make: aClass x: x y: y z: z radius: r color: colour | t | t := aClass new. t translationX: x y: y z: z. t colorize: colour. t class == TSphere ifTrue: [ t radius: r ] ifFalse: [ t extent: r@r@r ]. t radius: r. t objectName: aClass name, '_', x asString, '_', y asString. things addChild: t. ^ t.! !

makeStuff

GridParcelSpace {as yet unclassified}
makeStuff | a b wheel | a := gridCoordinate x. b := gridCoordinate y. " stacks of magenta balls along x=y axis, in parcel 0,0 " a+b==0 ifTrue: [ 0 to: 8 do: [ :i | | q | q := i * 12.5. 0 to: i do: [ :j | self make: TSphere x: q y: q z: j radius: 0.4 color: Color magenta. ]]]. wheel := Color wheel: gridConfig xSize. 5 to: 96 by: 5 do: [ :j | self make: TSphere x: 7+(a*10) y: j z: 1 radius: 0.9 color: (wheel at: a+1) ]. wheel := Color wheel: gridConfig ySize. 5 to: 96 by: 5 do: [ :j | self make: TSphere x: j y: 7+(b*10) z: 0.5 radius: 0.3 color: (wheel at: b+1) ]. self make: TSphere x: (a\\4*25+12.5) y: (a+b\\4*25+12.5) z: (a+b) radius: 5 color: Color cyan.

master

GridParcelSpace {as yet unclassified}
master ^ master! !

material

TFrame {accessing}
material frameChildren isEmptyOrNil ifTrue:[^nil]. ^frameChildren anyOne material! !

material:

TFrame {accessing}
material: mat frameChildren ifNil:[^self]. frameChildren do:[:each| each material: mat].! !

materialAlpha:

TFrame {accessing}
materialAlpha: ignored "backstop"! !

moveBy: duration: style: rate:

TFrame {yellow-scripts}
moveBy: aDirection duration: aDuration style: aStyle rate: aSamplingRate | direction duration style rate endState styleFunc lastState startState deltaTime msecsDuration proportion newState startT progressT script | direction := aDirection ifNil:[self defaultDirection asMoveDirection * self defaultDistance]. duration := aDuration ifNil:[self defaultDuration]. style := aStyle ifNil:[self defaultInterpolationStyle]. rate := aSamplingRate ifNil:[self defaultSamplingRate]. "Get the ultimate state we're interested in" endState := direction. duration <= 0 ifTrue:[^self transformBy: (Matrix4x4 withOffset: endState)]. "Compute msecs since that's what we'll be working on here" msecsDuration := duration * 1000. "Get the interpolation function (evaluating from 0-1 and returning values from 0-1)" styleFunc := style asScriptStyle. "Reset the interpolation state" lastState := startState := 0@0@0. "And go moving until we're out of time" rate := msecsDuration * rate // 1000. deltaTime := msecsDuration // rate. startT := self now. script := Processor activeProcess. 1 to: rate do:[:i| progressT := (i*deltaTime) asFloat. (startT + progressT) waitUntil. "<-- here is where tea scheduling kicks in" "Compute the proportion of time that's over" proportion := progressT / msecsDuration asFloat. "Map it through the interpolation style" proportion := styleFunc value: proportion. "Compute the state (e.g., offset) at our new proportion" newState := startState interpolateTo: endState at: proportion. "Transform incrementally - this is so that we can superimpose animations." self transformBy: (Matrix4x4 withOffset: newState - lastState). "Remember last state for the next round" lastState := newState. "see if a stop was requested" script isStopRequested ifTrue:[^self]. ]. (startT + msecsDuration) waitUntil. "<-- here is where tea scheduling kicks in" "Apply the remaining part of the transform (if any)" self transformBy: (Matrix4x4 withOffset: endState - lastState).

moveTo: duration: style: rate:

TFrame {yellow-scripts}
moveTo: aTarget duration: aDuration style: aStyle rate: aSamplingRate | target targetDir length | target := aTarget ifNil:[^self]. targetDir := self globalToLocal: target globalPosition. targetDir y: 0.0. length := targetDir length. targetDir := targetDir / length. ^self move: targetDir distance: length duration: aDuration style: aStyle rate: aSamplingRate! !

myBehaviors

TFrame {yellow-scripts-support}
myBehaviors ^(myProperties ifNotNil:[myProperties behaviors]) ifNil:[#()]! !

myBehaviors:

TFrame {yellow-scripts-support}
myBehaviors: aCollection self extraProperties behaviors: aCollection.

myEventMap

TObject {private}
myEventMap ^myProperties ifNotNil:[myProperties eventMap]! !

myEventMap:

TObject {private}
myEventMap: aMap self extraProperties eventMap: aMap.! !

myPlayer

TFrame {scripts}
myPlayer ^myProperties ifNotNil:[myProperties myPlayer]! !

myPlayer:

TFrame {scripts}
myPlayer: aPlayer self extraProperties player: aPlayer! !

myScripts

TObject {private}
myScripts ^(myProperties ifNotNil:[myProperties scripts]) ifNil:[#()]! !

myScripts:

TObject {private}
myScripts: scripts self extraProperties scripts: scripts.! !

new

TFrame class {instance creation}
new protoData ifNil:[^self basicNew initialize]. ^TIslandCopyImporter new importData: protoData.! !

newExtraProperties

TFrame {initialize}
newExtraProperties ^TFrameProperties new! !
TObject {private}
newExtraProperties "Create new extra properties for this object" ^TObjectProperties new.! ! 'From Croquet1.0beta of 11 April 2006 [latest update: #0] on 24 March 2007 at 5:54:01 pm'!

newOn:

TFrame class {*Wisconsin-SDK}
newOn: island "Copying between islands is much faster than instance creation. If your class can't get away with this, then redefine this method to just: '^island future new: self'. " | bits | bits := KSDKHarness frameCache at: self ifAbsentPut: [TIslandCopier new export: self basicNew initialize]. "TIslandCopier isn't designed to import data into the same island. Should it be?" self flag: #jcg. island == self island ifFalse: [^ TIslandCopier new import: bits to: island] ifTrue: [^ TIslandCopyImporter new importData: bits].

newOn: from:

TFrame class {*Wisconsin-SDK}
newOn: island from: input | container | container := self newOn: island. ^self connectContentsFrom: input intoContainer: container.! ! TFrame initialize! 'From Croquet1.0beta of 11 April 2006 [latest update: #0] on 24 March 2007 at 5:54:12 pm'!

newRoot: newTransform:

TFrame {transform}
newRoot: newRoot newTransform: newTransform | oldRoot | oldRoot := self root. self signal: #spaceLeave with: oldRoot. oldRoot signal: #objectLeave with: self. self parent removeChild: self. newRoot addChild: self. self localTransform: newTransform. self signal: #spaceEnter with: newRoot. newRoot signal: #objectEnter with: self.! !

nextLaserColor

TSpace {accessing}
nextLaserColor "Answer the next default laser color" defaultLaserColors atEnd ifTrue:[defaultLaserColors position: 0]. ^defaultLaserColors next! !

now

TFrame {events}
now ^Processor activeIsland time! !

objectID

TFrame {Islands}
objectID ^ objectID. ! !

objectName

TFrame {accessing}
objectName ^objectName ifNil:[self class defaultObjectName]! !

objectName:

TFrame {accessing}
objectName: oName self signal: #nameChanged. objectName := oName.

objectOwner

TFrame {ownership}
objectOwner "objectOwner should never be nil" ^ objectOwner.! !

octreeBox

TFrame {accessing}
octreeBox | box childBox bs | box := TBox new. frameChildren ifNotNil:[ frameChildren do:[ :fc | childBox := fc octreeBox. childBox ifNotNil:[ box := box unionBox: childBox.]. ]. ]. bs := self boundSphere. bs ifNotNil:[ bs transform: self globalTransform. box growVertex: bs globalPosition. ]. box min x > box max x ifTrue:[^ nil ]. ^ box.! !

octreeRadius

TFrame {accessing}
octreeRadius | rad childRad | " Find the max bound sphere radius of the tree. This is used for quadtree/octree construction " self boundSphere ifNotNil:[ rad := self boundSphere radius.] ifNil:[ rad := 0 ]. frameChildren ifNotNil:[ frameChildren do:[ :fc | childRad := fc octreeRadius. rad := rad max: childRad. ]. ]. ^ rad.! !

octreeSieve:

TFrame {accessing}
octreeSieve: octree | bs | bs := self boundSphere. bs ifNotNil:[ bs transform: self globalTransform. octree add: bs. ]. frameChildren ifNotNil:[ frameChildren do:[ :fc | fc octreeSieve: octree. ]. ].

oglid

TFrame {accessing}
oglid ^ oglid.! !

on: notify:

TFrame {events}
on: eventName notify: aClient "Overridden to update the eventMask as needed" | maskBit | maskBit := EventMaskBits at: eventName ifAbsent:[0]. maskBit = 0 ifFalse:[self eventMask: (eventMask bitOr: maskBit)]. ^super on: eventName notify: aClient! !

on: unNotify:

TFrame {events}
on: eventName unNotify: aClient "Overridden to update the eventMask as needed" | maskBit newMask | super on: eventName unNotify: aClient. maskBit := EventMaskBits at: eventName ifAbsent:[0]. maskBit = 0 ifFalse:["Reconstruct eventMask" newMask := 0. self myEventMap ifNotNilDo:[:map| map keysDo:[:evtName| newMask := newMask bitOr: (EventMaskBits at: evtName ifAbsent:[0])]]. self eventMask: newMask. ].! !

orientation

TFrame {transform}
orientation "This is used to return just the orientation part of the matrix.The translation part is 0.0." | mat | mat := localTransform clone. mat translationX: 0.0 y: 0.0 z: 0.0. ^ mat.! !

orientation:

TFrame {transform}
orientation: mat "This is used to set just the orientation part of the matrix. It keeps the translation parts intact." | trans | trans := self translation. localTransform := mat clone. self translation: trans. self frameChanged. ^ localTransform.! !

outVector

TFrame {transform}
outVector ^ self globalTransform column3. ! !

parcelRadius

GridParcelSpace {as yet unclassified}
parcelRadius ^ gridConfig parcelRadius! !

parent

TFrame {hierarchy}
parent ^frameParent.! !

parent:

TFrame {hierarchy}
parent: fp frameParent := fp.! !

parentChanged

TFrame {accessing}
parentChanged self parentChanged: self.

parentChanged:

TFrame {accessing}
parentChanged: frame " Does nothing, just forward on to children." frameChildren ifNotNil:[frameChildren do:[:fc | fc parentChanged: frame].].! !

pasteMaterial:

TFrame {*Wisconsin-SDK}
pasteMaterial: aMaterialOrTexture aMaterialOrTexture asMaterialFor: self.! !

pasteOnto: byUser:

TFrame {*Wisconsin-SDK}
pasteOnto: target byUser: userAvtrRep target addChild: self byUser: userAvtrRep. self justPastedOnto: target byUser: userAvtrRep. "Subclasses may extend this method."! !

pauseAmbientSound

TSpace {ambient sound}
pauseAmbientSound "this is really a fade and pause" ambientSound ifNil:[^self]. self ambientSoundFadeFrom: ambientSound volume to: 0.0 duration: 1000.0. (self future: 1000.0) ambientSoundPauseComplete.! !

pick:

TFrame {render}
pick: pointer ^ false! !

pickFloor:

TFrame {render}
pickFloor: pointer ^ self pick: pointer.! !

pickSelf:

TFrame {render}
pickSelf: ogl "This is used when we already (think we) know that we are just re-selecting an already selected object. This is used by TPointer>>#pointerPickCurrent" | frame | frame := self getOwnedObject: ogl eventPointer selection frameID. frame ifNotNil: [ (ogl eventPointer pointerPick: frame boundSphere) ifFalse: [ ogl eventPointer selectedGlobalPoint: (self globalTransform localPointToGlobal: ogl eventPointer selectedPoint). ]. ].! !

pitch

TFrame {transform}
pitch ^self pitchYawRoll x! !

pitch:

TFrame {transform}
pitch: p | angles | angles := self pitchYawRoll. angles x: p. self pitchYawRoll: angles.! !

pitchYawRoll

TFrame {transform}
pitchYawRoll ^localTransform pitchYawRoll! !

pitchYawRoll:

TFrame {transform}
pitchYawRoll: aVector | tfm | tfm := localTransform copy pitchYawRoll: aVector. self localTransform: tfm.! !

pitchYawRollBy:

TFrame {transform}
pitchYawRollBy: delta self pitchYawRoll: self pitchYawRoll + delta! !

playAmbientSound:

TSpace {ambient sound}
playAmbientSound: aBool aBool ifTrue:[self startAmbientSound] ifFalse:[self stopAmbientSound].

player

TFrame {scripts}
player ^self myPlayer! !

pointerDown:

TFrame {events}
pointerDown: event

pointerEnter:

TFrame {events}
pointerEnter: event

pointerLeave:

TFrame {events}
pointerLeave: event

pointerMove:

TFrame {events}
pointerMove: event

pointerOver:

TFrame {events}
pointerOver: event

pointerUp:

TFrame {events}
pointerUp: event

popAlphaObjects

TSpace {render}
popAlphaObjects "restore alpha objects saved while recursively rendering (in TPortal3D)" alphaObjects := savedAlphaObjects removeLast. ! !

postCopy

TFrame {copying}
postCopy super postCopy. localTransform := localTransform copy. " Only make copies ofthe frame heirarchy. Everything else stays as-is." frameChildren ifNotNil:[ frameChildren := frameChildren collect:[:fc| fc isTexture ifTrue:[fc] ifFalse: [fc copy] ]. ]. ^self! !

postImportFromIslandCopier:

TFrame {fileIn/Out}
postImportFromIslandCopier: importer | frame | super postImportFromIslandCopier: importer. "Create new object id after copying" objectID ifNil:[objectID := TObjectID for: self]. self register. "Restore object ownership" ownedObjects ifNotNil:[ ownedObjects keys do:[:id| frame := ownedObjects removeKey: id. ownedObjects at: frame objectID put: frame. ]. ].! !

postcard

TFrame {accessing}
postcard self register. ^ TPostcard new routerAddress: nil id: Processor activeIsland id name: Processor activeIsland name viewpointID: objectID.

prepareToExportOnIslandCopier:

TFrame {fileIn/Out}
prepareToExportOnIslandCopier: exporter super prepareToExportOnIslandCopier: exporter. objectID := nil. globalTransform := nil.! !

primitiveStep

TSpace {step}
primitiveStep | bs | testRays ifTrue:[ self doForPick:[:frame | bs := frame boundSphere. frame isFrameChanged ifTrue:[ bs ifNotNil:[ bs transform: frame globalTransform. ]. ]. rayFrames do:[ :rf | rf automatic ifTrue:[rf pick: bs.].]. ]. ]. (self future:100)primitiveStep.! !

printOn:

TFrame {accessing}
printOn: aStream "show the default - usually 'a ClassName'" super printOn: aStream. "show the size of the frameChildren array" frameChildren ifNotNil:[ aStream nextPutAll:'['; print:frameChildren size; nextPutAll:']'. ]. "show the name of this object" objectName ifNotNil:[ aStream nextPutAll:':'; print: objectName.].! !

prototype:

TFrame class {instance creation}
prototype: aTFrame aTFrame ifNil:[^protoData := nil]. protoData := TIslandCopier new export: aTFrame.

prune

TFrame {hierarchy}
prune " frameChildren ifNotNil:[ frameChildren do:[ :fc | fc prune ifTrue:[ self removeChild: fc.].]. frameChildren size = 0 ifTrue:[frameChildren := nil]. ]. (self class = TFrame and:[ frameChildren = nil ])ifTrue:[^true]. ^ false."! !

pushAlphaObjects

TSpace {render}
pushAlphaObjects "temporarily save alpha objects while recursively rendering (in TPortal3D)" savedAlphaObjects add: alphaObjects. alphaObjects := OrderedCollection new: 0. ! !

quaternion

TFrame {transform}
quaternion ^ localTransform asQuaternion.! !

rayFrames

TSpace {accessing}
rayFrames ^ rayFrames.! !

reallyDestroy

TFrame {*Wisconsin-SDK}
reallyDestroy "Destroying children will alter frameChildren. Must copy." frameChildren ifNotNil: [frameChildren copy do: [:child | child reallyDestroy]]. self destroy. self island unregister: self. "useful for tracking memory leaks." objectID := nil.

rearrange:

TFrame {transform}
rearrange: ogl "Used by the TSystemSpace overlay world to reposition its children upon a resize event. Many TFrame objects can simply ignore this"! !
TSpace {render}
rearrange: ogl " this allows a space to rearrange itself. Called when a portal bounds is resized."! !

register

TFrame {Islands}
register "Register me in the island's nameMap under my objectID." ^ Processor activeIsland register:self name: objectID. ! !

registerChildren

TFrame {Islands}
registerChildren "Register my children and give them a unique object name" | names newName pair | frameChildren ifNil:[^nil]. names := Set new: frameChildren size. frameChildren do:[:each| newName := each objectName. (names includes: newName) ifTrue:[ [pair := newName stemAndNumericSuffix. newName := pair first, (pair last+1 max: 2) printString. names includes: newName] whileTrue. each objectName: newName. ]. names add: newName. each register ].! !

registerGlobal:

TFrame {Islands}
registerGlobal: name | nm | " nm := Processor activeIsland globalNameAt:self ifAbsent:[nil]. nm ifNotNil:[Processor activeIsland removeGlobal: nm]. " ^ Processor activeIsland at:name put: self. ! !

registerName:

TFrame {Islands}
registerName: name ^ Processor activeIsland register:self name: name. ! !

relativeTransform:

TFrame {transform}
relativeTransform: frame ^ self globalTransform orthoNormInverse * frame globalTransform.! !

releaseFrame:

TFrame {*Wisconsin-SDK}
releaseFrame: event "see #releaseWindow:" self releasedBy: event avatar.

releaseToRoot

TFrame {transform}
releaseToRoot "Transfer the frame from the current parent to the root frame while keeping the pose in exactly the same orientation" | trans root | trans := self globalTransform. root := self root. self transferTo: root. self localTransform: trans.

releasedBy:

TFrame {*Wisconsin-SDK}
releasedBy: avatar avatar ifNil:[^nil]. "We could use the avatar argument to see if that's the avatar currently holding us, but we don't." self parent parent carryingRelease: self.

removeAll

TFrame {hierarchy}
removeAll | child | frameChildren ifNil:[^nil.]. [frameChildren size = 0] whileFalse:[ child := frameChildren at: 1. frameChildren removeAt: 1. child removeLightFrames. child removePortalFrames. ]. frameChildren := nil.

removeChild:

TFrame {hierarchy}
removeChild: child self root ifNotNil:[ self root doStop:child]. objectOwner removeOwnership: child. child removeLightFrames. child removePortalFrames. child removeRayFrames. child root: nil. frameChildren ifNotNil:[frameChildren remove: child ifAbsent:[].]. child parent: nil. self signal: #structureChanged.! !

removeFrame:

TSpace {accessing}
removeFrame: frame tframes removeKey: frame objectID.! !

removeLightFrame:

TFrame {frameManagement}
removeLightFrame: litefrm frameParent ifNotNil:[frameParent removeLightFrame: litefrm.]! !
TSpace {frameManagement}
removeLightFrame: ltfrm lightFrames remove: ltfrm ifAbsent:[]. " lightFrames doWithIndex:[ :lf :i| lf = ltfrm ifTrue: [lightFrames remove: i]]."! !

removeLightFrames

TFrame {frameManagement}
removeLightFrames " When a frame is disconnected from its parent, we need to remove the references to the lights in the TRoom." self isLight ifTrue:[self removeLightFrame: self.]. frameChildren ifNotNil:[frameChildren do:[ :fc | fc removeLightFrames ].]. ! !

removeOwnership:

TFrame {ownership}
removeOwnership: frame frame = self ifTrue:[ ^self ]. "we did not add ourselves to the dictionary" frame objectOwner ~= self ifTrue:[ ^self ]. "this frame is not in this dictionary " ownedObjects ifNotNil:[ownedObjects removeKey:frame objectID]. frame forceObjectOwner: frame. "set the objectOwner back to self" frame frameChildrenDo:[:child | self removeOwnership: child.].

removePortalFrame:

TFrame {frameManagement}
removePortalFrame: prtlFrm frameParent ifNotNil:[frameParent removePortalFrame: prtlFrm.]! !
TSpace {frameManagement}
removePortalFrame: prtlFrm portalFrames remove: prtlFrm. "portalFrames doWithIndex:[ :pf :i| pf = prtlFrm ifTrue: [portalFrames remove: i]]."! !

removePortalFrames

TFrame {frameManagement}
removePortalFrames " When a frame is disconnected from its parent, we need to remove the references to the lights in the TRoom." self isPortal ifTrue:[self removePortalFrame: self.]. frameChildren ifNotNil:[frameChildren do:[ :fc | fc removePortalFrames ].]. ! !

removeRayFrame:

TFrame {frameManagement}
removeRayFrame: rayfrm frameParent ifNotNil:[frameParent removeRayFrame: rayfrm.]! !
TSpace {frameManagement}
removeRayFrame: rayfrm rayFrames remove: rayfrm ifAbsent:[].

removeRayFrames

TFrame {frameManagement}
removeRayFrames " When a frame is disconnected from its parent, we need to remove the references to the rays in the TSpace." self isRay ifTrue:[self removeRayFrame: self.]. frameChildren ifNotNil:[frameChildren do:[ :fc | fc removeRayFrames ].]. ! !

removeSelf

TFrame {hierarchy}
removeSelf self parent ifNotNil:[ self parent removeChild: self.].

render:

TFrame {render}
render: ogl self renderAxes: ogl.! !
TSpace {render}
render: ogl " don't render me "! !

render: box:

TFrame {render}
render: ogl box: box | | self render: ogl cube: box location: box center scale: 1.0.! !

render: cube: location: scale:

TFrame {render}
render: ogl cube: cube location: loc scale: scale | dx dy dz x y z e | " This message is used only to make sure a frame is actually drawing something. In this case, I draw a cube. " e := cube extent. dx := e x*scale/2.0. dy := e y*scale/2.0. dz := e z*scale/2.0. x := loc x. y := loc y. z := loc z. ogl glBegin: GLQuads; glNormal3f: 0.0 with: 0.0 with: 1.0; glTexCoord2f:0.0 with:1.0; glVertex3f: x+(dx negated) with: y+(dy negated) with: z+dz; glTexCoord2f:1.0 with:1.0; glVertex3f: x+dx with: y+(dy negated) with: z+dz; glTexCoord2f:1.0 with:0.0; glVertex3f: x+dx with: y+dy with: z+dz; glTexCoord2f:0.0 with: 0.0; glVertex3f: x+(dx negated) with: y+dy with: z+dz. dz := dz negated. ogl glNormal3f: 0.0 with: 0.0 with: -1.0; glTexCoord2f:1.0 with: 0.0; glVertex3f: x+(dx negated) with: y+dy with: z+dz; glTexCoord2f:0.0 with:0.0; glVertex3f: x+dx with: y+dy with: z+dz; glTexCoord2f:0.0 with:1.0; glVertex3f: x+dx with: y+(dy negated) with: z+dz; glTexCoord2f:1.0 with:1.0; glVertex3f: x+(dx negated) with: y+(dy negated) with: z+dz. dz := dz negated. ogl glNormal3f: 1.0 with: 0.0 with: 0.0; glTexCoord2f:0.0 with:1.0; glVertex3f: x+dx with: y+(dy negated) with: z+dz; glTexCoord2f:1.0 with:1.0; glVertex3f: x+dx with: y+(dy negated) with: z+(dz negated); glTexCoord2f:1.0 with: 0.0; glVertex3f: x+dx with: y+dy with: z+(dz negated); glTexCoord2f:0.0 with: 0.0; glVertex3f: x+dx with: y+dy with: z+dz. dx := dx negated. ogl glNormal3f: -1.0 with: 0.0 with: 0.0; glTexCoord2f:1.0 with: 0.0; glVertex3f: x+dx with: y+dy with: z+dz; glTexCoord2f:0.0 with:0.0; glVertex3f: x+dx with: y+dy with: z+(dz negated); glTexCoord2f:0.0 with:1.0; glVertex3f: x+dx with: y+(dy negated) with: z+(dz negated); glTexCoord2f:1.0 with:1.0; glVertex3f: x+dx with: y+(dy negated) with: z+dz. dx := dx negated. ogl glNormal3f: 0.0 with: 1.0 with: 0.0; glTexCoord2f:1.0 with: 0.0; glVertex3f: x+dx with: y+dy with: z+dz; glTexCoord2f:0.0 with:0.0; glVertex3f: x+dx with: y+dy with: z+(dz negated); glTexCoord2f:0.0 with:1.0; glVertex3f: x+(dx negated) with: y+dy with: z+(dz negated); glTexCoord2f:1.0 with:1.0; glVertex3f: x+(dx negated) with: y+dy with: z+dz. dy := dy negated. ogl glNormal3f: 0.0 with: -1.0 with: 0.0; glTexCoord2f:0.0 with:1.0; glVertex3f: x+(dx negated) with: y+dy with: z+dz; glTexCoord2f:1.0 with:1.0; glVertex3f: x+(dx negated) with: y+dy with: z+(dz negated); glTexCoord2f:1.0 with:0.0; glVertex3f: x+dx with: y+dy with: z+(dz negated); glTexCoord2f:0.0 with: 0.0; glVertex3f: x+dx with: y+dy with: z+dz. ogl glEnd.

render: cube: scale:

TFrame {render}
render: ogl cube: box scale: scale self renderCube: ogl location: 0.0@0.0@0.0 scale: scale.

render: sphere: segments:

TFrame {render}
render: ogl sphere: bndSphr segments: segments | position radius ringSin ringCos pi2 seg2 vert rts rbs rtc rbc ax u du v dv | position := bndSphr localPosition. radius := bndSphr radius. seg2 := 1+ (segments * 2) . ringSin := FloatArray ofSize: seg2. ringCos := FloatArray ofSize: seg2. vert := Vector3 new. pi2 := Float pi *2.0. 1 to: seg2-1 do:[ :index | ax := ((index) * pi2)/ (seg2-1). ringSin at:index put: ax sin. ringCos at:index put: ax cos.]. ringSin at: seg2 put: (ringSin at: 1). ringCos at: seg2 put: (ringCos at: 1). rts := 0.0. rtc := 1.0. rbs :=ringSin at: 1. rbc := ringCos at: 1. du := 1.0/(seg2-1). v := 0.0. dv := 1.0/segments. 1 to: segments do:[ :iv | ogl glBegin: GLTriangleStrip. u := 0.0. 1 to: seg2 do: [ :ih | vert x: rts*(ringSin at: ih) y: rtc z: rts*(ringCos at: ih). ogl glNormal3fv: vert; glTexCoord2f: u with: v; glVertex3fv: (vert * radius)+ position. vert x: rbs*(ringSin at: ih) y: rbc z: rbs*(ringCos at: ih). ogl glNormal3fv: vert; glTexCoord2f: u with: v+dv; glVertex3fv: (vert * radius)+ position. u:= u+du.]. v := v+dv. rts := rbs. rtc := rbc. rbs := ringSin at: iv+1. rbc := ringCos at: iv+1. ogl glEnd.].

renderAlpha:

TFrame {render}
renderAlpha: ogl "This is used to render transparent ( alpha blended ) objects."! !
TSpace {render}
renderAlpha: ogl " don't render me "! !

renderAxes:

TFrame {render}
renderAxes: ogl ogl glDisable: GLLighting; " This is used to render solid objects (if any). " glColor3fv: #(1.0 0 0)asFloatArray; glBegin: GLLineStrip; glVertex3fv:#(0.0 0.0 0.0)asFloatArray; glVertex3fv:#(1.0 0.0 0.0)asFloatArray; glVertex3fv:#(0.75 0.25 0.0)asFloatArray; glVertex3fv:#(0.75 -0.25 0.0)asFloatArray; glVertex3fv:#(1.0 0.0 0.0)asFloatArray; glVertex3fv:#(0.75 0.0 0.25)asFloatArray; glVertex3fv:#(0.75 0.0 -0.25)asFloatArray; glVertex3fv:#(1.0 0.0 0.0)asFloatArray; glEnd; glColor3fv: #(0.0 1.0 0)asFloatArray; glBegin: GLLineStrip; glVertex3fv:#(0.0 0.0 0.0)asFloatArray; glVertex3fv:#(0.0 1.0 0.0)asFloatArray; glVertex3fv:#(0.0 0.75 0.25)asFloatArray; glVertex3fv:#(0.0 0.75 -0.25)asFloatArray; glVertex3fv:#(0.0 1.0 0.0)asFloatArray; glVertex3fv:#(0.25 0.75 0.0)asFloatArray; glVertex3fv:#(-0.25 0.75 0.0)asFloatArray; glVertex3fv:#(0.0 1.0 0.0)asFloatArray; glEnd; glColor3fv: #(0.0 0.0 1.0)asFloatArray; glBegin: GLLineStrip; glVertex3fv:#(0.0 0.0 0.0)asFloatArray; glVertex3fv:#(0.0 0.0 1.0)asFloatArray; glVertex3fv:#(0.25 0.0 0.75)asFloatArray; glVertex3fv:#(-0.25 0.0 0.75)asFloatArray; glVertex3fv:#(0.0 0.0 1.0)asFloatArray; glVertex3fv:#(0.0 0.25 0.75)asFloatArray; glVertex3fv:#(0.0 -0.25 0.75)asFloatArray; glVertex3fv:#(0.0 0.0 1.0)asFloatArray; glEnd; glEnable: GLLighting.! !

renderClear:

TSpace {render}
renderClear: ogl ogl glClearColor: (color at: 1) with: (color at: 2) with: (color at: 3) with: (color at: 4). ogl glClear: (GLColorBufferBit bitOr: (GLDepthBufferBit bitOr: GLStencilBufferBit)).

renderClearAll:

TSpace {render}
renderClearAll: ogl ogl glClearColor: (color at: 1) with: (color at: 2) with: (color at: 3) with: (color at: 4). ogl glClear: (GLColorBufferBit bitOr: (GLDepthBufferBit bitOr: GLStencilBufferBit)).

renderClearBounds:

TSpace {render}
renderClearBounds: ogl "This method is used when we have a smaller overlay portal/space in on top of a full portal/space rendering. This is used for picture-in-picture displays - that is, showing a full environment on top of another one" | ac h v | ac := ogl camera. " add the background poly, as we can't clear " h := ac bounds width/2.0. v := ac bounds height/2.0. ogl glDepthMask: GLFalse; " set depth buffer to not write. " glDisable: GLLighting; glColor3f: (color at: 1) with: (color at: 2) with: (color at: 3); glBegin: GLPolygon; glVertex3f: h negated with: v with: ac zScreen negated; glVertex3f: h with: v with: ac zScreen negated; glVertex3f: h with:v negated with: ac zScreen negated; glVertex3f: h negated with: v negated with: ac zScreen negated; glEnd; glDepthMask: GLTrue; glEnable: GLLighting.

renderCube: location: scale:

TFrame {render}
renderCube: ogl location: loc scale: scale | dx dy dz x y z | " This message is used only to make sure a frame is actually drawing something. In this case, I draw a cube. " dx := scale/2.0. dy := scale/2.0. dz := scale/2.0. x := loc x. y := loc y. z := loc z. ogl glBegin: GLQuads; glNormal3f: 0.0 with: 0.0 with: 1.0; glTexCoord2f:0.0 with:1.0; glVertex3f: x+(dx negated) with: y+(dy negated) with: z+dz; glTexCoord2f:1.0 with:1.0; glVertex3f: x+dx with: y+(dy negated) with: z+dz; glTexCoord2f:1.0 with:0.0; glVertex3f: x+dx with: y+dy with: z+dz; glTexCoord2f:0.0 with: 0.0; glVertex3f: x+(dx negated) with: y+dy with: z+dz. dz := dz negated. ogl glNormal3f: 0.0 with: 0.0 with: -1.0; glTexCoord2f:1.0 with: 0.0; glVertex3f: x+(dx negated) with: y+dy with: z+dz; glTexCoord2f:0.0 with:0.0; glVertex3f: x+dx with: y+dy with: z+dz; glTexCoord2f:0.0 with:1.0; glVertex3f: x+dx with: y+(dy negated) with: z+dz; glTexCoord2f:1.0 with:1.0; glVertex3f: x+(dx negated) with: y+(dy negated) with: z+dz. dz := dz negated. ogl glNormal3f: 1.0 with: 0.0 with: 0.0; glTexCoord2f:0.0 with:1.0; glVertex3f: x+dx with: y+(dy negated) with: z+dz; glTexCoord2f:1.0 with:1.0; glVertex3f: x+dx with: y+(dy negated) with: z+(dz negated); glTexCoord2f:1.0 with: 0.0; glVertex3f: x+dx with: y+dy with: z+(dz negated); glTexCoord2f:0.0 with: 0.0; glVertex3f: x+dx with: y+dy with: z+dz. dx := dx negated. ogl glNormal3f: -1.0 with: 0.0 with: 0.0; glTexCoord2f:1.0 with: 0.0; glVertex3f: x+dx with: y+dy with: z+dz; glTexCoord2f:0.0 with:0.0; glVertex3f: x+dx with: y+dy with: z+(dz negated); glTexCoord2f:0.0 with:1.0; glVertex3f: x+dx with: y+(dy negated) with: z+(dz negated); glTexCoord2f:1.0 with:1.0; glVertex3f: x+dx with: y+(dy negated) with: z+dz. dx := dx negated. ogl glNormal3f: 0.0 with: 1.0 with: 0.0; glTexCoord2f:1.0 with: 0.0; glVertex3f: x+dx with: y+dy with: z+dz; glTexCoord2f:0.0 with:0.0; glVertex3f: x+dx with: y+dy with: z+(dz negated); glTexCoord2f:0.0 with:1.0; glVertex3f: x+(dx negated) with: y+dy with: z+(dz negated); glTexCoord2f:1.0 with:1.0; glVertex3f: x+(dx negated) with: y+dy with: z+dz. dy := dy negated. ogl glNormal3f: 0.0 with: -1.0 with: 0.0; glTexCoord2f:0.0 with:1.0; glVertex3f: x+(dx negated) with: y+dy with: z+dz; glTexCoord2f:1.0 with:1.0; glVertex3f: x+(dx negated) with: y+dy with: z+(dz negated); glTexCoord2f:1.0 with:0.0; glVertex3f: x+dx with: y+dy with: z+(dz negated); glTexCoord2f:0.0 with: 0.0; glVertex3f: x+dx with: y+dy with: z+dz. ogl glEnd.

renderCube: scale:

TFrame {render}
renderCube: ogl scale: scale self renderCube: ogl location: 0.0@0.0@0.0 scale: scale.

renderFrame:

TFrame {render}
renderFrame: ogl " #renderFrame: must return the number of objects that were rendered - failure to do so will just crash." | count childCount ac distanceSquared hilite | count := 0. (visible or:[frameChildren notNil])ifFalse:[^ 0 ]. ac := ogl camera. " apply the local transform to this matrix " frameChanged ifTrue:[ self islandViolation:'this code must be moved somewhere else'. self globalTransform: (frameParent globalTransform * localTransform). ]. ogl pushMatrix. ogl glMultTransposeMatrixf: localTransform. hilite := false. self currentHiliteColor ifNotNil: [ hilite := ogl forceHilite: self currentHiliteColor. hilite ifTrue: [ ogl pushFog ]. ]. "------ is this inside the viewing pyramid?" (visible and:[ac testBounds: self boundSphere]) ifTrue:[ ogl eventPointer ifNotNil:[ (ogl forcePick or:[self objectOwner eventMask~=EventNone]) ifTrue:[ self isPortal ifFalse:[ (ogl eventPointer pointerPick: self boundSphere) ifTrue:[ ogl eventPointer selectedCameraTransform: ac globalTransform copy. ac currentPortal ifNil:[ ogl eventPointer selectedPortal:nil point:nil]. ]. ]. ]. ]. count := 1. distanceSquared :=((ac globalPosition-self globalPosition)squaredLength*ac frameScaleSquared). ogl distance: distanceSquared. (self hasOpaque:ogl)ifTrue:[ self render: ogl. ]. (self hasAlpha:ogl) ifTrue: [ self root addAlphaObject: self transform: ogl peekMatrix distance: distanceSquared parent: frameParent transparency: ogl transparency. ]. ]. frameChildren ifNotNil:[ " render all of the child frames " childCount := 0. frameChildren do:[:rFrame | childCount := childCount+(rFrame renderFrame: ogl).]. childCount > 0 ifTrue:[count := count+childCount. ] ]. hilite ifTrue: [ ogl forceHilite: nil. ogl popFog. ]. ogl popMatrix. ^ count.

renderOverlay: overlay:

TFrame {render}
renderOverlay: ogl overlay: ov | gTrans rval | ogl camera globalTransform: self globalMatrixOut. ogl eventPointer ifNotNil:[ gTrans := ogl eventPointer globalTransform. ogl eventPointer globalTransform: self globalMatrixOut * ogl eventPointer localTransform. rval := ogl camera renderOverlay: ogl space: self root overlay: ov. ogl eventPointer globalTransform: gTrans. ] ifNil: [ rval := ogl camera renderOverlay: ogl space: self root overlay: ov.]. ^ rval.! !

renderSpace:

GridParcelSpace {as yet unclassified}
renderSpace: ogl | rval gtrans xform | gtrans := self globalTransform. rval := super renderSpace: ogl. false ifTrue: [ [ "self neighboringSpaces" #( ) do: [ :neighbor | | shift | shift := self parcelRadius * (neighbor gridCoordinate - self gridCoordinate). self globalTransform: ((gtrans + Matrix4x4 identity) translationX: shift x y: 0 z: shift y). "<< one way >> rval := rval + (neighbor renderSpace: ogl port: nil depth: 1 ghostFrame: nil). " "<< another way >> rval := rval + (neighbor renderSubspace: ogl). " "<< another way >> ogl pushMatrix. xform := Matrix4x4 identity translationX: shift x y: 1 z: shift y. ogl glMultTransposeMatrixf: xform. ogl popMatrix. " ]. ] ensure: [ self globalTransform: gtrans ]. ]. ^ rval! !
TSpace {render}
renderSpace: ogl "----- test if enter the portal here -----" ogl avatar ifNotNil:[ ogl avatar prepareRayTest ifTrue:[ portalFrames do: [ :pf | "------ is the portal visible? ------" pf visible ifTrue:[ " ------ portal near avatar?-----" (pf testEnter:ogl avatar:ogl avatar) ifTrue:[ ogl noSwap. ^ 0.]. ].].].]. ^self renderSpace: ogl port: nil depth: 1 ghostFrame: nil.

renderSpace: port: depth: ghostFrame:

TSpace {render}
renderSpace: ogl port: portal depth: depth ghostFrame: ghost | currentCamTrans currentPointerTrans currentCameraInv cpt renderPortals renderedObjects ac cp saveEvent | ac := ogl camera. "ogl glEnable: GLLineSmooth. ogl glHint: GLLineSmoothHint with: GLNicest. ogl glEnable: GLPolygonSmooth. ogl glHint: GLPolygonSmoothHint with: GLNicest. ogl glEnable: GLBlend. ogl glBlendFunc: GLSrcAlpha with: GLOneMinusSrcAlpha." "------ The TSpace render method makes two passes. The first pass is used to render the non-alpha objects and to find the alpha objects. The alpha objects and their transforms are put into the SortedCollection alphaObjects. This array is sorted by distance using the bounding spheres of the objects and the second render pass using the renderAlpha method is made in using this sorted order from furthest to closest. Ghost frames are interleaved TFrames that render along side the space. Ghost frames can not contain portals or lights - as these are just ignored. ------" "------ reset the rayframes if this is the first time through...." renderedObjects := 0. "test ifNotNil:[ ogl eventPointer ifNotNil:[test translation: ogl eventPointer globalPosition + (ogl eventPointer outVector * -50).].]." ac transformClipPlanes. cpt := ac clipPlanesTransform. currentCamTrans := ac globalTransform copy. ogl eventPointer ifNotNil:[currentPointerTrans := ogl eventPointer globalTransform copy.]. currentCameraInv := currentCamTrans orthoNormInverse. ogl glLoadTransposeMatrixf: currentCameraInv. "------ The portals will have to be sorted here.... ------" "------ Render the portals from back to front. ------" (ogl maxPortalDepth > depth and: [ogl suppressPortals not]) ifTrue:[ renderPortals := OrderedCollection new. portalFrames do: [ :pf | (pf isNotPortal3D and:[pf ~= ac currentPortal or:[pf reentrant]])ifTrue:[ " ------ is the portal even visible? ------" pf visible ifTrue:[ " ------ portal facing camera?-----" (pf lookAtCamera: ac) ifTrue:[ "------- is the portal inside the view frustum? ------" pf boundSphere transform: pf globalTransform. (ac testBounds: pf boundSphere) ifTrue:[ renderPortals add: pf. ]. "(ac testBounds: pf boundSphere) ifTrue:" ]. "(delta dot: pf lookAt)>0 ifTrue:" ]. "pf visible" ]. "pf~=ac currentPortal or:[pf reentrant]" ]. "portalFrames do:" ogl forcePick ifTrue:[saveEvent:=ogl eventPointer. ogl eventPointer:nil. ]. (renderPortals asArray sort:[:a1 :a2| a1 cameraDistance < a2 cameraDistance]) do: [:pf | cp := ac currentPortal. ac currentPortal: pf. renderedObjects := renderedObjects + (pf render: ogl depth: depth). ac currentPortal: cp. " ------ restore the camera for the next go round ------ " ac globalTransform: currentCamTrans. ac clipPlanesTransform: cpt.]. ]. "ogl maxPortalDepth > depth ifTrue:" "------ restore camera position and set up clip planes in this pose.------" ogl forcePick ifTrue:[ogl eventPointer: saveEvent.]. ogl eventPointer ifNotNil:[ogl eventPointer globalTransform: currentPointerTrans.]. ogl glLoadTransposeMatrixf: currentCameraInv. "------ Once we have rendered all of the subportals, if this is a portal, set its clip plane so that we don't render objects in front of the portal.------" portal ifNotNil: [ portal enableClipPlane: ogl. ]. " create a new array " " turn on the lights and setup the fog " self setupLights: ogl. fogOn ifTrue:[ self setupFog: ogl. ]. " cull back faces if necessary." self setCull: ogl. "------ Render non-alpha geometry. While we are at it, find the alpha geometry for the next pass. All TFrames know how to do this, including TSpace. TSpace is a root frame (there is no THE root frame in TEA) so we need only call the TSpace >> renderFrame message to render everything inside of this. ------" renderedObjects := renderedObjects + (self renderFrame: ogl ). ogl glPushMatrix. ghost ifNotNil:[ renderedObjects := renderedObjects + (ghost renderFrame: ogl ). ]. ogl glPopMatrix. "------ If there are any alpha objects, set render mode to alpha blending and make a second pass. Use alphaLength because alphaObjects size may be bigger than the actual objects rendered. ------" (alphaObjects size ~= 0 or:[self forceAlpha])ifTrue:[ self renderSpaceAlpha: ogl transform: currentCamTrans. ]. 0 to: 7 do:[ :index | ogl glDisable: GLLight0 + index.]. ogl glDisable: GLCullFace. portal ifNotNil: [portal disableClipPlane:ogl.]. ogl fogOn:false. "clear this at the end because it contains bad things that can't be replicated" alphaObjects := OrderedCollection new: 0. ^ renderedObjects. "Return the number of objects we have rendered."! !

renderSpaceAlpha: transform:

TSpace {render}
renderSpaceAlpha: ogl transform: currentCamTrans | saveTrans | ogl glPushMatrix. ogl glMultTransposeMatrixf: currentCamTrans. self setupAlpha: ogl. "------ Sort the alphaObjects by distance - furthest first ------" saveTrans := ogl transparency. (alphaObjects asArray sort:[:a1 :a2| a1 distance > a2 distance]) do: [:aObject | ogl glPushMatrix. aObject transform ifNotNil:[ ogl glMultMatrixf: aObject transform.]. ogl transparency: aObject transparency. aObject tObject doRenderAlpha: ogl. ogl glPopMatrix. ]. ogl transparency: saveTrans. "------ Set render mode back to original state. ------" ogl glPopMatrix. self restoreFromAlpha: ogl.

renderSubspace:

TSpace {render}
renderSubspace: ogl "Completely render a space as if it is a single TFrame. This is used by the TPortal3D." | rval globalTrans | self pushAlphaObjects. "if we are in the middle of rendering this same world" rval := 0. rval := self renderFrame: ogl. self hasAlphaObjectsToRender ifTrue:[ globalTrans := Matrix4x4 new. ogl glGetFloatv: GLModelviewMatrix with: globalTrans. globalTrans := globalTrans transposed. ogl glLoadMatrixf: globalTrans transposed. self renderSpaceAlpha: ogl transform: (globalTrans inverseTransformation). ]. self popAlphaObjects. ^ rval.! !

renderView: overlay:

TFrame {render}
renderView: ogl overlay: ov "ogl camera globalTransform: self globalMatrixOut." ^ ogl camera renderView: ogl space: self root overlay: ov.

replaceChild: with:

TFrame {*Wisconsin-SDK}
replaceChild: oldChild with: newChild oldChild removeLightFrames. oldChild removePortalFrames. oldChild removeRayFrames. frameChildren at: (frameChildren indexOf: oldChild) put: newChild. oldChild parent: nil. newChild parent: self. newChild root: self root. newChild addLightFrames. newChild addPortalFrames. newChild addRayFrames.

resolveViewpoint:

TFrame {accessing}
resolveViewpoint: ogl "allows a TFrame to stand in for a TPostcard" ^ self.! !

restoreFromAlpha:

TSpace {render}
restoreFromAlpha: ogl ogl glDepthMask: GLTrue. ogl glDisable: GLBlend.

resumeAmbientSound

TSpace {ambient sound}
resumeAmbientSound | volume | ambientSound ifNil:[^self]. volume := 0.8. ambientSound reset. ambientSound volume: 0. ambientSound resumePlaying. self ambientSoundFadeFrom: 0.0 to: volume duration: 1000.0.

rigidBody

TFrame {accessing}
rigidBody "Answer my associated rigid body" ^nil! !

roll

TFrame {transform}
roll ^self pitchYawRoll z! !

roll:

TFrame {transform}
roll: r | angles | angles := self pitchYawRoll. angles z: r. self pitchYawRoll: angles.! !

rollBy: duration: style: rate:

TFrame {yellow-scripts}
rollBy: turns duration: duration style: style rate: samplingRate ^self turn: #ccw turns: turns duration: duration style: style rate: samplingRate! !

root

TFrame {accessing}
root ^ frameRoot.! !
TSpace {accessing}
root "I am my own root" ^ self.! !

root:

TFrame {accessing}
root: rt frameRoot ifNotNil:[frameRoot removeFrame: self]. frameRoot := rt. frameRoot ifNotNil:[frameRoot addFrame: self]. frameChildren ifNotNil:[frameChildren do:[:fc | fc root: rt].].! !

rootService

TSpace {rootService}
rootService updateFrames ifNotNil:[ updateFrames do:[ :uf | uf update. ]. updateFrames := nil. ].! !

rotFromBallPoints: to:

TFrame {transform}
rotFromBallPoints: from to: to | f t | " This matrix needs to be transposed to convert from left handed to right (which is OpenGL's world)." f := from normalized. t := to normalized. f := (f+t) normalized. f := (f+t) normalized. ^ (Quaternion a: (f x * t x) + (f y * t y) + (f z * t z ) b: (f y * t z) - (f z * t y) c: (f z * t x) - (f x * t z) d: (f x * t y) - (f y * t x) ).! !

rotateBy: around:

TFrame {transform}
rotateBy: anAngle around: aVector3 ^self transformBy: (Quaternion angle: anAngle axis: aVector3) asMatrix4x4! !

rotation: around:

TFrame {transform}
rotation: anAngle around: aVector3 | trans | trans := self translation. localTransform := Matrix4x4 identity rotation: anAngle around: aVector3. self translation: trans. self frameChanged. ^ localTransform.! !

rotation: aroundX: y: z:

TFrame {transform}
rotation: anAngle aroundX: xValue y: yValue z: zValue | trans | trans := self translation. localTransform := Matrix4x4 identity rotation: anAngle aroundX: xValue y: yValue z: zValue. self translation: trans. self frameChanged. ^ localTransform.! !

rotationAroundX:

TFrame {transform}
rotationAroundX: anAngle | trans | trans := self translation. localTransform := Matrix4x4 identity rotationAroundX: anAngle. self translation: trans. self frameChanged. ^ localTransform.! !

rotationAroundY:

TFrame {transform}
rotationAroundY: anAngle | trans | trans := self translation. localTransform := Matrix4x4 identity rotationAroundY: anAngle. self translation: trans. self frameChanged. ^ localTransform.! !

rotationAroundZ:

TFrame {transform}
rotationAroundZ: anAngle | trans | trans := self translation. localTransform := Matrix4x4 identity rotationAroundZ: anAngle. self translation: trans. self frameChanged. ^ localTransform.! !

scale

TFrame {transform}
scale ^ 1.0.! !

scale:

TFrame {transform}
scale: scale self translation: scale * self translation. frameChildren ifNotNil:[ frameChildren do:[ :fc | fc scale: scale.]].! !

scheduleSelfDestruct

TFrame {*Wisconsin-SDK}
scheduleSelfDestruct self flag: #FIXME. "A pointerUp is immediately followed by a pointerLeave, which is used for resetting locks and such. Thus whatever gesture caused the cut is going to be immediately followed by more gestures!! Better give them time work. How much is enough? Here we wait five minutes on the grounds that bad latency can play havock with intended message ordering. All we really care about is that the stuff goes away eventually, right? But if you're debugging the problem, you probably want to set this to be less." (self future: 1000 * 60 * 5) reallyDestroy.! !

scriptBehaviors

TFrame {yellow-scripts-support}
scriptBehaviors ^self myBehaviors ifNil:[#()]! !

scriptContext

TSpace {accessing}
scriptContext "Answer the receiver's script context" ^scriptContext! !

scriptContext:

TSpace {accessing}
scriptContext: aScriptContext "Answer the receiver's script context" scriptContext := aScriptContext! !

scriptEventNames

TFrame {scripts}
scriptEventNames "Answer the names of events that script code can see" ^#( pointerDown pointerMove pointerUp pointerEnter pointerOver pointerLeave keyDown keyStroke keyUp )! !

scriptIcon

TFrame {accessing}
scriptIcon ^self class scriptIcon! !

scriptManager

TFrame {scripts}
scriptManager "Get it from elsewhere" ^nil! !

selected:

TFrame {accessing}
selected: fc "Inform the parent frame that this frame has been selected" frameParent selected: fc.! !

serializeMaterial

TFrame {*Wisconsin-SDK}
serializeMaterial ^(self material ifNil: [ ([self texture] on: Error do: [:e | nil]) ifNil: [TMaterial new] ]) serializeMaterial

serializeYourself

TFrame {*Wisconsin-SDK}
serializeYourself | saveObjOwner saveTrans saveUser pickle | saveObjOwner := self parent. saveObjOwner ifNotNil: [saveObjOwner removeChild: self. self grabbedState: false.]. saveTrans := self localTransform. self localTransform: Matrix4x4 identity. saveUser := currentUser. "Should be nil, but let's not copy something that's screwed up." pickle := TIslandCopier new export: self. saveObjOwner ifNotNil: [saveObjOwner addChild: self. self grabbedState: true.]. self localTransform: saveTrans. currentUser := saveUser. ^ pickle.

setCull:

TSpace {render}
setCull: ogl cullBackFaces ifTrue: [ogl glEnable: GLCullFace; glFrontFace: ogl frontFace.] ifFalse: [ogl glDisable: GLCullFace.].

setFrameParent:

TFrame {hierarchy}
setFrameParent: fParent frameParent := fParent.! !

setupAlpha:

TSpace {render}
setupAlpha: ogl ogl glEnable: GLBlend. ogl glDepthMask: GLFalse. " set depth buffer to read only. " ogl glBlendFunc: GLSrcAlpha with: GLOneMinusSrcAlpha.

setupFog:

TSpace {render}
setupFog: ogl ogl fogOn:true; glFogi: GLFogMode with: GLExp; glFogfv: GLFogColor with: (self fogColor asFloatArray); glFogf: GLFogDensity with: fogDensity; glHint: GLFogHint with: GLDontCare; glFogf: GLFogStart with: fogStart; glFogf: GLFogEnd with: fogEnd.

setupLights:

TSpace {render}
setupLights: ogl " Enable the closest six lights at full strength, set the next two as a ratio if distance squared, and ignore the rest. The ratios would work as follows: distanceRatio := 0.5 * furthest distance/closest distance. This guarantees the following: distanceRatio is always less than 1.0. if the two values are very close to each other, then the ratio is about 0.5 : 0.5. if one is much closer than the other, then the ratio approaches 0.0 : 1.0." | sortedFrames distanceRatio | lightFrames size <= 8 ifTrue:[ lightFrames doWithIndex: [ :lf :i | lf enable: ogl index: i ]. lightFrames size + 1 to: 8 do: [ :i | ogl glDisable: (GLLight0 + i - 1). ]. ] ifFalse:[ lightFrames do:[ :lf | lf distance: (ogl camera globalPosition - lf globalPosition ) squaredLength.]. sortedFrames := lightFrames sort:[ :a1 :a2 | a1 distance > a2 distance]. 1 to: 6 do:[ :index | (sortedFrames at: index) enable: ogl index: index.]. distanceRatio := 0.5* ((sortedFrames at: 8) distance)/((sortedFrames at: 7) distance). (sortedFrames at: 7) enable: ogl index: 7 scaled: 1-distanceRatio. (sortedFrames at: 8) enable: ogl index: 8 scaled: distanceRatio. ].

showFrame

TFrame {accessing}
showFrame " TFrame >> showFrame recursively climbs the frame's tree and outputs it the Transcript." self showFrame: 0.! !

showFrame:

TFrame {accessing}
showFrame: depth 1 to: depth do:[ :i | Transcript show:'---|']. Transcript show: self objectName; cr. self frameChildren ifNotNil:[ frameChildren do:[ : fc | fc showFrame: depth+1.].].! !

signalEvent:

TFrame {scripts}
signalEvent: anEvent "Signal the occurance of anEvent" | sndr | super signalEvent: anEvent. myProperties ifNotNil:[ sndr := myProperties player ifNil:[^nil]. anEvent setSender: sndr. sndr signalEvent: anEvent. ].! !

solid

TFrame {accessing}
solid ^ solid.! !

solid:

TFrame {accessing}
solid: bool solid := bool.! !

solidTree:

TFrame {accessing}
solidTree: bool self do:[ :f | f solid: bool].

solidVisibleTree:

TFrame {accessing}
solidVisibleTree: bool self solidTree: bool. self visibleTree: bool.! !

sphereTree

TFrame {accessing}
sphereTree | bs | bs := self boundSphere. bs ifNotNil:[ frameChildren ifNotNil:[ frameChildren do:[ :fc | bs := bs union: (fc sphereTree).].]. ^ bs. ]. frameChildren ifNotNil:[ frameChildren do:[ :fc | bs ifNil:[ bs := fc sphereTree. ] ifNotNil: [bs := bs union: (fc sphereTree). ]. ]. ^ bs. ]. ^ nil.! !

start

TFrame {events}
start " Called when a TFrame is inserted into the hierarchy. Can be used to start sending future messages. "! !

startAmbientSound

TSpace {ambient sound}
startAmbientSound ambientSound ifNotNil:[ ambientSound isLoaded ifFalse:[^self]. ambientSound resumePlaying].! !

stepTime

TFrame {events}
stepTime "default step time - used when we call #start" ^100. ! !

stop

TFrame {events}
stop " Called when a TFrame is removed from the hierarchy. Can be used to stop sending future messages. "! !

stopAmbientSound

TSpace {ambient sound}
stopAmbientSound ambientSound ifNotNil:[ ambientSound isLoaded ifFalse:[^self]. ambientSound pause].! !

switchToAmbientSoundFrom:

TSpace {ambient sound}
switchToAmbientSoundFrom: prevSpace (self future: 1000.0) resumeAmbientSound. prevSpace pauseAmbientSound.! !

task:

TFrame {events}
task: task "default behavior for handling tasks" ^ task.! !

test

TFrame {accessing}
test ^ test.! !

test:

TFrame {accessing}
test: tst test := tst.! !

testRayFrames:

TSpace {render}
testRayFrames: bs rayFrames do:[ :rf | rf automatic ifTrue:[rf pick: bs.].].! !

testRayFramesQuadTree:

TSpace {render}
testRayFramesQuadTree: qt testRays ifTrue:[ rayFrames do:[ :rf | (rf automatic and:[rf downRay]) ifTrue: [ rf currentFrame: qt. qt quadPickFloor: rf location: rf globalPosition ].].].! !

testRays

TSpace {accessing}
testRays ^ testRays.! !

testRays:

TSpace {accessing}
testRays: bool " This is to turn off testing if we re-enter the same space. I should only test once. " testRays := bool.! !

things

GridParcelSpace {as yet unclassified}
things " things is a TGroup, for holding all the things, with Z axis going up " ^ things! ! 'From Croquet1.0beta of 11 April 2006 [latest update: #0] on 24 March 2007 at 5:54:05 pm'!

transcript:

TFrame {events}
transcript: txt Transcript show: txt.! !

transfer:

TFrame {hierarchy}
transfer: frame frame transferTo: self.

transferTo:

TFrame {hierarchy}
transferTo: frame | trns | trns := frame relativeTransform: self. self parent removeChild: self. self localTransform: trns. frame addChild: self.

transformBy:

TFrame {transform}
transformBy: m4x4 localTransform := localTransform composedWithLocal: m4x4. self frameChanged. ^ localTransform.

translateIntoContactWith: alongNormal:

TFrame {transform}
translateIntoContactWith: aPoint alongNormal: norm "Adjust my frame translation to be 'in contact' with the given point, such that: the given point touches my bounding box, and the normal from the point passes through my origin. The point and normal are in my parent's frame of reference. This is used for spatial drag and drop." | box offset | "For visually correct-looking results, we need to work with the bounding box, rather than the frame origin and boundSphere, since nontrivial models are rarely spheroid or balanced around the origin." box := self boundingBox transformedBy: (self orientation). offset := ( (norm x > 0 ifTrue: [box min x negated] ifFalse: [box max x]) @ (norm y > 0 ifTrue: [box min y negated] ifFalse: [box max y]) @ (norm z > 0 ifTrue: [box min z negated] ifFalse: [box max z])). offset := offset * norm. "Offset is now the offset for the box center along the normal." self translation: aPoint - box center + (box center * norm) + offset.

translation

TFrame {transform}
translation ^localTransform translation.! !

translation:

TFrame {transform}
translation: aVector localTransform translation: aVector. self frameChanged. ^ localTransform.

translationX: y: z:

TFrame {transform}
translationX: xValue y: yValue z: zValue localTransform translationX: xValue y: yValue z: zValue. self frameChanged. ^ localTransform.

transparency:

TFrame {accessing}
transparency: trans frameChildren ifNotNil:[ frameChildren do:[ :fc | fc transparency: trans].].! !

unhilite

TFrame {accessing}
unhilite "Cancel hiliting of this frame, so it appears normally. See #hilite: and #hilite ." hiliteColor := nil.! !

upVector

TFrame {transform}
upVector ^ self globalTransform column2. ! !

visible

TFrame {accessing}
visible ^ visible.! !

visible:

TFrame {accessing}
visible: bool visible := bool.! !

visibleTree

TFrame {accessing}
visibleTree self visible ifTrue:[^ true]. frameChildren ifNotNil:[ frameChildren do:[ :fc | fc visibleTree ifTrue:[^ true].].]. ^ false.! !

visibleTree:

TFrame {accessing}
visibleTree: bool self do:[ :f | f visible: bool].

wantsKPointerOver

TFrame {*Wisconsin-SDK}
wantsKPointerOver "See KPointer>>resetSelected:" ^false! ! "-- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- "! TFrame class instanceVariableNames: 'protoData'!

yaw

TFrame {transform}
yaw ^self pitchYawRoll y! !

yaw:

TFrame {transform}
yaw: y | angles | angles := self pitchYawRoll. angles y: y. self pitchYawRoll: angles.! !

yawTransform

TFrame {transform}
yawTransform | v | v := localTransform row3. v x > 0 ifTrue:[self yaw: v z arcCos radiansToDegrees negated] ifFalse: [self yaw: v z arcCos radiansToDegrees.].! !