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

ChemoJunUtility

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:

class methods:

  1. addOrReplaceSource: sourceCodeString pattern: patternString with: newString [pseudo] xrefs
     
    	"ChemoJunUtility addOrReplaceSource: 'zzz ^1234' pattern: nil with: '  tsuika'."
    	"ChemoJunUtility addOrReplaceSource: 'zzz ^1234' pattern: 'zzz' with: 'yyy'."
    	"ChemoJunUtility addOrReplaceSource: 'zzz ^1234' pattern: 'zZz' with: 'yyy'."
    	"ChemoJunUtility addOrReplaceSource: 'zzz ^1234' pattern: '^1' with: '^98'."
    	"ChemoJunUtility addOrReplaceSource: 'zzz ^1234' pattern: '^1##' with: '98765'."
    	"ChemoJunUtility addOrReplaceSource: 'abcdefghijklmnopqrstuvwxyz' pattern: 'c*m' with: '9876'."
    
    	| firstIndex interval lastIndex newSourceCodeString |
    	patternString ifNil: [firstIndex := 0]
    		ifNotNil: 
    			[interval := sourceCodeString 
    						findString: patternString
    						startingAt: 1
    						ignoreCase: false
    						useWildcards: true.
    			lastIndex := interval last.
    			firstIndex := interval first min: lastIndex].
    	firstIndex = 0 
    		ifTrue: [newSourceCodeString := sourceCodeString , newString]
    		ifFalse: 
    			[newSourceCodeString := sourceCodeString 
    						copyReplaceFrom: firstIndex
    						to: lastIndex
    						with: newString].
    	^newSourceCodeString
  2. categoryOfSelector: aSelector inClass: aClass [pseudo] xrefs
     
    	"ChemoJunUtility categoryOfSelector: #abs inClass: ArithmeticValue."
    
    	^aClass organization categoryOfElement: aSelector
  3. chemoJunMolDataUriString [sample data] xrefs
    	"JunURL browse: (ChemoJunUtility chemoJunMolDataUriString)."
    
    	| uriString |
    	uriString := JunEnvironmentUtility 
    				environmentVariableAt: 'ChemoJunMolDataUri'
    				ifAbsent: 
    					[(Filename defaultDirectory construct: 'ChemoJunMolData') asURI asString].
    	^uriString
  4. compileSource: sourceCodeString inClass: aClass classified: aCategory [pseudo] xrefs
     
    	"ChemoJunUtility compileSource: 'zzz ^self' inClass: ChemoJunUtility class classified: #'zzz'."
    
    	^aClass compile: sourceCodeString classified: aCategory
  5. copyright [copyright] xrefs
    	^'ChemoJun050 (2006/08/08) Copyright 2002-2006 National Institute of Informatics, Research Organization of Information and Systems.'
  6. directoriesInChemoJunSampleData [sample data] xrefs
    	"ChemoJunUtility directoriesInChemoJunSampleData."
    
    	| aDirectory aCollection aString |
    	aDirectory := self chemoJunMolDataUriString asURI asFilename.
    	aDirectory exists ifFalse: [^Array new].
    	aDirectory isDirectory ifFalse: [^Array new].
    	aCollection := aDirectory directoryContents 
    				collect: [:each | aDirectory construct: each].
    	aCollection := aCollection select: [:each | each isDirectory].
    	self isWeakInJapanese 
    		ifTrue: 
    			[aCollection := aCollection select: 
    							[:each | 
    							aString := (Filename splitPath: each asString) last.
    							aString ~= (Filename splitPath: aDirectory asString) last and: 
    									[(aString isKindOf: ByteString) 
    										and: [(aString detect: [:char | char asInteger >= 255] ifNone: [nil]) isNil]]]]
    		ifFalse: 
    			[aCollection := aCollection select: 
    							[:each | 
    							aString := (Filename splitPath: each asString) last.
    							aString ~= (Filename splitPath: aDirectory asString) last 
    								and: [(aString isKindOf: ByteString) or: [aString isKindOf: TwoByteString]]]].
    	^(aCollection asSortedCollection: [:f1 :f2 | f1 asString < f2 asString]) 
    		asArray
  7. expanded: moleculeObject by: serialNumbers [tips] xrefs
     
    	"(ChemoJunMoleculeViewer moleculeObject: (ChemoJunUtility 
    				expanded: (ChemoJunMoleculeObject fileName: (JunUniFileName named: './ChemoJunSampleData/fullerene.mol'))
    				by: #(21 34 41 35 22))) open."
    
    	"(ChemoJunMoleculeViewer moleculeObject: (ChemoJunUtility 
    				expanded: (ChemoJunMoleculeObject fileName: (JunUniFileName named: './ChemoJunSampleData/tyr.mol'))
    				by: #(10 13 17 19 15 14))) open."
    
    	"(ChemoJunMoleculeViewer moleculeObject: (ChemoJunUtility 
    				expanded: (ChemoJunMoleculeObject fileName: (JunUniFileName named: './ChemoJunSampleData/trp.mol'))
    				by: #(13 16 19 23 21 17))) open."
    
    	| pointAssociations compoundObject basePolygon aTransformation firstPoint anAngle xzPlane pointCollection polylineCollection basePoint assocCollection vertexCollection edgeCollection loopCollection newMoleculeObject |
    	pointAssociations := moleculeObject atomObjects 
    				collect: [:atomObject | atomObject atomicPoint -> atomObject atomicPoint].
    	compoundObject := JunOpenGL3dCompoundObject new.
    	moleculeObject atomConnectionsDo: 
    			[:atomConnection | 
    			compoundObject 
    				add: (((atomConnection fromAtom atomicPoint 
    						to: atomConnection toAtom atomicPoint) asJunOpenGL3dObject)
    						paint: ColorValue black;
    						lineWidth: 3;
    						yourself)].
    	basePolygon := JunOpenGL3dPolygon vertexes: (serialNumbers 
    						collect: [:serialNumber | (moleculeObject atomObjects at: serialNumber) atomicPoint]).
    	aTransformation := Jun3dTransformation 
    				translate: basePolygon averagePoint negated.
    	compoundObject := compoundObject transform: aTransformation.
    	basePolygon := basePolygon transform: aTransformation.
    	pointAssociations := pointAssociations 
    				collect: [:assoc | assoc value: (assoc value transform: aTransformation)].
    	"compoundObject showWithAxes hiddenlinePresentation."
    	aTransformation := Jun3dTransformation 
    				alignVector: basePolygon normalUnitVector
    				withVector: 0 , 0 , 1.
    	compoundObject := compoundObject transform: aTransformation.
    	basePolygon := basePolygon transform: aTransformation.
    	pointAssociations := pointAssociations 
    				collect: [:assoc | assoc value: (assoc value transform: aTransformation)].
    	"compoundObject showWithAxes hiddenlinePresentation."
    	firstPoint := basePolygon vertexes first.
    	anAngle := (0 , 0 , 0 to: 1 , 0 , 0) 
    				angleWithLine: (0 , 0 , 0 to: firstPoint).
    	xzPlane := JunPlane 
    				on: 0 , 0 , 0
    				on: 0 , 0 , 1
    				on: 1 , 0 , 0.
    	(xzPlane whichSide: firstPoint) >= 0 
    		ifTrue: [aTransformation := Jun3dTransformation rotateZ: anAngle negated]
    		ifFalse: [aTransformation := Jun3dTransformation rotateZ: anAngle].
    	compoundObject := compoundObject transform: aTransformation.
    	basePolygon := basePolygon transform: aTransformation.
    	pointAssociations := pointAssociations 
    				collect: [:assoc | assoc value: (assoc value transform: aTransformation)].
    	"compoundObject showWithAxes hiddenlinePresentation."
    	pointCollection := JunHashEqualitySet new.
    	pointCollection addAll: compoundObject asPointArray.
    	polylineCollection := OrderedCollection new.
    	compoundObject 
    		primitivesDo: [:aPolyline | polylineCollection add: aPolyline asArrayOfLines].
    	basePoint := 0 , 0 , (compoundObject boundingBox origin z - 1).
    	assocCollection := OrderedCollection new: pointCollection size.
    	pointCollection do: 
    			[:point | 
    			| distance |
    			distance := basePoint distance: point.
    			assocCollection add: point -> distance].
    	assocCollection := (assocCollection 
    				asSortedCollection: [:a1 :a2 | a1 value < a2 value]) asArray.
    	vertexCollection := OrderedCollection new: pointCollection size.
    	edgeCollection := OrderedCollection new: polylineCollection size * 3.
    	loopCollection := OrderedCollection new: polylineCollection size.
    	assocCollection := assocCollection collect: 
    					[:assoc | 
    					| point distance p1 p2 vertex |
    					point := assoc key.
    					distance := assoc value.
    					distance := distance * distance.
    					p1 := basePoint x , basePoint y , 0.
    					p2 := point x , point y , 0.
    					(p1 equal: p2) 
    						ifTrue: [vertex := p1]
    						ifFalse: [vertex := (p1 to: p2) normalized atT: distance].
    					vertexCollection add: vertex.
    					point -> vertex].
    	polylineCollection do: 
    			[:polyline | 
    			| edges |
    			edges := OrderedCollection new: polyline size.
    			polyline do: 
    					[:line | 
    					| edge |
    					edge := (assocCollection detect: [:a | line from equal: a key]) value 
    								to: (assocCollection detect: [:a | line to equal: a key]) value.
    					edgeCollection add: edge.
    					edges add: edge].
    			loopCollection add: edges asArray].
    	pointAssociations := pointAssociations collect: 
    					[:assoc | 
    					assoc 
    						value: (assocCollection detect: [:a | assoc value equal: a key]) value].
    	newMoleculeObject := moleculeObject copy.
    	newMoleculeObject atomObjectsDo: 
    			[:atomObject | 
    			atomObject 
    				atomicPoint: (pointAssociations 
    						detect: [:assoc | assoc key equal: atomObject atomicPoint]) value].
    	^newMoleculeObject
  8. isWeakInJapanese [testing] xrefs
    	"ChemoJunUtility isWeakInJapanese."
    
    	^(Parcel parcelNamed: 'Jpl') isNil or: 
    			[(VisualWorksSettings files20MessageDirectories target value asArray 
    				detect: 
    					[:aFilename | 
    					| aString aBoolean |
    					aString := aFilename asString.
    					(aString = '.' or: 
    							[(aString findString: 'messages' startingAt: 1) > 0 
    								and: [(aString findString: 'jun' startingAt: 1) > 0]]) 
    						ifTrue: 
    							[| aDirectory |
    							aDirectory := aFilename asFilename construct: 'ja'.
    							aBoolean := aDirectory exists and: [aDirectory isDirectory]]
    						ifFalse: [aBoolean := false].
    					aBoolean yourself]
    				ifNone: [nil]) isNil]
  9. makeMolfileOfFullerene [tips] xrefs
    	"ChemoJunUtility makeMolfileOfFullerene."
    
    	| aHedron lineCollection pointCollection aStream |
    	aHedron := JunOpenGL3dObject truncatedIcosahedron scaledBy: 3.5.
    	pointCollection := JunHashEqualitySet new: 60.
    	pointCollection addAll: aHedron asPointArray.
    	lineCollection := OrderedCollection new.
    	aHedron 
    		polygonsDo: [:aPolygon | lineCollection addAll: aPolygon asArrayOfLines].
    	pointCollection := (pointCollection asSortedCollection: 
    					[:point1 :point2 | 
    					| value1 value2 |
    					value1 := point1 x.
    					value2 := point2 x.
    					(value1 - value2) abs < JunGeometry accuracy 
    						ifTrue: 
    							[value1 := point1 y.
    							value2 := point2 y.
    							(value1 - value2) abs < JunGeometry accuracy 
    								ifTrue: 
    									[value1 := point1 z.
    									value2 := point2 z]].
    					value1 < value2]) 
    				asArray.
    	lineCollection := (lineCollection asSortedCollection: 
    					[:line1 :line2 | 
    					| index1 index2 |
    					index1 := pointCollection findFirst: [:p | p equal: line1 from].
    					index2 := pointCollection findFirst: [:p | p equal: line2 from].
    					index1 = index2 
    						ifTrue: 
    							[index1 := pointCollection findFirst: [:p | p equal: line1 to].
    							index2 := pointCollection findFirst: [:p | p equal: line2 to]].
    					index1 < index2]) 
    				asArray.
    	JunControlUtility 
    		assert: [aStream := 'fullerene.mol' asFilename writeStream]
    		do: 
    			[aStream
    				nextPutAll: 'fullerene.mol';
    				cr.
    			aStream cr.
    			aStream cr.
    			aStream 
    				nextPutAll: (JunStringUtility format: 'i3' value: pointCollection size).
    			aStream 
    				nextPutAll: (JunStringUtility format: 'i3' value: lineCollection size).
    			9 
    				timesRepeat: [aStream nextPutAll: (JunStringUtility format: 'i3' value: 0)].
    			aStream nextPutAll: (JunStringUtility format: 'x1' value: nil).
    			aStream nextPutAll: (JunStringUtility format: 'a5' value: 'V2000').
    			aStream cr.
    			pointCollection do: 
    					[:point | 
    					aStream nextPutAll: (JunStringUtility format: 'f10.4' value: point x).
    					aStream nextPutAll: (JunStringUtility format: 'f10.4' value: point y).
    					aStream nextPutAll: (JunStringUtility format: 'f10.4' value: point z).
    					aStream nextPutAll: (JunStringUtility format: 'x1' value: nil).
    					aStream nextPutAll: (JunStringUtility format: 'a3' value: 'C').
    					aStream nextPutAll: (JunStringUtility format: 'i2' value: 0).
    					11 
    						timesRepeat: [aStream nextPutAll: (JunStringUtility format: 'i3' value: 0)].
    					aStream cr].
    			lineCollection do: 
    					[:line | 
    					aStream nextPutAll: (JunStringUtility format: 'i3'
    								value: (pointCollection findFirst: [:p | line from equal: p])).
    					aStream nextPutAll: (JunStringUtility format: 'i3'
    								value: (pointCollection findFirst: [:p | line to equal: p])).
    					aStream nextPutAll: (JunStringUtility format: 'i3' value: 1).
    					aStream nextPutAll: (JunStringUtility format: 'i3' value: 0).
    					3 
    						timesRepeat: [aStream nextPutAll: (JunStringUtility format: 'i3' value: 0)].
    					aStream cr].
    			aStream nextPutAll: 'M  END'.
    			aStream cr]
    		ensure: [aStream close]
  10. makeMolfileOfFullereneExpanded [tips] xrefs
    	"ChemoJunUtility makeMolfileOfFullereneExpanded."
    
    	| aHedron polygonCollection lineCollection pointCollection basePoint assocCollection scaleFactor aBody aStream |
    	aHedron := JunOpenGL3dObject truncatedIcosahedron.
    	polygonCollection := OrderedCollection new: 32.
    	aHedron polygonsDo: [:aPolygon | polygonCollection add: aPolygon].
    	lineCollection := OrderedCollection new: 32 * 6.
    	polygonCollection 
    		do: [:aPolygon | lineCollection addAll: aPolygon asArrayOfLines].
    	pointCollection := JunHashEqualitySet new: 60.
    	pointCollection addAll: aHedron asPointArray.
    	pointCollection := (pointCollection asSortedCollection: 
    					[:point1 :point2 | 
    					| value1 value2 |
    					value1 := point1 x.
    					value2 := point2 x.
    					(value1 - value2) abs < JunGeometry accuracy 
    						ifTrue: 
    							[value1 := point1 y.
    							value2 := point2 y.
    							(value1 - value2) abs < JunGeometry accuracy 
    								ifTrue: 
    									[value1 := point1 z.
    									value2 := point2 z]].
    					value1 < value2]) 
    				asArray.
    	basePoint := 0 , 0 , (2 sqrt * 2 + 1) negated.
    	assocCollection := OrderedCollection new.
    	scaleFactor := 0.75.
    	aBody := JunOpenGL3dCompoundObject new.
    	pointCollection := pointCollection collect: 
    					[:each | 
    					| distance line point |
    					distance := (basePoint distance: each) - 1.
    					distance > 3.5 
    						ifTrue: [distance := distance ** 2.2]
    						ifFalse: [distance := distance ** 2].
    					line := (basePoint x , basePoint y , 0 to: each x , each y , 0) normalized.
    					point := line atT: distance.
    					assocCollection add: each -> point.
    					aBody add: ((point asJunOpenGL3dObject)
    								paint: ColorValue black;
    								size: 5;
    								yourself).
    					(point scaledBy: scaleFactor) yourself].
    	lineCollection := lineCollection collect: 
    					[:each | 
    					| line |
    					line := (assocCollection detect: [:a | each from equal: a key]) value 
    								to: (assocCollection detect: [:a | each to equal: a key]) value.
    					aBody add: ((line asJunOpenGL3dObject)
    								paint: ColorValue black;
    								lineWidth: 3;
    								yourself).
    					(line scaledBy: scaleFactor) yourself].
    	"aBody showWithAxes."
    	lineCollection := (lineCollection asSortedCollection: 
    					[:line1 :line2 | 
    					| index1 index2 |
    					index1 := pointCollection findFirst: [:p | p equal: line1 from].
    					index2 := pointCollection findFirst: [:p | p equal: line2 from].
    					index1 = index2 
    						ifTrue: 
    							[index1 := pointCollection findFirst: [:p | p equal: line1 to].
    							index2 := pointCollection findFirst: [:p | p equal: line2 to]].
    					index1 < index2]) 
    				asArray.
    	JunControlUtility 
    		assert: [aStream := 'fullerene_expanded.mol' asFilename writeStream]
    		do: 
    			[aStream
    				nextPutAll: 'fullerene.mol';
    				cr.
    			aStream cr.
    			aStream cr.
    			aStream 
    				nextPutAll: (JunStringUtility format: 'i3' value: pointCollection size).
    			aStream 
    				nextPutAll: (JunStringUtility format: 'i3' value: lineCollection size).
    			9 
    				timesRepeat: [aStream nextPutAll: (JunStringUtility format: 'i3' value: 0)].
    			aStream nextPutAll: (JunStringUtility format: 'x1' value: nil).
    			aStream nextPutAll: (JunStringUtility format: 'a5' value: 'V2000').
    			aStream cr.
    			pointCollection do: 
    					[:point | 
    					aStream nextPutAll: (JunStringUtility format: 'f10.4' value: point x).
    					aStream nextPutAll: (JunStringUtility format: 'f10.4' value: point y).
    					aStream nextPutAll: (JunStringUtility format: 'f10.4' value: point z).
    					aStream nextPutAll: (JunStringUtility format: 'x1' value: nil).
    					aStream nextPutAll: (JunStringUtility format: 'a3' value: 'C').
    					aStream nextPutAll: (JunStringUtility format: 'i2' value: 0).
    					11 
    						timesRepeat: [aStream nextPutAll: (JunStringUtility format: 'i3' value: 0)].
    					aStream cr].
    			lineCollection do: 
    					[:line | 
    					aStream nextPutAll: (JunStringUtility format: 'i3'
    								value: (pointCollection findFirst: [:p | line from equal: p])).
    					aStream nextPutAll: (JunStringUtility format: 'i3'
    								value: (pointCollection findFirst: [:p | line to equal: p])).
    					aStream nextPutAll: (JunStringUtility format: 'i3' value: 1).
    					aStream nextPutAll: (JunStringUtility format: 'i3' value: 0).
    					3 
    						timesRepeat: [aStream nextPutAll: (JunStringUtility format: 'i3' value: 0)].
    					aStream cr].
    			aStream nextPutAll: 'M  END'.
    			aStream cr]
    		ensure: [aStream close]
  11. manualBaseUriString [manuals] xrefs
    	"JunURL browse: (ChemoJunUtility manualBaseUriString)."
    
    	| uriString |
    	uriString := JunEnvironmentUtility 
    				environmentVariableAt: 'ChemoJunManualBaseUri'
    				ifAbsent: 
    					["((Filename defaultDirectory construct: 'Manuals') construct: 'ChemoJun') 
    						asURI asString"
    
    					'http://research.nii.ac.jp/~cheminfo/ChemoJun/Documents/Manuals/' yourself].
    	^uriString
  12. manualUriStringConstruct: aString [manuals] xrefs
     
    	"JunURL browse: (ChemoJunUtility manualUriStringConstruct: 'index.html')."
    
    	| uriString |
    	uriString := self manualBaseUriString asString.
    	uriString last = $/ ifFalse: [uriString := uriString , '/'].
    	uriString := uriString , aString.
    	^uriString
  13. molfilesInChemoJunSampleData [sample data] xrefs
    	"ChemoJunUtility molfilesInChemoJunSampleData."
    
    	| aDirectory aCollection aString |
    	aDirectory := self chemoJunMolDataUriString asURI asFilename.
    	aDirectory exists ifFalse: [^Array new].
    	aDirectory isDirectory ifFalse: [^Array new].
    	aCollection := (JunFileModel 
    				dive: aDirectory
    				level: 2
    				patterns: #('*.mol' '*.MOL')) collect: [:each | each asFilename].
    	self isWeakInJapanese 
    		ifTrue: 
    			[aCollection := aCollection select: 
    							[:each | 
    							aString := (Filename splitPath: each asString) first.
    							[aString isEmpty not and: [aString last = Filename separator]] 
    								whileTrue: [aString := aString copyFrom: 1 to: aString size - 1].
    							aString := (Filename splitPath: aString) last.
    							(aString isKindOf: ByteString) 
    								and: [(aString detect: [:char | char asInteger >= 255] ifNone: [nil]) isNil]]]
    		ifFalse: 
    			[aCollection := aCollection select: 
    							[:each | 
    							aString := (Filename splitPath: each asString) first.
    							[aString isEmpty not and: [aString last = Filename separator]] 
    								whileTrue: [aString := aString copyFrom: 1 to: aString size - 1].
    							aString := (Filename splitPath: aString) last.
    							(aString isKindOf: ByteString) or: [aString isKindOf: TwoByteString]]].
    	^(aCollection asSortedCollection: [:f1 :f2 | f1 asString < f2 asString]) 
    		asArray
  14. pesude: aClass pattern: patternString with: newString [pseudo] xrefs
     
    	"ChemoJunSystem classes do: [:aClass | ChemoJunUtility pesude: aClass pattern: patternString with: newString]."
    
    	| selectorCollection sourceCodeString newSourceCodeString aCategory |
    	selectorCollection := self selectorsOfClass: aClass.
    	selectorCollection do: 
    			[:aSelector | 
    			sourceCodeString := self sourceOfSelector: aSelector inClass: aClass.
    			newSourceCodeString := self 
    						addOrReplaceSource: sourceCodeString
    						pattern: patternString
    						with: newString.
    			aCategory := self categoryOfSelector: aSelector inClass: aClass.
    			self 
    				compileSource: newSourceCodeString
    				inClass: aClass
    				classified: aCategory]
  15. selectBlockForDirectoryContents [blocks] xrefs
    	"ChemoJunUtility selectBlockForDirectoryContents."
    
    	| selectBlock |
    	selectBlock := 
    			[:aFilename | 
    			| aString aBoolean |
    			aString := aFilename asString.
    			"Transcript
    						cr;
    						show: aString printString."
    			ChemoJunUtility isWeakInJapanese 
    				ifTrue: 
    					[aBoolean := (aString isKindOf: ByteString) 
    								and: [(aString detect: [:char | char asInteger >= 255] ifNone: [nil]) isNil]]
    				ifFalse: [aBoolean := true].
    			aBoolean yourself].
    	^selectBlock
  16. selectDirectoriesInChemoJunSampleData [sample data] xrefs
    	"ChemoJunUtility selectDirectoriesInChemoJunSampleData."
    
    	| aCollection |
    	aCollection := self directoriesInChemoJunSampleData.
    	aCollection isEmpty ifTrue: [^nil].
    	^ChemoJunDialog new 
    		chooseMultiple: (#chemoJun_Select_some_directories_ >> 'Select some directories.') 
    				asString
    		fromList: (aCollection 
    				collect: [:each | (Filename splitPath: each asString) last])
    		values: aCollection
    		lines: (aCollection size min: 32)
    		cancel: [nil]
  17. selectDirectoryInChemoJunSampleData [sample data] xrefs
    	"ChemoJunUtility selectDirectoryInChemoJunSampleData."
    
    	| aCollection |
    	aCollection := self directoriesInChemoJunSampleData.
    	aCollection isEmpty ifTrue: [^nil].
    	^ChemoJunDialog 
    		choose: (#jun_Select_a_directory_ >> 'Select a directory.') 
    				asString
    		fromList: (aCollection 
    				collect: [:each | (Filename splitPath: each asString) last])
    		values: aCollection
    		lines: (aCollection size min: 32)
    		cancel: [nil]
  18. selectMolfileInChemoJunSampleData [sample data] xrefs
    	"ChemoJunUtility selectMolfileInChemoJunSampleData."
    
    	| aCollection |
    	aCollection := self molfilesInChemoJunSampleData.
    	aCollection isEmpty ifTrue: [^nil].
    	^ChemoJunDialog 
    		choose: (#jun_Select_a_file_ >> 'Select a file.') asString
    		fromList: (aCollection collect: 
    					[:each | 
    					
    					[| aString |
    					aString := (Filename splitPath: each asString) first.
    					[aString isEmpty not and: [aString last = Filename separator]] 
    						whileTrue: [aString := aString copyFrom: 1 to: aString size - 1].
    					aString := '(' , (Filename splitPath: aString) last , ') '.
    					aString yourself] 
    							value , (Filename splitPath: each asString) last])
    		values: aCollection
    		lines: (aCollection size min: 32)
    		cancel: [nil]
  19. selectMolfilesInChemoJunSampleData [sample data] xrefs
    	"ChemoJunUtility selectMolfilesInChemoJunSampleData."
    
    	| aCollection |
    	aCollection := self molfilesInChemoJunSampleData.
    	aCollection isEmpty ifTrue: [^nil].
    	^ChemoJunDialog new 
    		chooseMultiple: (#chemoJun_Select_some_files_ >> 'Select some files.') asString
    		fromList: (aCollection collect: 
    					[:each | 
    					
    					[| aString |
    					aString := (Filename splitPath: each asString) first.
    					[aString isEmpty not and: [aString last = Filename separator]] 
    						whileTrue: [aString := aString copyFrom: 1 to: aString size - 1].
    					aString := '(' , (Filename splitPath: aString) last , ') '.
    					aString yourself] 
    							value , (Filename splitPath: each asString) last])
    		values: aCollection
    		lines: (aCollection size min: 32)
    		cancel: [nil]
  20. selectorsOfClass: aClass [pseudo] xrefs
     
    	"ChemoJunUtility selectorsOfClass: ChemoJunUtility class."
    
    	^aClass selectors
  21. sourceOfSelector: aSelector inClass: aClass [pseudo] xrefs
     
    	"ChemoJunUtility sourceOfSelector: #abs inClass: ArithmeticValue."
    
    	^aClass sourceCodeAt: aSelector
  22. system [copyright] xrefs
    	^'ChemoJun'
  23. version [copyright] xrefs
    	^'050'

index xrefs