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

ChemoJunMoleculeViewer

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. asGraph [converting] xrefs
    	^self moleculeObject asGraph
  2. asGrapher [converting] xrefs
    	^self moleculeObject asGrapher
  3. atomConnections [accessing] xrefs
    	^self moleculeObject ifNil: [Array new]
    		ifNotNil: [:it | it atomConnections]
  4. atomConnectionsDo: aBlock [enumerating] xrefs
     
    	self moleculeObject ifNotNil: [:it | it atomConnectionsDo: aBlock]
  5. atomObjects [accessing] xrefs
    	^self moleculeObject ifNil: [Array new] ifNotNil: [:it | it atomObjects]
  6. atomObjectsAndIndexesDo: aBlock [enumerating] xrefs
     
    	self moleculeObject ifNotNil: [:it | it atomObjectsAndIndexesDo: aBlock]
  7. atomObjectsDo: aBlock [enumerating] xrefs
     
    	self moleculeObject ifNotNil: [:it | it atomObjectsDo: aBlock]
  8. beInvisibleCameraButton [buttons] xrefs
    	| specWrapper |
    	(specWrapper := self cameraButtonSpecWrapper) isNil ifTrue: [^nil].
    	specWrapper
    		beInvisible;
    		disable
  9. beVisibleCameraButton [buttons] xrefs
    	| specWrapper |
    	(specWrapper := self cameraButtonSpecWrapper) isNil ifTrue: [^nil].
    	specWrapper
    		beVisible;
    		enable
  10. browseManual [menu messages] xrefs
    	JunURL browse: (ChemoJunUtility 
    				manualUriStringConstruct: 'ChemoJunMoleculeViewer/index.html')
  11. cameraButton [buttons] xrefs
    	cameraButton isNil 
    		ifTrue: 
    			[| image figure shape button |
    			image := JunCursors cameraCursor asOpaqueImage.
    			figure := image figure asImage.
    			shape := image shape asImage.
    			image := OpaqueImage figure: figure shape: shape.
    			button := JunButtonModel 
    						value: false
    						visual: image
    						action: [:model | model changed: #value].
    			cameraButton := button].
    	^cameraButton
  12. cameraButtonSpecWrapper [buttons] xrefs
    	| aBuilder |
    	(aBuilder := self builder) isNil ifTrue: [^nil].
    	^aBuilder componentAt: #cameraButtonView
  13. cameraButtonView [interface opening] xrefs
    	| view |
    	view := JunButtonView new.
    	view model: self cameraButton.
    	^view
  14. clickAt: mouse2dPoint [actions] xrefs
     
    	| pickedObject aProjection aPoint minimumDistance targetAtomObject targetSerialNumber aLine |
    	self moleculeObject isNil ifTrue: [^nil].
    	pickedObject := self pickedObjectAt: mouse2dPoint.
    	pickedObject isNil ifTrue: [^nil].
    	aProjection := self displayProjection.
    	aPoint := aProjection translateTo3dPointFromPoint: mouse2dPoint.
    	minimumDistance := nil.
    	targetAtomObject := nil.
    	targetSerialNumber := nil.
    	aLine := (Jun3dLine from: aProjection eyePoint to: aProjection sightPoint) 
    				translatedBy: aPoint - aProjection sightPoint.
    	self atomObjectsAndIndexesDo: 
    			[:atomObject :serialNumber | 
    			| atomicPoint |
    			atomicPoint := atomObject atomicPoint.
    			minimumDistance isNil 
    				ifTrue: 
    					[minimumDistance := aLine distanceFromPoint: atomicPoint.
    					targetAtomObject := atomObject.
    					targetSerialNumber := serialNumber]
    				ifFalse: 
    					[minimumDistance > (aLine distanceFromPoint: atomicPoint) 
    						ifTrue: 
    							[minimumDistance := aLine distanceFromPoint: atomicPoint.
    							targetAtomObject := atomObject.
    							targetSerialNumber := serialNumber]]].
    	targetAtomObject isNil ifTrue: [^nil].
    	^targetAtomObject
  15. cloneViewer [private] xrefs
    	| aViewer |
    	aViewer := super cloneViewer.
    	aViewer moleculeObject: self moleculeObject copy.
    	aViewer messageSymbol: self messageSymbol.
    	^aViewer
  16. computeDisplayInformationInView: aView [private] xrefs
     
    	self computeDisplayOffsetsInView: aView.
    	self computeModifierDisplayInformationInView: aView.
    	self computeSerialNumberDisplayInformationInView: aView
  17. computeDisplayOffsetFor: atomObject [private] xrefs
     
    	atomObject displayOffsetOfSerialNumber 
    		ifNil: [atomObject displayOffsetOfSerialNumber: 0 @ 0]
  18. computeDisplayOffsetFor: atomObject fromAtom: fromAtom toAtom: toAtom inView: aView [private] xrefs
     
    	atomObject displayOffsetOfSerialNumber ifNil: 
    			[atomObject displayOffsetOfSerialNumber: (self 
    						computeOffsetOfSerialNumber: atomObject
    						fromAtom: fromAtom
    						toAtom: toAtom
    						inView: aView)].
    	atomObject displayOffsetOfModifier ifNil: 
    			[atomObject displayOffsetOfModifier: (self 
    						computeOffsetOfModifier: atomObject
    						fromAtom: fromAtom
    						toAtom: toAtom
    						inView: aView)]
  19. computeDisplayOffsetsInView: aView [private] xrefs
     
    	self messageSymbol = #moleculeAsPlane 
    		ifTrue: 
    			[| aSet fromAtom toAtom |
    			aSet := Set new.
    			self atomConnectionsDo: 
    					[:atomConnection | 
    					fromAtom := atomConnection fromAtom.
    					toAtom := atomConnection toAtom.
    					(Array with: fromAtom with: toAtom) do: 
    							[:atomObject | 
    							(aSet includes: atomObject) 
    								ifFalse: 
    									[(self hasModifier: atomObject) 
    										ifTrue: 
    											[self 
    												computeDisplayOffsetFor: atomObject
    												fromAtom: fromAtom
    												toAtom: toAtom
    												inView: aView]
    										ifFalse: [self computeDisplayOffsetFor: atomObject].
    									aSet add: atomObject]]]]
    		ifFalse: 
    			[self 
    				atomObjectsDo: [:atomObject | self computeDisplayOffsetFor: atomObject]]
  20. computeModifierDisplayInformationInView: aView [private] xrefs
     
    	self atomObjectsDo: 
    			[:atomObject | 
    			| aBox aPoint zValue |
    			atomObject displayBooleanOfModifier: false.
    			(self modifierImage: atomObject) ifNotNil: 
    					[:anImage | 
    					aBox := anImage bounds.
    					aPoint := self convertModelPointToView3dPoint: atomObject atomicPoint
    								in: aView bounds.
    					zValue := aPoint z.
    					aPoint := (aPoint x @ aPoint y) rounded.
    					aBox := aBox align: aBox center with: aPoint.
    					aPoint := atomObject displayFocusAtomPointOfModifier.
    					aBox := aBox translatedBy: aPoint.
    					aPoint := atomObject displayOffsetOfModifier.
    					aBox := aBox translatedBy: aPoint.
    					atomObject displayBoxOfModifier: aBox.
    					atomObject displayOrderOfModifier: zValue.
    					atomObject displayBooleanOfModifier: true]]
  21. computeOffsetOfModifier: atomObject fromAtom: fromAtom toAtom: toAtom inView: aView [private] xrefs
     
    	| anImage |
    	anImage := self 
    				modifierImage: atomObject
    				fromAtom: fromAtom
    				toAtom: toAtom
    				inView: aView.
    	anImage yourself.
    	^0 @ 0
  22. computeOffsetOfSerialNumber: atomObject fromAtom: fromAtom toAtom: toAtom inView: aView [private] xrefs
     
    	| anotherAtom fromPoint toPoint offsetPoint |
    	anotherAtom := fromAtom = atomObject ifTrue: [toAtom] ifFalse: [fromAtom].
    	fromPoint := (self convertModelPointToView3dPoint: anotherAtom atomicPoint
    				in: aView bounds) as2dPoint.
    	toPoint := (self convertModelPointToView3dPoint: atomObject atomicPoint
    				in: aView bounds) as2dPoint.
    	toPoint y - fromPoint y >= 0 
    		ifTrue: [offsetPoint := 0 @ self defaultDisplayOffsetLength]
    		ifFalse: 
    			[offsetPoint := 0 @ (self defaultDisplayOffsetLength negated 
    								- (self defaultDisplayOffsetLength // 2))].
    	^offsetPoint
  23. computeSerialNumberDisplayInformationInView: aView [private] xrefs
     
    	self atomObjectsDo: 
    			[:atomObject | 
    			atomObject displayBooleanOfSerialNumber: false.
    			(self serialNumberComposedText: atomObject) ifNotNil: 
    					[:composedText | 
    					| aPoint zValue aBox minBox |
    					aPoint := self convertModelPointToView3dPoint: atomObject atomicPoint
    								in: aView bounds.
    					zValue := aPoint z.
    					aPoint := (aPoint x @ aPoint y) rounded.
    					aBox := composedText bounds.
    					minBox := self defaultMinimumBoxOfSerialNumber.
    					minBox := minBox align: minBox center with: aBox center.
    					aBox area < minBox area ifTrue: [aBox := aBox merge: minBox].
    					aBox := aBox align: aBox center with: aPoint.
    					atomObject displayOffsetOfSerialNumber 
    						ifNil: [atomObject displayOffsetOfSerialNumber: 0 @ 0].
    					aPoint := atomObject displayOffsetOfSerialNumber.
    					aBox := aBox translatedBy: aPoint.
    					atomObject displayBoxOfSerialNumber: aBox.
    					atomObject displayOrderOfSerialNumber: zValue.
    					atomObject displayBooleanOfSerialNumber: true]]
  24. convertModifierStringToImage: aString focusAtomIndex: anIndex [private] xrefs
     
    	| lineGrid subscriptDelta maxHeight focusBox aPixmap graphicsContext aPoint oneImage anImage imageBox focusPoint marginX |
    	lineGrid := (ChemoJunHelvetica character: $A size: 12) height.
    	subscriptDelta := lineGrid 
    				- (ChemoJunHelvetica character: $A size: 9) height.
    	maxHeight := lineGrid.
    	focusBox := nil.
    	self 
    		assert: [aPixmap := Pixmap extent: (lineGrid * aString size * 2) @ lineGrid]
    		do: 
    			[graphicsContext := aPixmap graphicsContext.
    			graphicsContext paint: ColorValue white.
    			graphicsContext displayRectangle: aPixmap bounds.
    			graphicsContext paint: ColorValue black.
    			aPoint := Point zero.
    			aString with: (1 to: aString size)
    				do: 
    					[:aCharacter :characterIndex | 
    					aCharacter isDigit 
    						ifTrue: 
    							[oneImage := ChemoJunHelvetica character: aCharacter size: 9.
    							oneImage displayOn: graphicsContext at: aPoint + (0 @ subscriptDelta)]
    						ifFalse: 
    							[oneImage := ChemoJunHelvetica character: aCharacter size: 12.
    							oneImage displayOn: graphicsContext at: aPoint].
    					characterIndex = anIndex 
    						ifTrue: 
    							[focusBox := oneImage bounds align: oneImage bounds origin with: aPoint].
    					aPoint := aPoint + (oneImage bounds width @ 0)].
    			anImage := aPixmap asImage]
    		ensure: [aPixmap close].
    	marginX := 2.
    	self 
    		assert: [aPixmap := Pixmap extent: (aPoint x + (marginX * 2)) @ maxHeight]
    		do: 
    			[graphicsContext := aPixmap graphicsContext.
    			graphicsContext paint: ColorValue white.
    			graphicsContext displayRectangle: aPixmap bounds.
    			anImage displayOn: graphicsContext at: marginX @ 0.
    			anImage := aPixmap asImage]
    		ensure: [aPixmap close].
    	imageBox := anImage bounds insetBy: marginX @ 0.
    	focusBox isNil 
    		ifTrue: [focusPoint := 0 @ 0]
    		ifFalse: 
    			[focusPoint := (imageBox align: imageBox center with: focusBox center) 
    						origin negated].
    	^Array with: anImage with: focusPoint
  25. defaultBaseName [defaults] xrefs
    	self moleculeObject isNil ifTrue: [^super defaultBaseName].
    	self moleculeObject fileName isNil ifTrue: [^super defaultBaseName].
    	self moleculeObject is2d 
    		ifTrue: 
    			[^(Filename splitExtension: self moleculeObject baseName) first , '_' 
    				, JunSystem defaultBaseName , '.2D'].
    	^self moleculeObject baseName , '_' , JunSystem defaultBaseName
  26. defaultColorOfSerialNumber [defaults] xrefs
    	^ColorValue brightness: 0.05
  27. defaultDisplayOffsetLength [defaults] xrefs
    	^9
  28. defaultEyePoint [defaults] xrefs
    	| box distance |
    	self displayObject isNil ifTrue: [^0 , 0 , 10000].
    	^self defaultProjectionTable at: #eyePoint
    		ifAbsent: 
    			[box := self boundingBox.
    			distance := box origin distance: box corner.
    			distance := distance * 2.
    			^0 , 0 , distance]
  29. defaultMessageSymbol [defaults] xrefs
    	^#moleculeAsStick
  30. defaultMinimumBoxOfSerialNumber [defaults] xrefs
    	^(0 @ 0 extent: 13 @ (self defaultStyleOfSerialNumber lineGrid max: 13)) 
    		rounded
  31. defaultMoleculeObjectClass [defaults] xrefs
    	^self class defaultMoleculeObjectClass
  32. defaultMolFileReaderClass [defaults] xrefs
    	^self class defaultMolFileReaderClass
  33. defaultString [defaults] xrefs
    	^'Molecule' copy
  34. defaultStyleOfSerialNumber [defaults] xrefs
    	^TextAttributes styleNamed: #small ifAbsent: [TextAttributes default]
  35. defaultUpVector [defaults] xrefs
    	^self defaultProjectionTable at: #upVector ifAbsent: [0 , 1 , 0]
  36. defaultWindowLabel [defaults] xrefs
    	^(#chemoJun_Molecular_Viewer >> 'Molecular Viewer') asString
  37. displayInformationInView: aView [displaying] xrefs
     
    	self messageSymbol = #moleculeAsPlane 
    		ifTrue: [self displayModifierInView: aView].
    	self displaySerialInView: aView
  38. displayModifierInView: aView [displaying] xrefs
     
    	| aGraphicsContext aCollection |
    	aGraphicsContext := aView graphicsContext.
    	aCollection := SortedCollection new: self numberOfAtoms.
    	aCollection sortBlock: [:n1 :n2 | n1 >= n2].
    	self atomObjectsDo: 
    			[:atomObject | 
    			atomObject displayBooleanOfModifier 
    				ifTrue: [aCollection add: atomObject displayOrderOfModifier -> atomObject]].
    	aCollection do: 
    			[:anAssociation | 
    			| atomObject anImage aBox |
    			atomObject := anAssociation value.
    			anImage := atomObject displayImageOfModifier.
    			aBox := atomObject displayBoxOfModifier.
    			self 
    				displayImage: anImage
    				on: aGraphicsContext
    				at: aBox origin]
  39. displayObject [accessing] xrefs
    	| theMolecule |
    	(displayObject isNil and: [(theMolecule := self moleculeObject) notNil]) 
    		ifTrue: 
    			[Cursor wait showWhile: 
    					[ObjectMemory globalGarbageCollect.
    					self displayObject: (theMolecule perform: self messageSymbol).
    					self displayObject boundingBox.
    					self informationHolder value: self informationString]].
    	^displayObject
  40. displaySerialInView: aView [displaying] xrefs
     
    	| aGraphicsContext aCollection |
    	self exceptIndex ifTrue: [^nil].
    	aGraphicsContext := aView graphicsContext.
    	aCollection := SortedCollection new: self numberOfAtoms.
    	aCollection sortBlock: [:n1 :n2 | n1 >= n2].
    	self atomObjectsDo: 
    			[:atomObject | 
    			atomObject displayBooleanOfSerialNumber 
    				ifTrue: [aCollection add: atomObject displayOrderOfSerialNumber -> atomObject]].
    	aCollection do: 
    			[:anAssociation | 
    			| atomObject aComposedText aBox |
    			atomObject := anAssociation value.
    			aComposedText := atomObject displayComposedTextOfSerialNumber.
    			aBox := atomObject displayBoxOfSerialNumber.
    			self 
    				displayComposedText: aComposedText
    				on: aGraphicsContext
    				at: aBox center
    				textColor: self defaultColorOfSerialNumber
    				vergeColor: (ColorValue brightness: 0.95)
    				alignmentSymbol: #center]
  41. displaySuperimposeInView: aView [displaying] xrefs
     
    	aView isNil ifTrue: [^nil].
    	aView isOpen ifFalse: [^nil].
    	self moleculeObject isNil ifTrue: [^nil].
    	self computeDisplayInformationInView: aView.
    	self displayInformationInView: aView
  42. exceptHydrogen [accessing] xrefs
    	^exceptHydrogen = true
  43. exceptHydrogen: aBoolean [accessing] xrefs
     
    	| oldBoolean |
    	JunControlUtility 
    		assert: [oldBoolean := self exceptHydrogen]
    		do: 
    			[exceptHydrogen := aBoolean = true.
    			self moleculeObject notNil 
    				ifTrue: [self moleculeObject exceptHydrogen: exceptHydrogen]]
    		ensure: [oldBoolean = self exceptHydrogen ifFalse: [self flushDisplayObject]]
  44. exceptIndex [accessing] xrefs
    	^exceptIndex = true
  45. exceptIndex: aBoolean [accessing] xrefs
     
    	exceptIndex := aBoolean = true
  46. fileName [accessing] xrefs
    	| aFilename |
    	self moleculeObject isNil ifTrue: [^nil].
    	aFilename := self moleculeObject fileName asFilename.
    	^aFilename
  47. flushDisplayAttributes [flushing] xrefs
    	self atomObjectsDo: 
    			[:atomObject | 
    			| displayKeys |
    			displayKeys := atomObject attributeTable keys 
    						select: [:displayKey | JunStringUtility stringMatch: displayKey asString and: 'display*'].
    			displayKeys 
    				do: [:displayKey | atomObject attributeTable removeKey: displayKey]]
  48. flushDisplayObject [flushing] xrefs
    	super flushDisplayObject.
    	self flushDisplayAttributes
  49. flushModifierAttributes [flushing] xrefs
    	self atomObjectsDo: 
    			[:atomObject | 
    			| displayKeys |
    			displayKeys := atomObject attributeTable keys select: 
    							[:displayKey | 
    							JunStringUtility stringMatch: displayKey asString and: 'display*Modifier'].
    			displayKeys 
    				do: [:displayKey | atomObject attributeTable removeKey: displayKey]]
  50. flushSerialNumberAttributes [flushing] xrefs
    	self atomObjectsDo: 
    			[:atomObject | 
    			| displayKeys |
    			displayKeys := atomObject attributeTable keys select: 
    							[:displayKey | 
    							JunStringUtility stringMatch: displayKey asString
    								and: 'display*SerialNumber'].
    			displayKeys 
    				do: [:displayKey | atomObject attributeTable removeKey: displayKey]]
  51. focus: aRectangle1 to: aRectangle2 [manipulating] xrefs
     
    	| originalRectangle newRectangle aProjection originalCenter newCenter originalTop originalBottom originalLeft originalRight originalHeight originalWidth newTop newBottom newLeft newRight newHeight newWidth newViewHeight newViewWidth tmpViewHeight newZoomHeight aLine minimumDistance aPoint targetPoint |
    	InputState default shiftDown 
    		ifTrue: 
    			[originalRectangle := aRectangle2.
    			newRectangle := aRectangle1]
    		ifFalse: 
    			[originalRectangle := aRectangle1.
    			newRectangle := aRectangle2].
    	self displayObject isNil ifTrue: [^self].
    	aProjection := self displayProjection.
    	originalCenter := aProjection 
    				translateTo3dPointFromPoint: (originalRectangle origin 
    						+ originalRectangle corner) / 2.0d.
    	newCenter := aProjection 
    				translateTo3dPointFromPoint: (newRectangle origin + newRectangle corner) 
    						/ 2.0d.
    	aProjection 
    		sightPoint: aProjection sightPoint + (newCenter - originalCenter).
    	originalTop := aProjection 
    				translateTo3dPointFromPoint: 0 , originalRectangle origin y.
    	originalBottom := aProjection 
    				translateTo3dPointFromPoint: 0 , originalRectangle corner y.
    	originalLeft := aProjection 
    				translateTo3dPointFromPoint: originalRectangle origin x , 0.
    	originalRight := aProjection 
    				translateTo3dPointFromPoint: originalRectangle corner x , 0.
    	originalHeight := (originalTop - originalBottom) length.
    	originalWidth := (originalLeft - originalRight) length.
    	newTop := aProjection 
    				translateTo3dPointFromPoint: 0 , newRectangle origin y.
    	newBottom := aProjection 
    				translateTo3dPointFromPoint: 0 , newRectangle corner y.
    	newLeft := aProjection 
    				translateTo3dPointFromPoint: newRectangle origin x , 0.
    	newRight := aProjection 
    				translateTo3dPointFromPoint: newRectangle corner x , 0.
    	newHeight := (newTop - newBottom) length.
    	newWidth := (newLeft - newRight) length.
    	newViewHeight := aProjection regularHeight * newHeight / originalHeight.
    	newViewWidth := newViewHeight * newWidth / newHeight.
    	originalWidth / originalHeight * newViewHeight < newViewWidth 
    		ifTrue: 
    			[tmpViewHeight := originalWidth / originalHeight 
    						* (newViewHeight / newViewWidth) * newViewHeight.
    			newZoomHeight := newViewHeight * (newViewHeight / tmpViewHeight)]
    		ifFalse: [newZoomHeight := newViewHeight].
    	(originalHeight * 0.01d < newHeight 
    		and: [newHeight * 0.01d < originalHeight]) 
    			ifTrue: [aProjection zoomHeight: newZoomHeight].
    	self moleculeObject notNil 
    		ifTrue: 
    			[minimumDistance := nil.
    			targetPoint := nil.
    			aLine := Jun3dLine from: aProjection eyePoint to: aProjection sightPoint.
    			self atomObjectsDo: 
    					[:each | 
    					aPoint := each atomicPoint.
    					minimumDistance isNil 
    						ifTrue: 
    							[minimumDistance := aLine distanceFromPoint: aPoint.
    							targetPoint := aPoint]
    						ifFalse: 
    							[minimumDistance > (aLine distanceFromPoint: aPoint) 
    								ifTrue: 
    									[minimumDistance := aLine distanceFromPoint: aPoint.
    									targetPoint := aPoint]]].
    			targetPoint notNil ifTrue: [aProjection sightPoint: targetPoint]].
    	self displayProjection: aProjection.
    	self changed: #projection
  52. grab: deltaPoint [manipulating] xrefs
     
    	self flushModifierAttributes.
    	super grab: deltaPoint
  53. grab: from2dPoint xy: to2dPoint [manipulating] xrefs
     
    	self flushModifierAttributes.
    	super grab: from2dPoint xy: to2dPoint
  54. hasModifier: atomObject [testing] xrefs
     
    	(self moleculeObject isMethyl: atomObject) ifTrue: [^true].
    	(self moleculeObject isHydroxyl: atomObject) ifTrue: [^true].
    	^atomObject isCarbon not and: 
    			[atomObject isHydrogen not 
    				or: [atomObject isHydrogen and: [self exceptHydrogen not]]]
  55. highResolution [menu messages] xrefs
    	self moleculeObject isNil ifTrue: [^super highResolution].
    	self moleculeObject atomResolution = #high ifTrue: [^nil].
    	self moleculeObject atomResolution: #high.
    	self flushDisplayObject.
    	self changed: #object.
    	self updateViewMenuIndication
  56. informationString [accessing] xrefs
    	| aStream aString |
    	self moleculeObject isNil ifTrue: [^String new].
    	self 
    		assert: [aStream := String new writeStream]
    		do: 
    			[aStream 
    				nextPutAll: (#chemoJun_Molecular_Information_ >> 'Molecular Information:') 
    						asString.
    			aStream cr.
    			aStream nextPutAll: self moleculeObject informationString.
    			aStream tab.
    			aStream 
    				nextPutAll: (#chemoJun_number_of_primitives__ >> 'number of primitives: ') 
    						asString.
    			aStream nextPutAll: self numberOfPrimitives printString.
    			aStream cr]
    		ensure: 
    			[aString := aStream contents.
    			aStream close].
    	^aString
  57. initialize [initialize-release] xrefs
    	super initialize.
    	moleculeObject := nil.
    	messageSymbol := nil.
    	exceptHydrogen := ChemoJunMoleculeObject defaultExceptHydrogen.
    	exceptIndex := self class defaultExceptSerialNumber.
    	indexExpression := nil.
    	indexExpressionBlock := nil.
    	cameraButton := nil.
    	self 
    		superimposeBlock: [:model :view :controller | self displaySuperimposeInView: view]
  58. is2d [testing] xrefs
    	^self moleculeObject ifNil: [super is2d] ifNotNil: [:it | it is2d]
  59. is3d [testing] xrefs
    	^self moleculeObject ifNil: [super is3d] ifNotNil: [:it | it is3d]
  60. isMoleculeViewer [testing] xrefs
    	^true
  61. lowResolution [menu messages] xrefs
    	self moleculeObject isNil ifTrue: [^super lowResolution].
    	self moleculeObject atomResolution = #low ifTrue: [^nil].
    	self moleculeObject atomResolution: #low.
    	self flushDisplayObject.
    	self changed: #object.
    	self updateViewMenuIndication
  62. mediumResolution [menu messages] xrefs
    	self moleculeObject isNil ifTrue: [^super mediumResolution].
    	self moleculeObject atomResolution = #medium ifTrue: [^nil].
    	self moleculeObject atomResolution: #medium.
    	self flushDisplayObject.
    	self changed: #object.
    	self updateViewMenuIndication
  63. messageSymbol [accessing] xrefs
    	messageSymbol isNil ifTrue: [messageSymbol := self defaultMessageSymbol].
    	^messageSymbol
  64. messageSymbol: aSymbol [accessing] xrefs
     
    	((#(#moleculeAsStick #moleculeAsBallAndStick #moleculeAsSpaceFill #moleculeAsStickAndSpaceFill #moleculeAsPlane) 
    		includes: aSymbol) and: [messageSymbol ~~ aSymbol]) 
    		ifTrue: 
    			[messageSymbol := aSymbol.
    			self flushDisplayObject]
  65. modifierImage: atomObject [accessing modifiers] xrefs
     
    	^atomObject displayImageOfModifier
  66. modifierImage: atomObject fromAtom: fromAtom toAtom: toAtom inView: aView [accessing modifiers] xrefs
     
    	(self hasModifier: atomObject) 
    		ifTrue: 
    			[atomObject displayImageOfModifier ifNil: 
    					[| fromPoint toPoint aPlane normalPresentation anAssociation anArray anImage aPoint |
    					atomObject = toAtom 
    						ifTrue: 
    							[fromPoint := fromAtom atomicPoint.
    							toPoint := toAtom atomicPoint]
    						ifFalse: 
    							[fromPoint := toAtom atomicPoint.
    							toPoint := fromAtom atomicPoint].
    					aPlane := self sightPoint plane: self sightPoint + self upVector
    								and: self eyePoint.
    					aPlane := aPlane translatedBy: fromPoint - self sightPoint.
    					aPlane ifNil: [normalPresentation := true]
    						ifNotNil: [:plane | normalPresentation := (plane whichSide: toPoint) >= 0].
    					anAssociation := self moleculeObject modifierAssociation: atomObject
    								normalPresentation: normalPresentation.
    					anArray := self convertModifierStringToImage: anAssociation key
    								focusAtomIndex: anAssociation value.
    					anImage := anArray first.
    					aPoint := anArray last.
    					atomObject displayFocusAtomPointOfModifier: aPoint.
    					atomObject displayImageOfModifier: anImage].
    			^atomObject displayImageOfModifier].
    	^nil
  67. moleculeFromReader: aReader [menu messages] xrefs
     
    	| chemMolecule cursorAnimator |
    	aReader isNil ifTrue: [^nil].
    	chemMolecule := self defaultMoleculeObjectClass fromReader: aReader.
    	cursorAnimator := JunCursorAnimator clockCursors.
    	cursorAnimator tick: 1000.
    	cursorAnimator showWhile: 
    			[self moleculeObject isNil 
    				ifTrue: [chemMolecule atomResolution: self defaultResolution]
    				ifFalse: [chemMolecule atomResolution: self moleculeObject atomResolution].
    			chemMolecule exceptHydrogen: self exceptHydrogen.
    			self moleculeObject: chemMolecule.
    			self setWindowLabel.
    			self resetView.
    			self updateMenuIndication]
  68. moleculeObject [accessing] xrefs
    	^moleculeObject
  69. moleculeObject: aMolecule [accessing] xrefs
     
    	moleculeObject := aMolecule.
    	aMolecule is2d ifTrue: [self messageSymbol: #moleculeAsPlane].
    	(aMolecule is3d and: [self messageSymbol = #moleculeAsPlane]) 
    		ifTrue: [self messageSymbol: self defaultMessageSymbol].
    	self flushDisplayObject
  70. moleculeText [accessing] xrefs
    	^ValueHolder with: 'xyz'
  71. numberOfAtoms [accessing] xrefs
    	^self moleculeObject ifNil: [0] ifNotNil: [:it | it numberOfAtoms]
  72. openMolecule [menu messages] xrefs
    	| aReader |
    	aReader := self defaultMolFileReaderClass request.
    	aReader isNil ifTrue: [^nil].
    	^self moleculeFromReader: aReader
  73. postBuildWith: aBuilder [interface opening] xrefs
     
    	super postBuildWith: aBuilder.
    	self beInvisibleCameraButton
  74. saveAsFile [menu messages] xrefs
    	| aWriter |
    	self moleculeObject isNil ifTrue: [^nil].
    	aWriter := ChemoJunMolFileWriter 
    				requestInitialFileName: self defaultBaseName 
    						, self moleculeObject extension.
    	aWriter ifNil: [^nil].
    	self saveFileTo: aWriter fileName.
    	self moleculeObject fileName: aWriter fileName.
    	self setWindowLabel
  75. saveFileTo: moleculeFilename [menu messages] xrefs
     
    	| aWriter |
    	aWriter := ChemoJunMolFileWriter fileName: moleculeFilename.
    	aWriter isNil ifTrue: [^nil].
    	aWriter moleculeObject: self moleculeObject.
    	aWriter write
  76. serialNumberComposedText: atomObject [accessing] xrefs
     
    	| aBlock numberOfArguments serialNumber argumentArray |
    	aBlock := self indexExpressionBlock.
    	numberOfArguments := aBlock numArgs.
    	serialNumber := atomObject serialNumber.
    	argumentArray := (Array 
    				with: serialNumber
    				with: atomObject atomicSymbol
    				with: atomObject atomicPoint
    				with: atomObject) copyFrom: 1 to: numberOfArguments.
    	((aBlock valueWithArguments: argumentArray) = true 
    		and: [(atomObject isHydrogen and: [self exceptHydrogen]) not]) 
    			ifTrue: 
    				[atomObject displayComposedTextOfSerialNumber ifNil: 
    						[| composedText |
    						composedText := ComposedText withText: serialNumber printString asText
    									style: self defaultStyleOfSerialNumber.
    						atomObject displayComposedTextOfSerialNumber: composedText].
    				^atomObject displayComposedTextOfSerialNumber].
    	^nil
  77. setIndexExpression: aString setIndexExpressionBlock: aBlock [private] xrefs
     
    	indexExpression := aString.
    	indexExpressionBlock := aBlock
  78. setWindowLabel [interface opening] xrefs
    	| aWindow aFilename aString |
    	aWindow := self getWindow.
    	aWindow isNil ifTrue: [^nil].
    	aWindow model = self ifFalse: [^nil].
    	self moleculeObject isNil 
    		ifTrue: [^aWindow label: self defaultWindowLabel].
    	self moleculeObject fileName isNil 
    		ifTrue: [^aWindow label: self defaultWindowLabel].
    	aFilename := self moleculeObject fileName asFilename.
    	aString := (Filename splitPath: aFilename asString) last.
    	aWindow label: self defaultWindowLabel , ' [' , aString , ']'
  79. showMoleculeAsBallAndStick [menu messages] xrefs
    	self moleculeObject isNil 
    		ifTrue: 
    			[self messageSymbol: #moleculeAsBallAndStick.
    			self updateViewMenuIndication.
    			^nil].
    	self messageSymbol = #moleculeAsBallAndStick ifTrue: [^nil].
    	self messageSymbol: #moleculeAsBallAndStick.
    	self changed: #object.
    	self updateViewMenuIndication
  80. showMoleculeAsPlane [menu messages] xrefs
    	self moleculeObject isNil 
    		ifTrue: 
    			[self messageSymbol: #moleculeAsPlane.
    			self updateViewMenuIndication.
    			^nil].
    	self messageSymbol = #moleculeAsPlane ifTrue: [^nil].
    	self messageSymbol: #moleculeAsPlane.
    	self changed: #object.
    	self updateViewMenuIndication
  81. showMoleculeAsSpaceFill [menu messages] xrefs
    	self moleculeObject isNil 
    		ifTrue: 
    			[self messageSymbol: #moleculeAsSpaceFill.
    			self exceptIndex: true.
    			self updateViewMenuIndication.
    			^nil].
    	self messageSymbol = #moleculeAsSpaceFill ifTrue: [^nil].
    	self messageSymbol: #moleculeAsSpaceFill.
    	self exceptIndex: true.
    	self changed: #object.
    	self updateViewMenuIndication
  82. showMoleculeAsStick [menu messages] xrefs
    	self moleculeObject isNil
    		ifTrue: 
    			[self messageSymbol: #moleculeAsStick.
    			self updateViewMenuIndication.
    			^nil].
    	self messageSymbol = #moleculeAsStick ifTrue: [^nil].
    	self messageSymbol: #moleculeAsStick.
    	self changed: #object.
    	self updateViewMenuIndication
  83. showMoleculeAsStickAndSpaceFill [menu messages] xrefs
    	self moleculeObject isNil
    		ifTrue: 
    			[self messageSymbol: #moleculeAsStickAndSpaceFill.
    			self updateViewMenuIndication.
    			^nil].
    	self messageSymbol = #moleculeAsStickAndSpaceFill ifTrue: [^nil].
    	self messageSymbol: #moleculeAsStickAndSpaceFill.
    	self changed: #object.
    	self updateViewMenuIndication
  84. toggleHydrogen [menu messages] xrefs
    	self messageSymbol = #moleculeAsSpaceFill ifTrue: [^nil].
    	self exceptHydrogen: self exceptHydrogen not.
    	self flushDisplayObject.
    	self changed: #object.
    	self updateViewMenuIndication
  85. toggleIndex [menu messages] xrefs
    	self messageSymbol = #moleculeAsSpaceFill ifTrue: [^nil].
    	self exceptIndex: self exceptIndex not.
    	self changed: #object.
    	self updateViewMenuIndication
  86. updateMiscMenuIndication [menu accessing] xrefs
    	| menuItem aMenu |
    	super updateMiscMenuIndication.
    	menuItem := self menuItemLabeled: 'Misc' inMenu: self menuBar.
    	menuItem isNil ifTrue: [^self].
    	aMenu := menuItem submenu.
    	aMenu notNil 
    		ifTrue: 
    			[menuItem := aMenu menuItemWithValue: #showInformation ifNone: [nil].
    			menuItem notNil 
    				ifTrue: 
    					[self moleculeObject isNil 
    						ifTrue: [menuItem disable]
    						ifFalse: [menuItem enable]]]
  87. updateStringHolder: aPoint [updating] xrefs
     
    	| x y z |
    	aPoint isNil ifTrue: [^self stringHolder value: self defaultString].
    	x := aPoint x asFloat.
    	y := aPoint y asFloat.
    	z := aPoint z asFloat.
    	self stringHolder 
    		value: x printString , ', ' , y printString , ', ' , z printString
  88. updateViewMenuIndication [menu accessing] xrefs
    	| menuItem aMenu |
    	super updateViewMenuIndication.
    	menuItem := self menuItemLabeled: 'View' inMenu: self menuBar.
    	menuItem isNil ifTrue: [^self].
    	aMenu := menuItem submenu.
    	aMenu notNil 
    		ifTrue: 
    			[menuItem := aMenu menuItemWithValue: #showMoleculeAsPlane ifNone: [nil].
    			menuItem notNil 
    				ifTrue: 
    					[menuItem enable.
    					self messageSymbol = #moleculeAsPlane 
    						ifTrue: [menuItem beOn]
    						ifFalse: [menuItem beOff]].
    			menuItem := aMenu menuItemWithValue: #showMoleculeAsStick ifNone: [nil].
    			menuItem notNil 
    				ifTrue: 
    					[menuItem enable.
    					self messageSymbol = #moleculeAsStick 
    						ifTrue: [menuItem beOn]
    						ifFalse: [menuItem beOff]].
    			menuItem := aMenu menuItemWithValue: #showMoleculeAsBallAndStick
    						ifNone: [nil].
    			menuItem notNil 
    				ifTrue: 
    					[menuItem enable.
    					self messageSymbol = #moleculeAsBallAndStick 
    						ifTrue: [menuItem beOn]
    						ifFalse: [menuItem beOff]].
    			menuItem := aMenu menuItemWithValue: #showMoleculeAsSpaceFill ifNone: [nil].
    			menuItem notNil 
    				ifTrue: 
    					[menuItem enable.
    					self messageSymbol = #moleculeAsSpaceFill 
    						ifTrue: [menuItem beOn]
    						ifFalse: [menuItem beOff]].
    			menuItem := aMenu menuItemWithValue: #showMoleculeAsStickAndSpaceFill
    						ifNone: [nil].
    			menuItem notNil 
    				ifTrue: 
    					[menuItem enable.
    					self messageSymbol = #moleculeAsStickAndSpaceFill 
    						ifTrue: [menuItem beOn]
    						ifFalse: [menuItem beOff]].
    			menuItem := aMenu menuItemWithValue: #toggleHydrogen ifNone: [nil].
    			menuItem notNil 
    				ifTrue: 
    					[menuItem enable.
    					self exceptHydrogen ifTrue: [menuItem beOff] ifFalse: [menuItem beOn].
    					self messageSymbol = #moleculeAsSpaceFill ifTrue: [menuItem disable]].
    			menuItem := aMenu menuItemWithValue: #toggleIndex ifNone: [nil].
    			menuItem notNil 
    				ifTrue: 
    					[menuItem enable.
    					self exceptIndex ifTrue: [menuItem beOff] ifFalse: [menuItem beOn].
    					self messageSymbol = #moleculeAsSpaceFill ifTrue: [menuItem disable]].
    			menuItem := aMenu menuItemWithValue: #settingIndex ifNone: [nil].
    			menuItem notNil 
    				ifTrue: 
    					[self exceptIndex ifTrue: [menuItem disable] ifFalse: [menuItem enable]].
    			menuItem := aMenu menuItemWithValue: #lowResolution ifNone: [nil].
    			menuItem notNil 
    				ifTrue: 
    					[self messageSymbol = #moleculeAsPlane 
    						ifTrue: [menuItem disable]
    						ifFalse: 
    							[menuItem enable.
    							self moleculeObject isNil 
    								ifTrue: 
    									[self defaultResolution = #low 
    										ifTrue: [menuItem beOn]
    										ifFalse: [menuItem beOff]]
    								ifFalse: 
    									[self moleculeObject atomResolution = #low 
    										ifTrue: [menuItem beOn]
    										ifFalse: [menuItem beOff]]]].
    			menuItem := aMenu menuItemWithValue: #mediumResolution ifNone: [nil].
    			menuItem notNil 
    				ifTrue: 
    					[self messageSymbol = #moleculeAsPlane 
    						ifTrue: [menuItem disable]
    						ifFalse: 
    							[menuItem enable.
    							self moleculeObject isNil 
    								ifTrue: 
    									[self defaultResolution = #medium 
    										ifTrue: [menuItem beOn]
    										ifFalse: [menuItem beOff]]
    								ifFalse: 
    									[self moleculeObject atomResolution = #medium 
    										ifTrue: [menuItem beOn]
    										ifFalse: [menuItem beOff]]]].
    			menuItem := aMenu menuItemWithValue: #highResolution ifNone: [nil].
    			menuItem notNil 
    				ifTrue: 
    					[self messageSymbol = #moleculeAsPlane 
    						ifTrue: [menuItem disable]
    						ifFalse: 
    							[menuItem enable.
    							self moleculeObject isNil 
    								ifTrue: 
    									[self defaultResolution = #high 
    										ifTrue: [menuItem beOn]
    										ifFalse: [menuItem beOff]]
    								ifFalse: 
    									[self moleculeObject atomResolution = #high 
    										ifTrue: [menuItem beOn]
    										ifFalse: [menuItem beOff]]]].
    			menuItem := aMenu menuItemWithValue: #resetView ifNone: [nil].
    			menuItem notNil 
    				ifTrue: 
    					[self moleculeObject isNil 
    						ifTrue: [menuItem disable]
    						ifFalse: [menuItem enable]]]
  89. wheelActionInTopCenterBox: wheelUpBoolean [wheel actions] xrefs
     
    	self flushModifierAttributes.
    	super wheelActionInTopCenterBox: wheelUpBoolean

class methods:

  1. copyright [copyright] xrefs
    	^'ChemoJun050 (2006/08/08) Copyright 2002-2006 National Institute of Informatics, Research Organization of Information and Systems.'
  2. defaultExceptSerialNumber [defaults] xrefs
    	^true
  3. defaultMoleculeObjectClass [defaults] xrefs
    	^ChemoJunMoleculeObject
  4. defaultMolFileReaderClass [defaults] xrefs
    	^ChemoJunMolFileReader
  5. example1 [examples] xrefs
    	"ChemoJunMoleculeViewer example1."
    
    	| aViewer |
    	aViewer := ChemoJunMoleculeViewer new.
    	aViewer open.
    	^aViewer
  6. example2 [examples] xrefs
    	"ChemoJunMoleculeViewer example2."
    
    	| fileName originalMolecule originalViewer |
    	fileName := './CastData/ABC-88-52-211-1.2D.mol'.
    	originalMolecule := ChemoJunMoleculeObject 
    				fileName: (JunUniFileName named: fileName).
    	originalViewer := ChemoJunMoleculeViewer moleculeObject: originalMolecule.
    	originalViewer messageSymbol: #moleculeAsPlane.
    	originalViewer openIn: (100 @ 200 extent: 600 @ 300).
    	^originalViewer
  7. example3 [examples] xrefs
    	"ChemoJunMoleculeViewer example3."
    
    	| fileName originalMolecule originalViewer modifiedMolecule modifiedViewer aCollection |
    	fileName := './ChemoJunSampleData/fullerene_expanded.mol'.
    	originalMolecule := ChemoJunMoleculeObject 
    				fileName: (JunUniFileName named: fileName).
    	originalViewer := ChemoJunMoleculeViewer moleculeObject: originalMolecule.
    	originalViewer showMoleculeAsPlane.
    	originalViewer openIn: (100 @ 200 extent: 600 @ 300).
    	modifiedMolecule := ChemoJunMoleculeObject 
    				fileName: (JunUniFileName named: fileName).
    	modifiedMolecule 
    		changeColor: ColorValue red
    		serialNumbers: #(8 9)
    		nestLevel: 0.
    	modifiedViewer := ChemoJunMoleculeViewer moleculeObject: modifiedMolecule.
    	modifiedViewer showMoleculeAsPlane.
    	modifiedViewer openIn: (100 @ 550 extent: 600 @ 300).
    	aCollection := Array with: originalViewer with: modifiedViewer.
    	aCollection do: [:each | each closeTogether: aCollection].
    	^aCollection
  8. example4 [examples] xrefs
    	"ChemoJunMoleculeViewer example4."
    
    	| fileName originalMolecule originalViewer modifiedMolecule modifiedViewer aCollection |
    	fileName := './ChemoJunSampleData/fullerene.mol'.
    	originalMolecule := ChemoJunMoleculeObject 
    				fileName: (JunUniFileName named: fileName).
    	originalViewer := ChemoJunMoleculeViewer moleculeObject: originalMolecule.
    	originalViewer showMoleculeAsBallAndStick.
    	originalViewer openIn: (100 @ 200 extent: 600 @ 300).
    	modifiedMolecule := ChemoJunMoleculeObject 
    				fileName: (JunUniFileName named: fileName).
    	modifiedMolecule 
    		changeColor: ColorValue red
    		serialNumbers: #(8 9)
    		nestLevel: 0.
    	modifiedViewer := ChemoJunMoleculeViewer moleculeObject: modifiedMolecule.
    	modifiedViewer showMoleculeAsBallAndStick.
    	modifiedViewer openIn: (100 @ 550 extent: 600 @ 300).
    	aCollection := Array with: originalViewer with: modifiedViewer.
    	aCollection do: [:each | each closeTogether: aCollection].
    	^aCollection
  9. example5 [examples] xrefs
    	"ChemoJunMoleculeViewer example5."
    
    	| fileName originalMolecule originalViewer modifiedMolecule modifiedViewer aCollection |
    	fileName := './ChemoJunSampleData/fullerene_expanded.mol'.
    	originalMolecule := ChemoJunMoleculeObject 
    				fileName: (JunUniFileName named: fileName).
    	originalViewer := ChemoJunMoleculeViewer moleculeObject: originalMolecule.
    	originalViewer showMoleculeAsPlane.
    	originalViewer openIn: (100 @ 200 extent: 600 @ 300).
    	modifiedMolecule := ChemoJunMoleculeObject 
    				fileName: (JunUniFileName named: fileName).
    	modifiedMolecule 
    		changeColor: ColorValue red
    		serialNumberPairs: #(#(8 4) #(7 17))
    		nestLevel: 1.
    	modifiedViewer := ChemoJunMoleculeViewer moleculeObject: modifiedMolecule.
    	modifiedViewer showMoleculeAsPlane.
    	modifiedViewer openIn: (100 @ 550 extent: 600 @ 300).
    	aCollection := Array with: originalViewer with: modifiedViewer.
    	aCollection do: [:each | each closeTogether: aCollection].
    	^aCollection
  10. example6 [examples] xrefs
    	"ChemoJunMoleculeViewer example6."
    
    	| fileName originalMolecule originalViewer modifiedMolecule modifiedViewer aCollection |
    	fileName := './ChemoJunSampleData/fullerene.mol'.
    	originalMolecule := ChemoJunMoleculeObject 
    				fileName: (JunUniFileName named: fileName).
    	originalViewer := ChemoJunMoleculeViewer moleculeObject: originalMolecule.
    	originalViewer showMoleculeAsBallAndStick.
    	originalViewer openIn: (100 @ 200 extent: 600 @ 300).
    	modifiedMolecule := ChemoJunMoleculeObject 
    				fileName: (JunUniFileName named: fileName).
    	modifiedMolecule 
    		changeColor: ColorValue red
    		serialNumberPairs: #(#(22 35) #(34 37))
    		nestLevel: 0.
    	modifiedViewer := ChemoJunMoleculeViewer moleculeObject: modifiedMolecule.
    	modifiedViewer showMoleculeAsBallAndStick.
    	modifiedViewer openIn: (100 @ 550 extent: 600 @ 300).
    	aCollection := Array with: originalViewer with: modifiedViewer.
    	aCollection do: [:each | each closeTogether: aCollection].
    	^aCollection
  11. fileName: moleculeFilename [instance creation] xrefs
     
    	^self 
    		moleculeObject: (self defaultMoleculeObjectClass fileName: moleculeFilename)
  12. menuBar [resources] xrefs
    	"Tools.MenuEditor new openOnClass: self andSelector: #menuBar"
    
    	<resource: #menu>
    	^#(#{UI.Menu} #(
    			#(#{UI.MenuItem} 
    				#rawLabel: 
    				#(#{Kernel.UserMessage} 
    					#key: #jun_File 
    					#defaultString: 'File' ) 
    				#submenu: #(#{UI.Menu} #(
    						#(#{UI.MenuItem} 
    							#rawLabel: 
    							#(#{Kernel.UserMessage} 
    								#key: #jun_New 
    								#defaultString: 'New' ) 
    							#value: #newModel ) 
    						#(#{UI.MenuItem} 
    							#rawLabel: 
    							#(#{Kernel.UserMessage} 
    								#key: #jun_Open 
    								#defaultString: 'Open' ) 
    							#value: #openMolecule ) 
    						#(#{UI.MenuItem} 
    							#rawLabel: 
    							#(#{Kernel.UserMessage} 
    								#key: #chemoJun_Save_as 
    								#defaultString: 'Save as' ) 
    							#value: #saveAsFile ) 
    						#(#{UI.MenuItem} 
    							#rawLabel: 
    							#(#{Kernel.UserMessage} 
    								#key: #chemoJun_Save_as_Image 
    								#defaultString: 'Save as Image' ) 
    							#value: #saveAsImage ) 
    						#(#{UI.MenuItem} 
    							#rawLabel: 
    							#(#{Kernel.UserMessage} 
    								#key: #jun_Quit 
    								#defaultString: 'Quit' ) 
    							#value: #quitDoing ) ) #(2 2 1 ) nil ) ) 
    			#(#{UI.MenuItem} 
    				#rawLabel: 
    				#(#{Kernel.UserMessage} 
    					#key: #chemoJun_View 
    					#defaultString: 'View' ) 
    				#submenu: #(#{UI.Menu} #(
    						#(#{UI.MenuItem} 
    							#rawLabel: 
    							#(#{Kernel.UserMessage} 
    								#key: #chemoJun_2D 
    								#defaultString: '2D' ) 
    							#value: #showMoleculeAsPlane ) 
    						#(#{UI.MenuItem} 
    							#rawLabel: 
    							#(#{Kernel.UserMessage} 
    								#key: #chemoJun_Sticks 
    								#defaultString: 'Sticks' ) 
    							#value: #showMoleculeAsStick ) 
    						#(#{UI.MenuItem} 
    							#rawLabel: 
    							#(#{Kernel.UserMessage} 
    								#key: #chemoJun_Ball_and_Stick 
    								#defaultString: 'Ball && Stick' ) 
    							#value: #showMoleculeAsBallAndStick ) 
    						#(#{UI.MenuItem} 
    							#rawLabel: 
    							#(#{Kernel.UserMessage} 
    								#key: #chemoJun_Space_Filling 
    								#defaultString: 'Space Filling' ) 
    							#value: #showMoleculeAsSpaceFill ) 
    						#(#{UI.MenuItem} 
    							#rawLabel: 
    							#(#{Kernel.UserMessage} 
    								#key: #chemoJun_Stick_and_Space_Filling 
    								#defaultString: 'Stick && Space Filling' ) 
    							#value: #showMoleculeAsStickAndSpaceFill ) 
    						#(#{UI.MenuItem} 
    							#rawLabel: 
    							#(#{Kernel.UserMessage} 
    								#key: #chemoJun_Show_Hydrogens 
    								#defaultString: 'Hydrogens' ) 
    							#value: #toggleHydrogen ) 
    						#(#{UI.MenuItem} 
    							#rawLabel: 
    							#(#{Kernel.UserMessage} 
    								#key: #chemoJun_Show_Serial_Nos__of_Atoms 
    								#defaultString: 'Serial Nos. of Atoms' ) 
    							#value: #toggleIndex ) 
    						#(#{UI.MenuItem} 
    							#rawLabel: 
    							#(#{Kernel.UserMessage} 
    								#key: #chemoJun_Setting_Serial_Nos_ 
    								#defaultString: 'Setting Serial Nos.' ) 
    							#value: #settingIndex ) 
    						#(#{UI.MenuItem} 
    							#rawLabel: 
    							#(#{Kernel.UserMessage} 
    								#key: #chemoJun_Low_Resolution 
    								#defaultString: 'Low Resolution' ) 
    							#value: #lowResolution ) 
    						#(#{UI.MenuItem} 
    							#rawLabel: 
    							#(#{Kernel.UserMessage} 
    								#key: #chemoJun_Medium_Resolution 
    								#defaultString: 'Medium Resolution' ) 
    							#value: #mediumResolution ) 
    						#(#{UI.MenuItem} 
    							#rawLabel: 
    							#(#{Kernel.UserMessage} 
    								#key: #chemoJun_High_Resolution 
    								#defaultString: 'High Resolution' ) 
    							#value: #highResolution ) 
    						#(#{UI.MenuItem} 
    							#rawLabel: 
    							#(#{Kernel.UserMessage} 
    								#key: #jun_Reset 
    								#defaultString: 'Reset' ) 
    							#value: #resetView ) ) #(5 3 3 1 ) nil ) ) 
    			#(#{UI.MenuItem} 
    				#rawLabel: 
    				#(#{Kernel.UserMessage} 
    					#key: #jun_Misc 
    					#defaultString: 'Misc' ) 
    				#submenu: #(#{UI.Menu} #(
    						#(#{UI.MenuItem} 
    							#rawLabel: 
    							#(#{Kernel.UserMessage} 
    								#key: #jun_Manual 
    								#defaultString: 'Manual' ) 
    							#value: #browseManual ) 
    						#(#{UI.MenuItem} 
    							#rawLabel: 
    							#(#{Kernel.UserMessage} 
    								#key: #chemoJun_Information 
    								#defaultString: 'Information' ) 
    							#value: #showInformation ) 
    						#(#{UI.MenuItem} 
    							#rawLabel: 
    							#(#{Kernel.UserMessage} 
    								#key: #jun_Viewfinder 
    								#defaultString: 'Viewfinder' ) 
    							#value: #spawnObject ) 
    						#(#{UI.MenuItem} 
    							#rawLabel: 
    							#(#{Kernel.UserMessage} 
    								#key: #jun_Viewport 
    								#defaultString: 'Viewport' ) 
    							#value: #spawnViewport ) 
    						#(#{UI.MenuItem} 
    							#rawLabel: 
    							#(#{Kernel.UserMessage} 
    								#key: #jun_Inspect 
    								#defaultString: 'Inspect' ) 
    							#value: #inspectModel ) ) #(1 1 2 1 ) nil ) ) ) #(3 ) nil ) decodeAsLiteralArray
  13. moleculeObject: moleculeObject [instance creation] xrefs
     
    	^(self new)
    		moleculeObject: moleculeObject;
    		exceptHydrogen: moleculeObject exceptHydrogen;
    		yourself
  14. system [copyright] xrefs
    	^'ChemoJun'
  15. version [copyright] xrefs
    	^'050'
  16. windowSpec [interface specs] xrefs
    	"Tools.UIPainter new openOnClass: self andSelector: #windowSpec"
    
    	<resource: #canvas>
    	^#(#{UI.FullSpec} 
    		#window: 
    		#(#{UI.WindowSpec} 
    			#label: 
    			#(#{Kernel.UserMessage} 
    				#key: #chemoJun_Molecular_Viewer 
    				#defaultString: 'Molecular Viewer' ) 
    			#min: #(#{Core.Point} 280 280 ) 
    			#bounds: #(#{Graphics.Rectangle} 512 280 812 580 ) 
    			#flags: 4 
    			#menu: #menuBar ) 
    		#component: 
    		#(#{UI.SpecCollection} 
    			#collection: #(
    				#(#{UI.ArbitraryComponentSpec} 
    					#layout: #(#{Graphics.LayoutFrame} 1 0 1 0 -20 1 -1 1 ) 
    					#name: #displayView 
    					#colors: 
    					#(#{UI.LookPreferences} 
    						#setBackgroundColor: #(#{Graphics.ColorValue} #white ) ) 
    					#component: #displayView ) 
    				#(#{UI.ArbitraryComponentSpec} 
    					#layout: #(#{Graphics.LayoutFrame} -19 1 1 0 -1 1 19 0 ) 
    					#name: #pickButtonView 
    					#flags: 0 
    					#component: #pickButtonView ) 
    				#(#{UI.ArbitraryComponentSpec} 
    					#layout: #(#{Graphics.LayoutFrame} -19 1 20 0 -1 1 38 0 ) 
    					#name: #grabButtonView 
    					#flags: 0 
    					#component: #grabButtonView ) 
    				#(#{UI.ArbitraryComponentSpec} 
    					#layout: #(#{Graphics.LayoutFrame} -19 1 39 0 -1 1 57 0 ) 
    					#name: #dragButtonView 
    					#flags: 0 
    					#component: #dragButtonView ) 
    				#(#{UI.ArbitraryComponentSpec} 
    					#layout: #(#{Graphics.LayoutFrame} -19 1 -61 0.5 -1 1 61 0.5 ) 
    					#name: #zThumbWheelView 
    					#flags: 0 
    					#component: #zThumbWheelView ) 
    				#(#{UI.ArbitraryComponentSpec} 
    					#layout: #(#{Graphics.LayoutFrame} -19 1 62 0.5 -1 1 80 0.5 ) 
    					#name: #focusButtonView 
    					#flags: 0 
    					#component: #focusButtonView ) 
    				#(#{UI.ArbitraryComponentSpec} 
    					#layout: #(#{Graphics.LayoutFrame} -19 1 -38 1 -1 1 -20 1 ) 
    					#name: #cameraButtonView 
    					#flags: 48 
    					#component: #cameraButtonView ) ) ) )

index xrefs