index xrefs 2006/08/08 17:41:24

ChemoJunAbstractViewer

ChemoJun050 (2006/08/08) Copyright 2002-2006 National Institute of Informatics, Research Organization of Information and Systems.

category:

inheritance:

instance variables:

class instance variables:

class variables:

pool variables:

instance methods:

  1. asImage [converting] xrefs
    	| aView imageExtent |
    	aView := self getView.
    	(aView isNil or: [aView isOpen not]) 
    		ifTrue: [imageExtent := self defaultImageExtent]
    		ifFalse: [imageExtent := aView bounds extent].
    	^self asImageExtent: imageExtent
  2. asImageExtent: imageExtent [converting] xrefs
     
    	| anImage aPixmap |
    	anImage := super asImageExtent: imageExtent.
    	JunControlUtility 
    		assert: [aPixmap := Pixmap extent: anImage extent]
    		do: 
    			[anImage displayOn: aPixmap graphicsContext.
    			superimposeBlock notNil 
    				ifTrue: 
    					[| arguments |
    					arguments := Array 
    								with: self
    								with: aPixmap
    								with: nil.
    					superimposeBlock 
    						valueWithArguments: (arguments copyFrom: 1 to: superimposeBlock numArgs)]]
    		ensure: 
    			[anImage := aPixmap asImage.
    			aPixmap close].
    	^anImage
  3. boundingBoxesFrom: a3dObject [pencil] xrefs
     
    	| width height depth denominator point boundingBoxes |
    	width := a3dObject boundingBox width.
    	height := a3dObject boundingBox height.
    	depth := a3dObject boundingBox depth.
    	denominator := width max: (height max: depth).
    	point := width / denominator , (height / denominator) 
    				, (depth / denominator).
    	point := point * self defaultPartitionSize.
    	point := point rounded.
    	boundingBoxes := Jun3dBoundingBoxes fromObject: a3dObject howMany: point.
    	self pencilTrace: 
    			[| aBody aViewfinder aViewport |
    			aBody := JunOpenGL3dCompoundObject new.
    			aBody add: self displayObject.
    			aBody add: a3dObject.
    			aBody 
    				add: (boundingBoxes asJunOpenGL3dObjectColor: ColorValue cyan alpha: 0.1).
    			aViewfinder := JunOpenGLDisplayModel displayObject: aBody.
    			aViewfinder defaultProjectionTable: self projectionTable.
    			aViewfinder openAt: 200 @ 200.
    			aViewfinder parallelProjection.
    			aViewport := JunOpenGLShowModel displayModel: aViewfinder.
    			aViewport useTransparency: true.
    			aViewport openAt: 200 @ 200.
    			aViewport parallelProjection].
    	^boundingBoxes
  4. classToSpawn [private] xrefs
    	(JunSensorUtility shiftDown or: [JunSensorUtility altDown]) 
    		ifTrue: [^JunOpenGLDisplayModel].
    	^ChemoJunAbstractViewer
  5. clickAt: aPoint [actions] xrefs
     
    	^self
  6. cloneViewer [private] xrefs
    	^self cloneViewerUseDisplayList: self useDisplayList
  7. cloneViewerUseDisplayList: aBoolean [private] xrefs
     
    	| aViewer |
    	aViewer := self class new.
    	aBoolean = true 
    		ifTrue: [aViewer useDisplayList: true]
    		ifFalse: [aViewer useDisplayList: false].
    	aViewer displayObject: self displayObject.
    	aViewer defaultProjectionTable: self projectionTable.
    	aViewer allButOpenInterface: #windowSpec.
    	aViewer projectionTable: self projectionTable.
    	^aViewer
  8. convert: collectionOfPoints triangles: collectionOfTriangles controller: aController [pencil] xrefs
     
    	| aPlane aProjection pointCollection triangleCollection |
    	aProjection := self displayProjection.
    	pointCollection := collectionOfPoints collect: 
    					[:point | 
    					| aPoint |
    					aPoint := aController regularizePoint: point.
    					aPoint := aProjection translateTo3dPointFromPoint: aPoint.
    					aPoint := aPoint - self sightPoint.
    					aPoint yourself].
    	triangleCollection := collectionOfTriangles collect: 
    					[:triangle | 
    					| aTriangle |
    					aTriangle := triangle collect: 
    									[:point | 
    									| aPoint |
    									aPoint := aController regularizePoint: point.
    									aPoint := aProjection translateTo3dPointFromPoint: aPoint.
    									aPoint := aPoint - self sightPoint.
    									aPoint yourself].
    					aPlane := JunPlane 
    								on: (aTriangle at: 1)
    								on: (aTriangle at: 2)
    								on: (aTriangle at: 3).
    					(aPlane valueF: self eyePoint) sign < 0 
    						ifTrue: [aTriangle := aTriangle reverse].
    					aTriangle yourself].
    	self pencilTrace: 
    			[| aLine aTransformation0 aTransformation1 aTransformation2 aBody aViewfinder aViewport |
    			aLine := (self sightPoint to: self eyePoint) normalized.
    			aTransformation0 := Jun3dTransformation 
    						translate: (aLine atT: self zoomHeight / 2).
    			aTransformation1 := Jun3dTransformation 
    						translate: (aLine atT: self zoomHeight / 1.99).
    			aTransformation2 := Jun3dTransformation 
    						translate: (aLine atT: self zoomHeight / 1.98).
    			aBody := JunOpenGL3dCompoundObject new.
    			aBody add: self displayObject.
    			triangleCollection do: 
    					[:triangle | 
    					| aTriangle aPolyline |
    					aTriangle := (JunOpenGL3dPolygon vertexes: triangle asArray) 
    								transform: aTransformation0.
    					aTriangle paint: (ColorValue red blendWith: ColorValue white).
    					aBody add: aTriangle.
    					aTriangle := (JunOpenGL3dPolylineLoop vertexes: triangle asArray) 
    								transform: aTransformation1.
    					aTriangle lineWidth: 1.
    					aTriangle paint: ColorValue red.
    					aBody add: aTriangle.
    					aPolyline := (JunOpenGL3dPolylineLoop vertexes: pointCollection) 
    								transform: aTransformation2.
    					aPolyline lineWidth: 3.
    					aPolyline paint: ColorValue magenta.
    					aBody add: aPolyline].
    			aViewfinder := JunOpenGLDisplayModel displayObject: aBody.
    			aViewfinder defaultProjectionTable: self projectionTable.
    			aViewfinder openAt: 200 @ 200.
    			aViewfinder parallelProjection.
    			aViewport := JunOpenGLShowModel displayModel: aViewfinder.
    			aViewport useTransparency: true.
    			aViewport openAt: 200 @ 200.
    			aViewport parallelProjection].
    	^Array with: pointCollection with: triangleCollection
  9. cylinder: pointCollection triangles: triangleCollection [pencil] xrefs
     
    	| baseLine aRadius anInterval anArray aCylinder aPolygon aTransformation |
    	baseLine := (Jun3dLine from: self sightPoint to: self eyePoint) 
    				normalizedLine.
    	aRadius := self zoomHeight / 2.
    	baseLine := Jun3dLine from: (baseLine atT: 0)
    				to: (baseLine atT: aRadius * 1.5).
    	anInterval := 0 to: 1 by: 0.1.
    	anArray := Array new: anInterval size.
    	(1 to: anArray size) 
    		do: [:index | anArray at: index put: (OrderedCollection new: pointCollection size)].
    	pointCollection do: 
    			[:aPoint | 
    			| aLine |
    			aLine := baseLine translatedBy: aPoint.
    			anInterval with: (1 to: anArray size)
    				do: [:t :index | (anArray at: index) add: (aLine atT: t)]].
    	aCylinder := JunOpenGL3dCompoundObject new.
    	(1 to: anArray size - 1) do: 
    			[:arrayIndex | 
    			| fromPoints toPoints fp1 tp1 fp2 tp2 |
    			fromPoints := anArray at: arrayIndex.
    			toPoints := anArray at: arrayIndex + 1.
    			fp1 := fromPoints at: 1.
    			tp1 := toPoints at: 1.
    			(2 to: pointCollection size) do: 
    					[:index | 
    					fp2 := fromPoints at: index.
    					tp2 := toPoints at: index.
    					aPolygon := JunOpenGL3dPolygon vertexes: (Array 
    										with: fp1
    										with: tp1
    										with: tp2
    										with: fp2).
    					self defaultTriangulationClass = JunFormTriangulation3 
    						ifTrue: [aPolygon := aPolygon reversed].
    					aCylinder add: aPolygon.
    					fp1 := fp2.
    					tp1 := tp2]].
    	aTransformation := Jun3dTransformation translate: (baseLine atT: 0).
    	triangleCollection do: 
    			[:aTriangle | 
    			aPolygon := (JunOpenGL3dPolygon vertexes: aTriangle reverse) 
    						transform: aTransformation.
    			aCylinder add: aPolygon].
    	aTransformation := Jun3dTransformation translate: (baseLine atT: 1).
    	triangleCollection do: 
    			[:aTriangle | 
    			aPolygon := (JunOpenGL3dPolygon vertexes: aTriangle yourself) 
    						transform: aTransformation.
    			aCylinder add: aPolygon].
    	aCylinder 
    		primitivesDo: [:primitive | primitive paint: ColorValue magenta alpha: 0.5].
    	self pencilTrace: 
    			[| aBody aViewfinder aViewport |
    			aBody := JunOpenGL3dCompoundObject new.
    			aBody add: self displayObject.
    			aBody add: aCylinder.
    			aViewfinder := JunOpenGLDisplayModel displayObject: aBody.
    			aViewfinder defaultProjectionTable: self projectionTable.
    			aViewfinder openAt: 200 @ 200.
    			aViewfinder parallelProjection.
    			aViewport := JunOpenGLShowModel displayModel: aViewfinder.
    			aViewport useTransparency: true.
    			aViewport openAt: 200 @ 200.
    			aViewport parallelProjection].
    	^aCylinder
  10. defaulSerialNumberSetting [defaults] xrefs
    	| aSerialNumberSetting |
    	aSerialNumberSetting := ChemoJunSerialNumberSetting new.
    	^aSerialNumberSetting
  11. defaultBaseName [defaults] xrefs
    	^self displayObject name ifNil: [super defaultBaseName]
    		ifNotNil: [:aString | aString , '_' , JunSystem defaultBaseName]
  12. defaultDisplayViewClass [defaults] xrefs
    	^ChemoJunAbstractViewerView
  13. defaultEyePoint [defaults] xrefs
    	| box distance |
    	self displayObject isNil ifTrue: [^10000 , 0 , 0].
    	^self defaultProjectionTable at: #eyePoint
    		ifAbsent: 
    			[box := self boundingBox.
    			distance := box origin distance: box corner.
    			distance := distance * 2.
    			^distance , 0 , 0]
  14. defaultMinimumTriangleArea [defaults] xrefs
    	self featureResolution = #high ifTrue: [^0.001]
  15. defaultPartitionSize [defaults] xrefs
    	^16
  16. defaultResolution [defaults] xrefs
    	defaultResolution isNil ifTrue: [defaultResolution := #medium].
    	^defaultResolution
  17. defaultResolution: aSymbol [defaults] xrefs
     
    	(#(#low #medium #high) includes: aSymbol)
    		ifTrue: [defaultResolution := aSymbol]
  18. defaultShading [defaults] xrefs
    	^self defaultProjectionTable at: #shading ifAbsent: [^#smoothShading]
  19. defaultString [defaults] xrefs
    	^String new
  20. defaultTriangulationClass [defaults] xrefs
    	"{ JunFormTriangulation2 | JunFormTriangulation3 }"
    
    	^JunFormTriangulation2
  21. defaultUpVector [defaults] xrefs
    	^self defaultProjectionTable at: #upVector ifAbsent: [0 , -1 , 1]
  22. defaultWindowLabel [defaults] xrefs
    	^(#jun_Viewfinder >> 'Viewfinder') asString
  23. extractPatchesFrom: boundingBoxes [pencil] xrefs
     
    	| compoundObject cursorAnimator |
    	compoundObject := JunOpenGL3dCompoundObject new.
    	cursorAnimator := JunCursorAnimator clockCursors.
    	cursorAnimator tick: 1000.
    	cursorAnimator showWhile: 
    			[self displayObject polygonsDo: 
    					[:aPolygon | 
    					| anArray |
    					anArray := aPolygon asPointArray 
    								collect: [:aPoint | boundingBoxes containsPoint: aPoint].
    					(anArray detect: [:aBoolean | aBoolean = false] ifNone: [nil]) isNil 
    						ifTrue: [compoundObject add: aPolygon]]].
    	self pencilTrace: 
    			[| aBody aViewfinder |
    			aBody := JunOpenGL3dCompoundObject new.
    			aBody add: compoundObject.
    			aBody 
    				add: (boundingBoxes asJunOpenGL3dObjectColor: ColorValue cyan alpha: 0.1).
    			aViewfinder := JunOpenGLDisplayModel displayObject: aBody.
    			aViewfinder defaultProjectionTable: self projectionTable.
    			aViewfinder openAt: 200 @ 200.
    			aViewfinder parallelProjection].
    	"[| frontPatches |
    	frontPatches := JunOpenGL3dCompoundObject new.
    	compoundObject polygonsDo: 
    			[:aPolygon | 
    			| pointCollection aPlane |
    			pointCollection := aPolygon vertexes.
    			aPlane := JunPlane 
    						on: (pointCollection at: 1)
    						on: (pointCollection at: pointCollection size // 3 + 1)
    						on: (pointCollection at: pointCollection size // 3 * 2 + 1).
    			(aPlane valueF: self eyePoint) >= 0 ifTrue: [frontPatches add: aPolygon]].
    	compoundObject := frontPatches] value."
    	^compoundObject
  24. featureResolution [accessing] xrefs
    	^#medium
  25. fileName [accessing] xrefs
    	^nil
  26. flushDisplayObject [flushing] xrefs
    	self displayObject: nil
  27. getInformationView [private] xrefs
    	| window |
    	window := self informationHolder dependents detect: [:each | each isKindOf: ComposedTextView]
    				ifNone: [nil].
    	window isNil ifTrue: [^nil].
    	^window
  28. getInformationWindow [private] xrefs
    	| window |
    	window := self informationHolder dependents detect: [:each | each isKindOf: ScheduledWindow]
    				ifNone: [nil].
    	window isNil ifTrue: [^nil].
    	^window
  29. highResolution [menu messages] xrefs
    	self defaultResolution: #high.
    	self updateViewMenuIndication
  30. informationHolder [accessing] xrefs
    	informationHolder isNil
    		ifTrue: 
    			[informationHolder := ValueHolder with: String new.
    			informationHolder compute: [:value | self setInformationWindowLabel]].
    	^informationHolder
  31. initialize [initialize-release] xrefs
    	super initialize.
    	informationHolder := nil.
    	defaultResolution := nil.
    	withoutResetViewWhenOpen := false.
    	self serialNumberSetting
  32. is2d [testing] xrefs
    	^false
  33. is3d [testing] xrefs
    	^true
  34. isElectroViewer [testing] xrefs
    	^false
  35. isFeaturesViewer [testing] xrefs
    	^false
  36. isMoleculeViewer [testing] xrefs
    	^false
  37. isStericViewer [testing] xrefs
    	^false
  38. lowResolution [menu messages] xrefs
    	self defaultResolution: #low.
    	self updateViewMenuIndication
  39. mediumResolution [menu messages] xrefs
    	self defaultResolution: #medium.
    	self updateViewMenuIndication
  40. noticeOfWindowClose: aWindow [interface closing] xrefs
     
    	| window |
    	super noticeOfWindowClose: aWindow.
    	window := self getInformationWindow.
    	window isNil ifFalse: [window sensor eventQuit: nil].
    	self serialNumberSetting closeRequest
  41. numberOfPolygons [accessing] xrefs
    	| numberOfPolygons |
    	self displayObject isNil ifTrue: [^0].
    	numberOfPolygons := 0.
    	self displayObject polygonsDo: [:each | numberOfPolygons := numberOfPolygons + 1].
    	^numberOfPolygons
  42. numberOfPrimitives [accessing] xrefs
    	| numberOfPrimitives |
    	self displayObject isNil ifTrue: [^0].
    	numberOfPrimitives := 0.
    	self displayObject primitivesDo: [:each | numberOfPrimitives := numberOfPrimitives + 1].
    	^numberOfPrimitives
  43. openWithoutResetView [interface opening] xrefs
    	withoutResetViewWhenOpen := true.
    	self open
  44. pencilClosedPointCollection: collectionOfPoints from: aController [pencil] xrefs
     
    	| aTriangulation anArray aCylinder boundingBoxes patchCollection |
    	self displayObject isNil ifTrue: [^nil].
    	collectionOfPoints size < 3 ifTrue: [^nil].
    	aController isNil ifTrue: [^nil].
    	self errorSignal handle: 
    			[:exception | 
    			JunDialog 
    				warn: (#chemoJun_Can_not_perform_triangulation_ 
    						>> 'Can not perform triangulation.') asString.
    			^nil]
    		do: 
    			[aTriangulation := self 
    						triangulationClass: self defaultTriangulationClass
    						pointCollection: collectionOfPoints
    						controller: aController].
    	self errorSignal handle: 
    			[:exception | 
    			JunDialog 
    				warn: (#chemoJun_Can_not_perform_conversion_ >> 'Can not perform conversion.') 
    						asString.
    			^nil]
    		do: 
    			[anArray := self 
    						convert: aTriangulation points
    						triangles: aTriangulation triangles
    						controller: aController].
    	aCylinder := self cylinder: anArray first triangles: anArray last.
    	aCylinder components isEmpty ifTrue: [^nil].
    	boundingBoxes := self boundingBoxesFrom: aCylinder.
    	boundingBoxes isEmpty ifTrue: [^nil].
    	patchCollection := self extractPatchesFrom: boundingBoxes.
    	patchCollection components isEmpty ifTrue: [^nil].
    	self spawnObject: patchCollection
  45. pencilOpenedPointCollection: collectionOfPoints from: aController [pencil] xrefs
     
    	| aPlane patchCollection |
    	self displayObject isNil ifTrue: [^nil].
    	collectionOfPoints size < 3 ifTrue: [^nil].
    	aController isNil ifTrue: [^nil].
    	aPlane := self plane: collectionOfPoints from: aController.
    	patchCollection := self splitPathesFrom: aPlane.
    	patchCollection components isEmpty ifTrue: [^nil].
    	self spawnObject: patchCollection
  46. pencilTrace: aBlock [pencil] xrefs
     
    	"aBlock value"
  47. pickedObjectAt: mouse2dPoint [actions] xrefs
     
    	| compoundObject pickedObject |
    	self displayObject isNil ifTrue: [^nil].
    	compoundObject := JunOpenGL3dCompoundObject new.
    	self displayObject polygonsDo: [:aPolygon | compoundObject add: aPolygon].
    	pickedObject := JunOpenGLObjectPicker 
    				pickObjectAt: mouse2dPoint
    				fromCompound: compoundObject
    				projection: self displayProjection.
    	pickedObject isNil ifTrue: [^nil].
    	^pickedObject
  48. plane: collectionOfPoints from: aController [pencil] xrefs
     
    	| aProjection pointCollection firstPoint secondPoint thirdPoint aLine aPlane |
    	self pencilTrace: 
    			[aController notNil 
    				ifTrue: 
    					[| anImage aWindow |
    					anImage := aController view topComponent asImage.
    					aWindow := ScheduledWindow new.
    					aWindow label: self getWindow label.
    					aWindow component: anImage.
    					aWindow openIn: (200 @ 200 extent: anImage extent)]].
    	aProjection := self displayProjection.
    	pointCollection := collectionOfPoints collect: 
    					[:point | 
    					| aPoint |
    					aPoint := aController regularizePoint: point.
    					aPoint := aProjection translateTo3dPointFromPoint: aPoint.
    					aPoint := aPoint - self sightPoint.
    					aPoint yourself].
    	aLine := (Jun3dLine from: self sightPoint to: self eyePoint) 
    				normalizedLine.
    	firstPoint := pointCollection first 
    				translatedBy: (aLine atT: self zoomHeight / 2).
    	secondPoint := pointCollection last 
    				translatedBy: (aLine atT: self zoomHeight / 2).
    	aLine := aLine 
    				translatedBy: (firstPoint center: secondPoint) - (aLine atT: 0).
    	thirdPoint := aLine atT: (self zoomHeight * 1.5) negated.
    	aPlane := firstPoint plane: secondPoint and: thirdPoint.
    	^aPlane
  49. postOpenWith: aBuilder [interface opening] xrefs
     
    	super postOpenWith: aBuilder.
    	self setWindowLabel.
    	withoutResetViewWhenOpen = false ifTrue: [self resetView]
  50. serialNumberSetting [accessing] xrefs
    	serialNumberSetting ifNil: 
    			[serialNumberSetting := self defaulSerialNumberSetting.
    			serialNumberSetting compute: 
    					[:expression | 
    					self indexExpression: expression.
    					self flushDisplayObject.
    					self changed: #object].
    			self indexExpression: serialNumberSetting expression].
    	^serialNumberSetting
  51. setInformationWindowLabel [private] xrefs
    	| aWindow aString |
    	aWindow := self getInformationWindow.
    	aWindow isNil ifTrue: [^nil].
    	aString := (#chemoJun_Information >> 'Information') asString.
    	self fileName notNil ifTrue: [aString := aString , ' [' , (Filename splitPath: self fileName asString) last , ']'].
    	aWindow label: aString
  52. settingIndex [menu messages] xrefs
    	self serialNumberSetting ifNotNil: 
    			[:aSerialNumberSetting | 
    			| aWindow |
    			(aWindow := aSerialNumberSetting getWindow) isNil 
    				ifTrue: 
    					[aWindow := self getWindow.
    					aWindow isNil 
    						ifTrue: [self serialNumberSetting open]
    						ifFalse: 
    							[self serialNumberSetting openAt: aWindow displayBox topRight + (8 @ 0)]]
    				ifFalse: 
    					[aWindow isCollapsed ifTrue: [aWindow expand].
    					aWindow raise]]
  53. setWindowLabel [interface opening] xrefs
    	| aWindow |
    	aWindow := self getWindow.
    	aWindow isNil ifTrue: [^nil].
    	aWindow model = self ifFalse: [^nil].
    	aWindow label: self defaultWindowLabel
  54. showInformation [menu messages] xrefs
    	| aWindow myWindow aView |
    	(aWindow := self getInformationWindow) isNil
    		ifTrue: 
    			[aWindow := ComposedTextView
    						createOn: self informationHolder
    						label: (#chemoJun_Information >> 'Information') asString
    						icon: (Icon constantNamed: #workspace).
    			(myWindow := self getWindow) isNil
    				ifTrue: [aWindow openWithExtent: 300 @ 300]
    				ifFalse: [aWindow openIn: (myWindow displayBox bottomRight + (8 @ 27) extent: 300 @ 300)].
    			aView := self getInformationView.
    			aView controller menuHolder: [self class editMenu].
    			self setInformationWindowLabel]
    		ifFalse: 
    			[aWindow isCollapsed ifTrue: [aWindow expand].
    			aWindow raise]
  55. spawnObject [menu messages] xrefs
    	| displayModel |
    	displayModel := super spawnObject.
    	self moleculeObject 
    		ifNotNil: [:it | displayModel displayObject name: it baseName].
    	displayModel setWindowLabel.
    	displayModel updateMenuIndication.
    	^displayModel
  56. spawnObject: spawningObject [menu messages] xrefs
     
    	| aViewer aWindow |
    	aViewer := self cloneViewer.
    	aViewer displayObject: spawningObject.
    	aWindow := aViewer builder window.
    	aWindow openWithExtent: aWindow bounds extent.
    	aWindow displayPendingInvalidation.
    	aViewer setWindowLabel.
    	aViewer updateMenuIndication.
    	^aWindow
  57. splitPathesFrom: aPlane [pencil] xrefs
     
    	| compoundObject cursorAnimator |
    	self pencilTrace: 
    			[| aCircle aBody aViewfinder |
    			aCircle := Jun3dCircle 
    						center: aPlane asTriangle centerOfGravity
    						radius: self zoomHeight / 2
    						upVector: aPlane normalVector.
    			aBody := JunOpenGL3dCompoundObject new.
    			aBody add: self displayObject.
    			aBody 
    				add: (aCircle asJunOpenGL3dObjectColor: ColorValue magenta alpha: 0.5) 
    						reversed.
    			aBody 
    				add: (aCircle asJunOpenGL3dObjectColor: ColorValue magenta alpha: 0.5).
    			aViewfinder := JunOpenGLDisplayModel displayObject: aBody.
    			aViewfinder defaultProjectionTable: self projectionTable.
    			aViewfinder openAt: 200 @ 200
    			"aViewfinder parallelProjection"].
    	compoundObject := JunOpenGL3dCompoundObject new.
    	cursorAnimator := JunCursorAnimator handCursors.
    	cursorAnimator tick: 1000.
    	cursorAnimator showWhile: 
    			[self displayObject polygonsDo: 
    					[:aPolygon | 
    					| anArray |
    					anArray := aPolygon asPointArray 
    								collect: [:aPoint | (aPlane valueF: aPoint) >= 0].
    					(anArray detect: [:aBoolean | aBoolean = false] ifNone: [nil]) isNil 
    						ifTrue: [compoundObject add: aPolygon]]].
    	self pencilTrace: 
    			[| aCircle aBody aViewfinder |
    			aCircle := Jun3dCircle 
    						center: aPlane asTriangle centerOfGravity
    						radius: self zoomHeight / 2
    						upVector: aPlane normalVector.
    			aBody := JunOpenGL3dCompoundObject new.
    			aBody add: compoundObject.
    			aBody 
    				add: (aCircle asJunOpenGL3dObjectColor: ColorValue magenta alpha: 0.5) 
    						reversed.
    			aBody 
    				add: (aCircle asJunOpenGL3dObjectColor: ColorValue magenta alpha: 0.5).
    			aViewfinder := JunOpenGLDisplayModel displayObject: aBody.
    			aViewfinder defaultProjectionTable: self projectionTable.
    			aViewfinder openAt: 200 @ 200
    			"aViewfinder parallelProjection"].
    	^compoundObject
  58. triangulationClass: aClass pointCollection: collectionOfPoints controller: aController [pencil] xrefs
     
    	| formTriangulation |
    	self pencilTrace: 
    			[aController notNil 
    				ifTrue: 
    					[| anImage aWindow |
    					anImage := aController view topComponent asImage.
    					aWindow := ScheduledWindow new.
    					aWindow label: self getWindow label.
    					aWindow component: anImage.
    					aWindow openIn: (200 @ 200 extent: anImage extent)]].
    	formTriangulation := aClass points: collectionOfPoints.
    	self pencilTrace: 
    			[| aWindow aPixmap graphicsContext |
    			aWindow := ScheduledWindow new.
    			aWindow label: 'Triangulation'.
    			aWindow 
    				openIn: (200 @ 200 extent: formTriangulation boundingBox extent rounded).
    			aPixmap := Pixmap extent: aWindow bounds extent.
    			
    			[self errorSignal handle: 
    					[:exception | 
    					aWindow controller closeAndUnschedule.
    					exception reject]
    				do: 
    					[graphicsContext := aPixmap graphicsContext.
    					graphicsContext paint: ColorValue white.
    					graphicsContext displayRectangle: aPixmap bounds.
    					JunApplicationModel displayPendingInvalidation.
    					Cursor wait showWhile: 
    							[self defaultTriangulationClass = JunFormTriangulation2 
    								ifTrue: 
    									[formTriangulation trianglesInterim: 
    											[:triangles :triangle :pending | 
    											formTriangulation 
    												displayOn: graphicsContext
    												triangles: triangles
    												triangle: triangle
    												pending: pending.
    											JunApplicationModel displayPendingInvalidation.
    											aWindow raise.
    											aWindow graphicsContext displayPixmap: aPixmap at: Point zero]].
    							self defaultTriangulationClass = JunFormTriangulation3 
    								ifTrue: 
    									[formTriangulation trianglesInterim: 
    											[:triangles | 
    											formTriangulation displayOn: graphicsContext triangles: triangles.
    											JunApplicationModel displayPendingInvalidation.
    											aWindow raise.
    											aWindow graphicsContext displayPixmap: aPixmap at: Point zero]]].
    					formTriangulation displayOn: graphicsContext.
    					JunApplicationModel displayPendingInvalidation.
    					aWindow raise.
    					aWindow graphicsContext displayPixmap: aPixmap at: Point zero.
    					aWindow component: aPixmap asImage.
    					aWindow display.
    					JunApplicationModel displayPendingInvalidation]] 
    					ensure: [aPixmap close]].
    	^formTriangulation
  59. updateStringHolder: aValue [updating] xrefs
     
    	^self
  60. updateViewMenuIndication [menu accessing] xrefs
    	^self

class methods:

  1. copyright [copyright] xrefs
    	^'ChemoJun050 (2006/08/08) Copyright 2002-2006 National Institute of Informatics, Research Organization of Information and Systems.'
  2. system [copyright] xrefs
    	^'ChemoJun'
  3. version [copyright] xrefs
    	^'050'

index xrefs