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

ChemoJunGeneralViewer

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 anImage |
    	aView := self getView.
    	(aView isNil or: [aView isOpen not]) 
    		ifTrue: [anImage := super asImage]
    		ifFalse: 
    			[self errorSignal handle: [:exception | anImage := super asImage]
    				do: 
    					[| aWindow aPixmap |
    					aWindow := aView topComponent.
    					aWindow isCollapsed ifTrue: [aWindow expand].
    					aWindow raise.
    					aWindow display.
    					anImage := aWindow asImage.
    					aPixmap := Pixmap extent: aView bounds extent.
    					anImage displayOn: aPixmap graphicsContext
    						at: (aView localPointToGlobal: 0 @ 0) negated.
    					anImage := aPixmap asImage.
    					aPixmap close]].
    	^anImage
  2. displaySuperimposeInView: aView [displaying] xrefs
     
    	| aGraphicsContext aBlock numberOfArbuments aCollection |
    	self exceptIndex ifTrue: [^nil].
    	aView isNil ifTrue: [^nil].
    	aView isOpen ifFalse: [^nil].
    	self moleculeObject isNil ifTrue: [^nil].
    	aGraphicsContext := aView graphicsContext.
    	aBlock := self indexExpressionBlock.
    	numberOfArbuments := aBlock numArgs.
    	aCollection := SortedCollection new: self numberOfAtoms.
    	self atomObjectsAndIndexesDo: 
    			[:atomObject :index | 
    			true = (aBlock 
    						valueWithArguments: ((Array 
    								with: index
    								with: atomObject atomicSymbol
    								with: atomObject atomicPoint) copyFrom: 1 to: numberOfArbuments)) 
    				ifTrue: 
    					[| aText aPoint zValue |
    					(atomObject isHydrogen and: [self exceptHydrogen]) 
    						ifFalse: 
    							[aText := index printString asText.
    							aPoint := self convertModelPointToView3dPoint: atomObject atomicPoint
    										in: aView bounds.
    							zValue := aPoint z.
    							aPoint := (aPoint x @ aPoint y) rounded.
    							aCollection add: zValue -> (Array with: aText with: aPoint)]]].
    	aCollection reverseDo: 
    			[:anAssociation | 
    			| aText aPoint |
    			aText := anAssociation value first.
    			aPoint := anAssociation value last.
    			aView 
    				displayText: aText
    				on: aGraphicsContext
    				at: aPoint
    				textColor: (ColorValue brightness: 0.05)
    				vergeColor: (ColorValue brightness: 0.95)
    				styleSymbol: #small
    				alignmentSymbol: #center]
  3. exceptHydrogen [accessing] xrefs
    	^false
  4. exceptIndex [accessing] xrefs
    	^false
  5. flushDisplayObject [flushing] xrefs
    	^self
  6. indexExpression [accessing] xrefs
    	| index string |
    	index := self class allInstVarNames indexOf: 'indexExpression'.
    	index < 1 ifTrue: [^'[]' copy].
    	(self instVarAt: index) isNil 
    		ifTrue: 
    			[string := '[:index :atom | (atom = ''H'') not]' copy.
    			self setIndexExpression: string
    				setIndexExpressionBlock: (Compiler evaluate: string)].
    	^self instVarAt: index
  7. indexExpression: aString [accessing] xrefs
     
    	| aBlock aBoolean |
    	self errorSignal handle: [:exception | aBlock := nil]
    		do: 
    			[aBlock := Compiler 
    						evaluate: aString
    						for: self
    						logged: false.
    			aBoolean := aBlock 
    						valueWithArguments: ((Array 
    								with: 999
    								with: 'H'
    								with: 0 , 0 , 0
    								with: nil) copyFrom: 1 to: aBlock numArgs).
    			(aBoolean isKindOf: Boolean) ifFalse: [self error: 'unexpected error']].
    	aBlock isNil ifTrue: [^nil].
    	self setIndexExpression: aString setIndexExpressionBlock: aBlock
  8. indexExpressionBlock [accessing] xrefs
    	| index |
    	index := self class allInstVarNames indexOf: 'indexExpressionBlock'.
    	index < 1 ifTrue: [^[] yourself].
    	(self instVarAt: index) isNil ifTrue: [self indexExpression].
    	^self instVarAt: index
  9. initialize [initialize-release] xrefs
    	super initialize.
    	self useMovementProcess: false
  10. isOpen [testing] xrefs
    	self getView ifNil: [^false] ifNotNil: [:aView | ^aView isOpen]
  11. moleculeObject [accessing] xrefs
    	^nil
  12. requestNewImageFilename [menu messages] xrefs
    	"ChemoJunGeneralViewer new requestNewImageFilename."
    
    	| labels values menu message aFilename |
    	labels := Array 
    				with: (Array with: (#jun_Image_files >> 'Image files') asString).
    	values := Array with: JunSystem defaultImageExtensionPatterns.
    	menu := Menu labelList: labels values: values.
    	message := #jun_Input_an_image_file_ >> 'Input an image file.' 
    				expandMacrosWith: 'image'.
    	aFilename := ChemoJunFileRequesterDialog 
    				requestNewFilename: message
    				initialFilename: self defaultBaseName , '.jpg'
    				fileTypeMenu: menu
    				initialFileType: values first.
    	aFilename isNil ifTrue: [^nil].
    	^aFilename
  13. saveAsImage [menu messages] xrefs
    	| aBoolean anImage aFilename |
    	aBoolean := JunSensorUtility shiftDown or: [JunSensorUtility altDown].
    	anImage := self asImage.
    	anImage isNil ifTrue: [^nil].
    	aBoolean 
    		ifTrue: 
    			[anImage := anImage convertToPalette: JunImageProcessor grayPalette256
    						renderedBy: NearestPaint new].
    	aFilename := self requestNewImageFilename.
    	aFilename isNil ifTrue: [^nil].
    	self writeImage: anImage to: aFilename.
    	^anImage
  14. setIndexExpression: aString setIndexExpressionBlock: aBlock [private] xrefs
     
    	^self
  15. settingIndex [menu messages] xrefs
    	| aStream aString |
    	aStream := String new writeStream.
    	aStream nextPutAll: (#chemoJun_Expression_ >> 'Expression?') asString.
    	aStream cr.
    	aStream nextPutAll: (#jun_ex_ >> 'ex.') asString , ')'.
    	aStream cr.
    	aStream nextPutAll: '[:index | true]'.
    	aStream cr.
    	aStream nextPutAll: '[:index | index odd]'.
    	aStream cr.
    	aStream nextPutAll: '[:index | index even]'.
    	aStream cr.
    	aStream nextPutAll: '[:index | (index \\ 3) = 1]'.
    	aStream cr.
    	aStream nextPutAll: '[:index | #(1 10 50 100 150 999) includes: index]'.
    	aStream cr.
    	aStream nextPutAll: '[:index :atom | atom = ''C'']'.
    	aStream cr.
    	aStream nextPutAll: '[:index :atom | (atom = ''H'') not]'.
    	aStream cr.
    	aStream nextPutAll: '[:index :atom | (index odd) & (atom = ''C'')]'.
    	aStream cr.
    	aStream nextPutAll: '[:index :atom :point | false]'.
    	aString := aStream contents.
    	aStream close.
    	aString := JunDialog request: aString initialAnswer: self indexExpression.
    	aString isNil ifTrue: [^nil].
    	aString isEmpty ifTrue: [^nil].
    	self indexExpression: aString.
    	self flushDisplayObject.
    	self changed: #object
  16. updateFileMenuIndication [menu accessing] xrefs
    	| menuItem aMenu displayObjectIsEmpty |
    	super updateFileMenuIndication.
    	menuItem := self menuItemLabeled: 'File' inMenu: self menuBar.
    	menuItem isNil ifTrue: [^self].
    	aMenu := menuItem submenu.
    	aMenu isNil ifTrue: [^nil].
    	displayObjectIsEmpty := self isEmpty.
    	menuItem := self menuItemLabeled: 'Save as' asString inMenu: aMenu.
    	menuItem notNil 
    		ifTrue: 
    			[displayObjectIsEmpty ifTrue: [menuItem disable] ifFalse: [menuItem enable]]

class methods:

  1. copyright [copyright] xrefs
    	^'ChemoJun050 (2006/08/08) Copyright 2002-2006 National Institute of Informatics, Research Organization of Information and Systems.'
  2. 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: #chemoJun_Save_as_Image 
    								#defaultString: 'Save as Image' ) 
    							#value: #saveAsImage ) 
    						#(#{UI.MenuItem} 
    							#rawLabel: 
    							#(#{Kernel.UserMessage} 
    								#key: #chemoJun_Save_as_VRML 
    								#defaultString: 'Save as VRML' ) 
    							#value: #saveWRL97 ) 
    						#(#{UI.MenuItem} 
    							#rawLabel: 
    							#(#{Kernel.UserMessage} 
    								#key: #jun_Quit 
    								#defaultString: 'Quit' ) 
    							#value: #quitDoing ) ) #(2 1 ) nil ) ) 
    			#(#{UI.MenuItem} 
    				#rawLabel: 
    				#(#{Kernel.UserMessage} 
    					#key: #chemoJun_View 
    					#defaultString: 'View' ) 
    				#submenu: #(#{UI.Menu} #(
    						#(#{UI.MenuItem} 
    							#rawLabel: 
    							#(#{Kernel.UserMessage} 
    								#key: #jun_Reset 
    								#defaultString: 'Reset' ) 
    							#value: #resetView ) ) #(1 ) nil ) ) 
    			#(#{UI.MenuItem} 
    				#rawLabel: 
    				#(#{Kernel.UserMessage} 
    					#key: #jun_Misc 
    					#defaultString: 'Misc' ) 
    				#submenu: #(#{UI.Menu} #(
    						#(#{UI.MenuItem} 
    							#rawLabel: 
    							#(#{Kernel.UserMessage} 
    								#key: #jun_Spawn 
    								#defaultString: 'Spawn' ) 
    							#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 ) ) #(2 1 ) nil ) ) ) #(3 ) nil ) decodeAsLiteralArray
  3. system [copyright] xrefs
    	^'ChemoJun'
  4. version [copyright] xrefs
    	^'050'
  5. windowSpec [interface specs] xrefs
    	"UIPainter new openOnClass: self andSelector: #windowSpec"
    
    	<resource: #canvas>
    	^#(#FullSpec 
    		#window: 
    		#(#WindowSpec 
    			#label: 
    			#(#UserMessage 
    				#key: #jun_Viewfinder 
    				#defaultString: 'Viewfinder' ) 
    			#min: #(#Point 280 280 ) 
    			#bounds: #(#Rectangle 100 100 400 400 ) 
    			#flags: 4 
    			#menu: #menuBar ) 
    		#component: 
    		#(#SpecCollection 
    			#collection: #(
    				#(#ArbitraryComponentSpec 
    					#layout: #(#LayoutFrame 20 0 1 0 -20 1 -20 1 ) 
    					#name: #displayView 
    					#colors: 
    					#(#LookPreferences 
    						#setBackgroundColor: #(#ColorValue #white ) ) 
    					#component: #displayView ) 
    				#(#ArbitraryComponentSpec 
    					#layout: #(#LayoutFrame -19 1 1 0 -1 1 19 0 ) 
    					#name: #pickButtonView 
    					#flags: 0 
    					#component: #pickButtonView ) 
    				#(#ArbitraryComponentSpec 
    					#layout: #(#LayoutFrame -19 1 20 0 -1 1 38 0 ) 
    					#name: #grabButtonView 
    					#flags: 0 
    					#component: #grabButtonView ) 
    				#(#ArbitraryComponentSpec 
    					#layout: #(#LayoutFrame -19 1 39 0 -1 1 57 0 ) 
    					#name: #dragButtonView 
    					#flags: 0 
    					#component: #dragButtonView ) 
    				#(#ArbitraryComponentSpec 
    					#layout: #(#LayoutFrame 1 0 -61 0.5 19 0 61 0.5 ) 
    					#name: #xThumbWheelView 
    					#flags: 0 
    					#component: #xThumbWheelView ) 
    				#(#ArbitraryComponentSpec 
    					#layout: #(#LayoutFrame -61 0.5 -19 1 61 0.5 -1 1 ) 
    					#name: #yThumbWheelView 
    					#flags: 0 
    					#component: #yThumbWheelView ) 
    				#(#ArbitraryComponentSpec 
    					#layout: #(#LayoutFrame -19 1 -61 0.5 -1 1 61 0.5 ) 
    					#name: #zThumbWheelView 
    					#flags: 0 
    					#component: #zThumbWheelView ) 
    				#(#ArbitraryComponentSpec 
    					#layout: #(#LayoutFrame -19 1 62 0.5 -1 1 80 0.5 ) 
    					#name: #focusButtonView 
    					#flags: 0 
    					#component: #focusButtonView ) ) ) )

index xrefs