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

ChemoJunMoleculeObject

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. arrayOfPolylinesForAromaticBondAsPlane: atomConnection [3d aux] xrefs
     
    	| fromAtom toAtom fromPoint toPoint centerPoint firstPolylines aLine offsetPoint secondPolylines aPlane connectedAtoms positiveAtoms negativeAtoms |
    	atomConnection bondTypeSymbol = #aromatic 
    		ifFalse: [^self error: 'connection is not aromatic bond.'].
    	fromAtom := atomConnection fromAtom.
    	toAtom := atomConnection toAtom.
    	fromPoint := fromAtom atomicPoint.
    	toPoint := toAtom atomicPoint.
    	centerPoint := fromPoint center: toPoint.
    	firstPolylines := Array with: (JunOpenGL3dPolyline 
    						vertexes: (Array with: fromPoint with: centerPoint))
    				with: (JunOpenGL3dPolyline 
    						vertexes: (Array with: centerPoint with: toPoint)).
    	atomConnection hasConnectionColor 
    		ifTrue: 
    			[firstPolylines first paint: atomConnection connectionColor.
    			firstPolylines last paint: atomConnection connectionColor]
    		ifFalse: 
    			[fromAtom hasAtomicColor 
    				ifTrue: [firstPolylines first paint: fromAtom atomicColor]
    				ifFalse: [firstPolylines first paint: atomConnection defaultConnectionColor].
    			toAtom hasAtomicColor 
    				ifTrue: [firstPolylines last paint: toAtom atomicColor]
    				ifFalse: [firstPolylines last paint: atomConnection defaultConnectionColor]].
    	firstPolylines first lineWidth: 2.
    	firstPolylines last lineWidth: 2.
    	aLine := (fromPoint as2dPoint bisector: toPoint as2dPoint) normalized.
    	offsetPoint := ((aLine atT: 0.05) - (aLine atT: 0)) as3dPoint.
    	secondPolylines := firstPolylines collect: 
    					[:each | 
    					| polyline from to line |
    					polyline := each copy.
    					from := polyline vertexes first.
    					to := polyline vertexes last.
    					line := from to: to.
    					from = centerPoint ifFalse: [from := line atT: 0.12].
    					to = centerPoint ifFalse: [to := line atT: 0.88].
    					polyline vertexes: (Array with: from with: to).
    					polyline yourself].
    	aPlane := fromPoint plane: toPoint and: fromPoint x , fromPoint y , 1.
    	connectedAtoms := self connectedAromaticAtomsAround: atomConnection.
    	positiveAtoms := connectedAtoms 
    				select: [:atom | (atom atomicPoint whichSideOf: aPlane) >= 0].
    	negativeAtoms := connectedAtoms 
    				select: [:atom | (atom atomicPoint whichSideOf: aPlane) < 0].
    	secondPolylines := secondPolylines collect: 
    					[:each | 
    					| polyline |
    					positiveAtoms size >= negativeAtoms size 
    						ifTrue: [polyline := each translatedBy: (offsetPoint * 2) negated]
    						ifFalse: [polyline := each translatedBy: (offsetPoint * 2) yourself].
    					polyline yourself].
    	secondPolylines do: [:each | each halftone: 0.25].
    	^Array with: firstPolylines with: secondPolylines
  2. arrayOfPolylinesForDoubleBondAsPlane: atomConnection [3d aux] xrefs
     
    	| fromAtom toAtom fromPoint toPoint centerPoint firstPolylines secondPolylines aLine offsetPoint fromConnections toConnections aPlane |
    	atomConnection bondTypeSymbol = #double 
    		ifFalse: [^self error: 'connection is not double bond.'].
    	fromAtom := atomConnection fromAtom.
    	toAtom := atomConnection toAtom.
    	fromPoint := fromAtom atomicPoint.
    	toPoint := toAtom atomicPoint.
    	centerPoint := fromPoint center: toPoint.
    	firstPolylines := Array with: (JunOpenGL3dPolyline 
    						vertexes: (Array with: fromPoint with: centerPoint))
    				with: (JunOpenGL3dPolyline 
    						vertexes: (Array with: centerPoint with: toPoint)).
    	atomConnection hasConnectionColor 
    		ifTrue: 
    			[firstPolylines first paint: atomConnection connectionColor.
    			firstPolylines last paint: atomConnection connectionColor]
    		ifFalse: 
    			[fromAtom hasAtomicColor 
    				ifTrue: [firstPolylines first paint: fromAtom atomicColor]
    				ifFalse: [firstPolylines first paint: atomConnection defaultConnectionColor].
    			toAtom hasAtomicColor 
    				ifTrue: [firstPolylines last paint: toAtom atomicColor]
    				ifFalse: [firstPolylines last paint: atomConnection defaultConnectionColor]].
    	firstPolylines first lineWidth: 2.
    	firstPolylines last lineWidth: 2.
    	secondPolylines := firstPolylines collect: [:each | each copy].
    	aLine := (fromPoint as2dPoint bisector: toPoint as2dPoint) normalized.
    	offsetPoint := ((aLine atT: 0.05) - (aLine atT: 0)) as3dPoint.
    	(fromPoint z isZero not and: [toPoint z isZero not]) 
    		ifTrue: 
    			[firstPolylines := firstPolylines 
    						collect: [:each | each translatedBy: offsetPoint negated].
    			secondPolylines := secondPolylines 
    						collect: [:each | each translatedBy: offsetPoint yourself].
    			^Array with: firstPolylines with: secondPolylines].
    	fromConnections := (self connectionsWith: fromAtom) 
    				reject: [:each | each = atomConnection].
    	toConnections := (self connectionsWith: toAtom) 
    				reject: [:each | each = atomConnection].
    	aPlane := fromPoint plane: toPoint and: fromPoint x , fromPoint y , 1.
    	firstPolylines := firstPolylines collect: 
    					[:each | 
    					| from to polyline line |
    					from := each vertexes first.
    					to := each vertexes last.
    					polyline := each translatedBy: offsetPoint negated.
    					from = fromPoint 
    						ifTrue: 
    							[fromConnections isEmpty 
    								ifTrue: 
    									[from := polyline vertexes first.
    									to := polyline vertexes last.
    									line := from to: to.
    									from := line atT: 0.12.
    									polyline vertexes: (Array with: from with: to)]
    								ifFalse: 
    									[| sign connections |
    									from := polyline vertexes first.
    									to := polyline vertexes last.
    									sign := from whichSideOf: aPlane.
    									connections := fromConnections select: 
    													[:connection | 
    													| target |
    													target := connection toAtom.
    													target = fromAtom ifTrue: [target := connection fromAtom].
    													(target atomicPoint whichSideOf: aPlane) = sign].
    									connections isEmpty 
    										ifTrue: 
    											[polyline vertexes: (Array 
    														with: fromPoint
    														with: ((from to: to) atT: 0.06)
    														with: to)]
    										ifFalse: 
    											[| points |
    											points := connections collect: 
    															[:connection | 
    															line := connection fromAtom atomicPoint as2dPoint 
    																		to: connection toAtom atomicPoint as2dPoint.
    															(from as2dPoint to: to as2dPoint) intersectingPointWithLine: line].
    											points := (points reject: [:p | p isNil]) collect: [:p | p as3dPoint].
    											points isEmpty 
    												ifFalse: 
    													[points := points 
    																asSortedCollection: [:p1 :p2 | (p1 distance: from) < (p2 distance: from)].
    													polyline vertexes: (Array with: points first with: to)]]]].
    					to = toPoint 
    						ifTrue: 
    							[toConnections isEmpty 
    								ifTrue: 
    									[from := polyline vertexes first.
    									to := polyline vertexes last.
    									line := from to: to.
    									to := line atT: 0.88.
    									polyline vertexes: (Array with: from with: to)]
    								ifFalse: 
    									[| sign connections |
    									from := polyline vertexes first.
    									to := polyline vertexes last.
    									sign := to whichSideOf: aPlane.
    									connections := toConnections select: 
    													[:connection | 
    													| target |
    													target := connection fromAtom.
    													target = toAtom ifTrue: [target := connection toAtom].
    													(target atomicPoint whichSideOf: aPlane) = sign].
    									connections isEmpty 
    										ifTrue: 
    											[polyline vertexes: (Array 
    														with: from
    														with: ((from to: to) atT: 0.94)
    														with: toPoint)]
    										ifFalse: 
    											[| points |
    											points := connections collect: 
    															[:connection | 
    															line := connection fromAtom atomicPoint as2dPoint 
    																		to: connection toAtom atomicPoint as2dPoint.
    															(from as2dPoint to: to as2dPoint) intersectingPointWithLine: line].
    											points := (points reject: [:p | p isNil]) collect: [:p | p as3dPoint].
    											points isEmpty 
    												ifFalse: 
    													[points := points 
    																asSortedCollection: [:p1 :p2 | (p1 distance: to) < (p2 distance: to)].
    													polyline vertexes: (Array with: from with: points first)]]]].
    					polyline yourself].
    	secondPolylines := secondPolylines collect: 
    					[:each | 
    					| from to polyline line |
    					from := each vertexes first.
    					to := each vertexes last.
    					polyline := each translatedBy: offsetPoint yourself.
    					from = fromPoint 
    						ifTrue: 
    							[fromConnections isEmpty 
    								ifTrue: 
    									[from := polyline vertexes first.
    									to := polyline vertexes last.
    									line := from to: to.
    									from := line atT: 0.12.
    									polyline vertexes: (Array with: from with: to)]
    								ifFalse: 
    									[| sign connections |
    									from := polyline vertexes first.
    									to := polyline vertexes last.
    									sign := from whichSideOf: aPlane.
    									connections := fromConnections select: 
    													[:connection | 
    													| target |
    													target := connection toAtom.
    													target = fromAtom ifTrue: [target := connection fromAtom].
    													(target atomicPoint whichSideOf: aPlane) = sign].
    									connections isEmpty 
    										ifTrue: 
    											[polyline vertexes: (Array 
    														with: fromPoint
    														with: ((from to: to) atT: 0.06)
    														with: to)]
    										ifFalse: 
    											[| points |
    											points := connections collect: 
    															[:connection | 
    															line := connection fromAtom atomicPoint as2dPoint 
    																		to: connection toAtom atomicPoint as2dPoint.
    															(from as2dPoint to: to as2dPoint) intersectingPointWithLine: line].
    											points := (points reject: [:p | p isNil]) collect: [:p | p as3dPoint].
    											points isEmpty 
    												ifFalse: 
    													[points := points 
    																asSortedCollection: [:p1 :p2 | (p1 distance: from) < (p2 distance: from)].
    													polyline vertexes: (Array with: points first with: to)]]]].
    					to = toPoint 
    						ifTrue: 
    							[toConnections isEmpty 
    								ifTrue: 
    									[from := polyline vertexes first.
    									to := polyline vertexes last.
    									line := from to: to.
    									to := line atT: 0.88.
    									polyline vertexes: (Array with: from with: to)]
    								ifFalse: 
    									[| sign connections |
    									from := polyline vertexes first.
    									to := polyline vertexes last.
    									sign := to whichSideOf: aPlane.
    									connections := toConnections select: 
    													[:connection | 
    													| target |
    													target := connection fromAtom.
    													target = toAtom ifTrue: [target := connection toAtom].
    													(target atomicPoint whichSideOf: aPlane) = sign].
    									connections isEmpty 
    										ifTrue: 
    											[polyline vertexes: (Array 
    														with: from
    														with: ((from to: to) atT: 0.94)
    														with: toPoint)]
    										ifFalse: 
    											[| points |
    											points := connections collect: 
    															[:connection | 
    															line := connection fromAtom atomicPoint as2dPoint 
    																		to: connection toAtom atomicPoint as2dPoint.
    															(from as2dPoint to: to as2dPoint) intersectingPointWithLine: line].
    											points := (points reject: [:p | p isNil]) collect: [:p | p as3dPoint].
    											points isEmpty 
    												ifFalse: 
    													[points := points 
    																asSortedCollection: [:p1 :p2 | (p1 distance: to) < (p2 distance: to)].
    													polyline vertexes: (Array with: from with: points first)]]]].
    					polyline yourself].
    	^Array with: firstPolylines with: secondPolylines
  3. arrayOfPolylinesForSingleBondAsPlane: atomConnection [3d aux] xrefs
     
    	| fromAtom toAtom fromPoint toPoint centerPoint firstPolylines |
    	atomConnection bondTypeSymbol = #single 
    		ifFalse: [^self error: 'connection is not single bond.'].
    	fromAtom := atomConnection fromAtom.
    	toAtom := atomConnection toAtom.
    	fromPoint := fromAtom atomicPoint.
    	toPoint := toAtom atomicPoint.
    	centerPoint := fromPoint center: toPoint.
    	firstPolylines := Array with: (JunOpenGL3dPolyline 
    						vertexes: (Array with: fromPoint with: centerPoint))
    				with: (JunOpenGL3dPolyline 
    						vertexes: (Array with: centerPoint with: toPoint)).
    	atomConnection hasConnectionColor 
    		ifTrue: 
    			[firstPolylines first paint: atomConnection connectionColor.
    			firstPolylines last paint: atomConnection connectionColor]
    		ifFalse: 
    			[fromAtom hasAtomicColor 
    				ifTrue: [firstPolylines first paint: fromAtom atomicColor]
    				ifFalse: [firstPolylines first paint: atomConnection defaultConnectionColor].
    			toAtom hasAtomicColor 
    				ifTrue: [firstPolylines last paint: toAtom atomicColor]
    				ifFalse: [firstPolylines last paint: atomConnection defaultConnectionColor]].
    	firstPolylines first lineWidth: 2.
    	firstPolylines last lineWidth: 2.
    	^Array with: firstPolylines
  4. arrayOfPolylinesForTripleBondAsPlane: atomConnection [3d aux] xrefs
     
    	| fromAtom toAtom fromPoint toPoint centerPoint firstPolylines secondPolylines thirdPolylines aLine offsetPoint |
    	atomConnection bondTypeSymbol = #triple 
    		ifFalse: [^self error: 'connection is not triple bond.'].
    	fromAtom := atomConnection fromAtom.
    	toAtom := atomConnection toAtom.
    	fromPoint := fromAtom atomicPoint.
    	toPoint := toAtom atomicPoint.
    	centerPoint := fromPoint center: toPoint.
    	firstPolylines := Array with: (JunOpenGL3dPolyline 
    						vertexes: (Array with: fromPoint with: centerPoint))
    				with: (JunOpenGL3dPolyline 
    						vertexes: (Array with: centerPoint with: toPoint)).
    	atomConnection hasConnectionColor 
    		ifTrue: 
    			[firstPolylines first paint: atomConnection connectionColor.
    			firstPolylines last paint: atomConnection connectionColor]
    		ifFalse: 
    			[fromAtom hasAtomicColor 
    				ifTrue: [firstPolylines first paint: fromAtom atomicColor]
    				ifFalse: [firstPolylines first paint: atomConnection defaultConnectionColor].
    			toAtom hasAtomicColor 
    				ifTrue: [firstPolylines last paint: toAtom atomicColor]
    				ifFalse: [firstPolylines last paint: atomConnection defaultConnectionColor]].
    	firstPolylines first lineWidth: 2.
    	firstPolylines last lineWidth: 2.
    	secondPolylines := firstPolylines collect: [:each | each copy].
    	thirdPolylines := firstPolylines collect: [:each | each copy].
    	aLine := (fromPoint as2dPoint bisector: toPoint as2dPoint) normalized.
    	offsetPoint := ((aLine atT: 0.05) - (aLine atT: 0)) as3dPoint.
    	secondPolylines := secondPolylines 
    				collect: [:each | each translatedBy: offsetPoint negated].
    	thirdPolylines := thirdPolylines 
    				collect: [:each | each translatedBy: offsetPoint yourself].
    	^Array 
    		with: firstPolylines
    		with: secondPolylines
    		with: thirdPolylines
  5. asGraph [converting] xrefs
    	| aGraph nodeClass aNode fromAtom toAtom nodeTable fromNode toNode |
    	aGraph := self defaultGraphClass new.
    	aGraph beUndirectedGraph.
    	nodeClass := aGraph class defaultNodeClass.
    	nodeTable := Dictionary new.
    	self atomObjectsAndIndexesDo: 
    			[:atomObject :serialNumber | 
    			aNode := nodeClass 
    						label: atomObject atomicSymbol , '-' , serialNumber printString.
    			aGraph add: aNode.
    			nodeTable at: atomObject put: aNode].
    	self atomConnectionsDo: 
    			[:atomConnection | 
    			fromAtom := atomConnection fromAtom.
    			toAtom := atomConnection toAtom.
    			fromNode := nodeTable at: fromAtom.
    			toNode := nodeTable at: toAtom.
    			aGraph connect: fromNode with: toNode].
    	aGraph arrange: #concentric.
    	^aGraph
  6. asGrapher [converting] xrefs
    	^self defaultGrapherClass graph: self asGraph
  7. atomConnection: atomObject with: anotherAtomObject [accessing connection] xrefs
     
    	self atomConnections do: 
    			[:atomConnection | 
    			(atomConnection fromAtom = atomObject 
    				and: [atomConnection toAtom = anotherAtomObject]) ifTrue: [^atomConnection].
    			(atomConnection fromAtom = anotherAtomObject 
    				and: [atomConnection toAtom = atomObject]) ifTrue: [^atomConnection]].
    	^nil
  8. atomConnections [accessing connection] xrefs
    	atomConnections isNil ifTrue: [atomConnections := Array new].
    	^atomConnections
  9. atomConnections: atomConnectionCollection [accessing connection] xrefs
     
    	atomConnections := atomConnectionCollection asArray
  10. atomConnectionsDo: aBlock [enumerating] xrefs
     
    	self atomConnections do: [:atomConnection | aBlock value: atomConnection]
  11. atomObjectAt: serialNumber [accessing atom] xrefs
     
    	^self atomObjects 
    		detect: [:atomObject | atomObject serialNumber = serialNumber]
    		ifNone: [nil]
  12. atomObjects [accessing atom] xrefs
    	atomObjects isNil ifTrue: [atomObjects := Array new].
    	^atomObjects
  13. atomObjects: atomObjectCollection [accessing atom] xrefs
     
    	atomObjects := atomObjectCollection asArray
  14. atomObjectsAndIndexesDo: aBlock [enumerating] xrefs
     
    	self atomObjects 
    		do: [:atomObject | aBlock value: atomObject value: atomObject serialNumber]
  15. atomObjectsDo: aBlock [enumerating] xrefs
     
    	self atomObjects do: [:atomObject | aBlock value: atomObject]
  16. atomResolution [accessing] xrefs
    	atomResolution isNil ifTrue: [atomResolution := #medium].
    	^atomResolution
  17. atomResolution: aSymbol [accessing] xrefs
     
    	(#(#low #medium #high) includes: aSymbol)
    		ifTrue: [atomResolution := aSymbol]
  18. atomTable [accessing] xrefs
    	| aTable |
    	aTable := Dictionary new.
    	self atomObjectsDo: 
    			[:atomObject | 
    			(aTable includesKey: atomObject atomicSymbol) 
    				ifTrue: 
    					[aTable at: atomObject atomicSymbol
    						put: 1 + (aTable at: atomObject atomicSymbol)]
    				ifFalse: [aTable at: atomObject atomicSymbol put: 1]].
    	^aTable
  19. attributeTable [attribute accessing] xrefs
    	attributeTable isNil ifTrue: [attributeTable := JunAttributeTable new].
    	^attributeTable
  20. changeColor: colorValue serialNumberPairs: serialNumberPairs nestLevel: nestLevel [coloring] xrefs
     
    	| collectionOfAtomConnections |
    	collectionOfAtomConnections := self atomConnections select: 
    					[:atomConnection | 
    					| aPair |
    					aPair := Array with: atomConnection fromAtom serialNumber
    								with: atomConnection toAtom serialNumber.
    					(serialNumberPairs includes: aPair) 
    						or: [serialNumberPairs includes: aPair reverse]].
    	collectionOfAtomConnections 
    		do: [:atomConnection | atomConnection connectionColor: colorValue].
    	nestLevel > 0 
    		ifTrue: 
    			[collectionOfAtomConnections do: 
    					[:atomConnection | 
    					self 
    						changeColor: colorValue
    						serialNumberPairs: ((self connectionsWith: atomConnection fromAtom) asArray 
    								, (self connectionsWith: atomConnection toAtom) asArray collect: 
    										[:each | 
    										Array with: each fromAtom serialNumber with: each toAtom serialNumber])
    						nestLevel: nestLevel - 1]]
  21. changeColor: colorValue serialNumbers: serialNumbers nestLevel: nestLevel [coloring] xrefs
     
    	| collectionOfAtomObjects |
    	collectionOfAtomObjects := self atomObjects 
    				select: [:atomObject | serialNumbers includes: atomObject serialNumber].
    	collectionOfAtomObjects 
    		do: [:atomObject | atomObject atomicColor: colorValue].
    	nestLevel > 0 
    		ifTrue: 
    			[collectionOfAtomObjects do: 
    					[:atomObject | 
    					self 
    						changeColor: colorValue
    						serialNumbers: ((self connectedAtomsWith: atomObject) 
    								collect: [:each | each serialNumber])
    						nestLevel: nestLevel - 1]]
  22. connectedAromaticAtomsAround: atomConnection [accessing atom] xrefs
     
    	| connectedAtoms |
    	connectedAtoms := Set new.
    	(self connectedAtomsAndConnectionsWith: atomConnection fromAtom) 
    		associations do: 
    				[:assoc | 
    				| atom connection |
    				atom := assoc key.
    				connection := assoc value.
    				connection bondTypeSymbol = #aromatic 
    					ifTrue: 
    						[(atom = atomConnection fromAtom or: [atom = atomConnection toAtom]) 
    							ifFalse: [connectedAtoms add: atom]]].
    	(self connectedAtomsAndConnectionsWith: atomConnection toAtom) 
    		associations do: 
    				[:assoc | 
    				| atom connection |
    				atom := assoc key.
    				connection := assoc value.
    				connection bondTypeSymbol = #aromatic 
    					ifTrue: 
    						[(atom = atomConnection fromAtom or: [atom = atomConnection toAtom]) 
    							ifFalse: [connectedAtoms add: atom]]].
    	^(connectedAtoms 
    		asSortedCollection: [:a1 :a2 | a1 serialNumber < a2 serialNumber]) asArray
  23. connectedAtomsAndConnectionsWith: atomObject [accessing atom] xrefs
     
    	| aTable |
    	aTable := Dictionary new.
    	self atomConnections do: 
    			[:atomConnection | 
    			atomConnection fromAtom = atomObject 
    				ifTrue: [aTable add: atomConnection toAtom -> atomConnection].
    			atomConnection toAtom = atomObject 
    				ifTrue: [aTable add: atomConnection fromAtom -> atomConnection]].
    	^aTable
  24. connectedAtomsAround: atomConnection [accessing atom] xrefs
     
    	| connectedAtoms |
    	connectedAtoms := Set new.
    	(self connectedAtomsWith: atomConnection fromAtom) do: 
    			[:each | 
    			(each = atomConnection fromAtom or: [each = atomConnection toAtom]) 
    				ifFalse: [connectedAtoms add: each]].
    	(self connectedAtomsWith: atomConnection toAtom) do: 
    			[:each | 
    			(each = atomConnection fromAtom or: [each = atomConnection toAtom]) 
    				ifFalse: [connectedAtoms add: each]].
    	^(connectedAtoms 
    		asSortedCollection: [:a1 :a2 | a1 serialNumber < a2 serialNumber]) asArray
  25. connectedAtomsWith: atomObject [accessing atom] xrefs
     
    	^(self connectedAtomsAndConnectionsWith: atomObject) keys
  26. connectedConnectionsAround: atomConnection [accessing connection] xrefs
     
    	| connectedConnections |
    	connectedConnections := Set new.
    	(self connectedAtomsAndConnectionsWith: atomConnection fromAtom) 
    		associations do: 
    				[:assoc | 
    				| connection |
    				connection := assoc value.
    				connection = atomConnection 
    					ifFalse: [connectedConnections add: connection]].
    	(self connectedAtomsAndConnectionsWith: atomConnection toAtom) 
    		associations do: 
    				[:assoc | 
    				| connection |
    				connection := assoc value.
    				connection = atomConnection 
    					ifFalse: [connectedConnections add: connection]].
    	^(connectedConnections asSortedCollection: 
    			[:c1 :c2 | 
    			c1 fromAtom serialNumber = c2 fromAtom serialNumber 
    				ifTrue: [c1 toAtom serialNumber < c2 toAtom serialNumber]
    				ifFalse: [c1 fromAtom serialNumber < c2 fromAtom serialNumber]]) 
    		asArray
  27. connectionsWith: atomObject [accessing connection] xrefs
     
    	^(self connectedAtomsAndConnectionsWith: atomObject) values
  28. connectionTable [accessing connection] xrefs
    	| aTable aCollection aString |
    	aTable := Dictionary new.
    	self atomConnections
    		do: 
    			[:each | 
    			aCollection := SortedCollection new: 2.
    			aCollection add: each fromAtom atomicSymbol.
    			aCollection add: each toAtom atomicSymbol.
    			aString := (aCollection at: 1)
    						, '-' , (aCollection at: 2).
    			(aTable includesKey: aString)
    				ifTrue: [aTable at: aString put: 1 + (aTable at: aString)]
    				ifFalse: [aTable at: aString put: 1]].
    	^aTable
  29. cylinderFrom: fromPoint to: toPoint width: widthValue by: divisionNumber [3d aux] xrefs
     
    	| aCylinder aRadius fromCircle fromPoints aPolygon toPoints |
    	aCylinder := JunOpenGL3dCompoundObject new.
    	aRadius := widthValue / 2.
    	fromCircle := Jun3dCircle 
    				center: fromPoint
    				radius: aRadius
    				upVector: (toPoint to: fromPoint) normalUnitVector.
    	fromPoints := fromCircle trackPointsBy: (360 / divisionNumber) rounded.
    	aPolygon := JunOpenGL3dPolygon vertexes: fromPoints.
    	aPolygon paint: ColorValue red.
    	aCylinder add: aPolygon.
    	toPoints := fromPoints collect: [:p | p translatedBy: toPoint - fromPoint].
    	aPolygon := JunOpenGL3dPolygon vertexes: toPoints reverse.
    	aPolygon paint: ColorValue red.
    	aCylinder add: aPolygon.
    	(1 to: fromPoints size - 1) with: (1 to: toPoints size - 1)
    		do: 
    			[:i :j | 
    			| p1 p2 p3 p4 points vectors |
    			p1 := fromPoints at: i.
    			p2 := fromPoints at: i + 1.
    			p3 := toPoints at: j.
    			p4 := toPoints at: j + 1.
    			points := Array 
    						with: p1
    						with: p3
    						with: p4
    						with: p2.
    			vectors := Array 
    						with: (fromPoint to: p1) normalUnitVector
    						with: (toPoint to: p3) normalUnitVector
    						with: (toPoint to: p4) normalUnitVector
    						with: (fromPoint to: p2) normalUnitVector.
    			aPolygon := JunOpenGL3dPolygon vertexes: points.
    			aPolygon normalVectors: vectors.
    			aPolygon paint: ColorValue red.
    			aCylinder add: aPolygon].
    	^aCylinder
  30. default2dMolfilePatterns [defaults] xrefs
    	^#('*.2d.mol')
  31. defaultAtomConnectionClass [defaults] xrefs
    	^self class defaultAtomConnectionClass
  32. defaultAtomObjectClass [defaults] xrefs
    	^self class defaultAtomObjectClass
  33. defaultBallDivisionNumberHigh [defaults] xrefs
    	^2
  34. defaultBallDivisionNumberLow [defaults] xrefs
    	^0
  35. defaultBallDivisionNumberMedium [defaults] xrefs
    	^1
  36. defaultBondThickness [defaults] xrefs
    	^0.09
  37. defaultFrontierMinimumDistance [defaults] xrefs
    	self atomResolution = #high ifTrue: [^0.001d].
    	self atomResolution = #medium ifTrue: [^0.01d].
    	self atomResolution = #low ifTrue: [^0.1d].
    	^0.01d
  38. defaultFrontierRevisedCoeffcient [defaults] xrefs
    	self atomResolution = #high ifTrue: [^0.997d].
    	self atomResolution = #medium ifTrue: [^0.983d].
    	self atomResolution = #low ifTrue: [^0.900d].
    	^0.983d
  39. defaultGraphClass [defaults] xrefs
    	^self class defaultGraphClass
  40. defaultGrapherClass [defaults] xrefs
    	^self class defaultGrapherClass
  41. defaultHalftoneValue [defaults] xrefs
    	^0.5
  42. defaultMinimumTriangleArea [defaults] xrefs
    	self atomResolution = #high ifTrue: [^0.001d].
    	self atomResolution = #medium ifTrue: [^0.01d].
    	self atomResolution = #low ifTrue: [^0.1d].
    	^0.01d
  43. defaultMolFileReaderClass [defaults] xrefs
    	^self class defaultMolFileReaderClass
  44. defaultSpaceFillDivisionNumber [defaults] xrefs
    	self atomResolution = #low 
    		ifTrue: [^self defaultSpaceFillDivisionNumberLow].
    	self atomResolution = #medium 
    		ifTrue: [^self defaultSpaceFillDivisionNumberMedium].
    	self atomResolution = #high 
    		ifTrue: [^self defaultSpaceFillDivisionNumberHigh].
    	^self defaultSpaceFillDivisionNumber
  45. defaultSpaceFillDivisionNumberHigh [defaults] xrefs
    	^3
  46. defaultSpaceFillDivisionNumberLow [defaults] xrefs
    	^1
  47. defaultSpaceFillDivisionNumberMedium [defaults] xrefs
    	^2
  48. defaultTubeDivisionNumber [defaults] xrefs
    	^self defaultTubeDivisionNumberMedium
  49. defaultTubeDivisionNumberHigh [defaults] xrefs
    	^60
  50. defaultTubeDivisionNumberLow [defaults] xrefs
    	^120
  51. defaultTubeDivisionNumberMedium [defaults] xrefs
    	^90
  52. distancesFrom: aPoint [functions] xrefs
     
    	| collection |
    	collection := OrderedCollection new: self numberOfAtoms.
    	self atomObjectsAndIndexesDo: 
    			[:atom :index | 
    			| distance |
    			distance := atom distanceFrom: aPoint.
    			collection add: distance -> (Array with: atom with: index)].
    	collection := collection asSortedCollection: [:d1 :d2 | d1 < d2].
    	^collection
  53. exceptHydrogen [accessing] xrefs
    	^exceptHydrogen = true
  54. exceptHydrogen: aBoolean [accessing] xrefs
     
    	exceptHydrogen := aBoolean = true
  55. frontierPoint: aLine rejectedBy: aBall [frontier] xrefs
     
    	| incrementValue firstDistance firstPoint lastDistance lastPoint |
    	firstPoint := aLine first.
    	lastPoint := aLine last.
    	(firstPoint distance: lastPoint) < self defaultFrontierMinimumDistance 
    		ifTrue: [^firstPoint center: lastPoint].
    	incrementValue := 0.5.
    	(0 to: 1 - incrementValue by: incrementValue) 
    		with: (0 + incrementValue to: 1 by: incrementValue)
    		do: 
    			[:firstT :lastT | 
    			firstDistance := (firstPoint := aLine atT: firstT) distance: aBall center.
    			lastDistance := (lastPoint := aLine atT: lastT) distance: aBall center.
    			(aBall radius between: (firstDistance min: lastDistance)
    				and: (firstDistance max: lastDistance)) 
    					ifTrue: [^self frontierPoint: (firstPoint to: lastPoint) rejectedBy: aBall]].
    	^firstPoint center: lastPoint
  56. frontierPolygons: aPolygon of: atomObject offset: offsetValue [frontier] xrefs
     
    	| aTriangle triangleCollection intersectedAtoms aBall aCollection frontierPolygons |
    	aTriangle := Jun3dTriangle 
    				on: (aPolygon vertexes at: 1)
    				on: (aPolygon vertexes at: 2)
    				on: (aPolygon vertexes at: 3).
    	aBall := Jun3dBoundingBall center: atomObject atomicPoint
    				radius: atomObject atomicRadius + offsetValue.
    	intersectedAtoms := self atomObjects select: 
    					[:eachAtom | 
    					(eachAtom = atomObject) not and: 
    							[aBall intersects: (Jun3dBoundingBall center: eachAtom atomicPoint
    										radius: eachAtom atomicRadius + offsetValue)]].
    	triangleCollection := OrderedCollection with: aTriangle.
    	intersectedAtoms do: 
    			[:eachAtom | 
    			aBall := Jun3dBoundingBall center: eachAtom atomicPoint
    						radius: eachAtom atomicRadius + offsetValue.
    			aCollection := OrderedCollection new.
    			triangleCollection do: 
    					[:eachTriangle | 
    					aCollection 
    						addAll: (self frontierTriangles: eachTriangle rejectedBy: aBall)].
    			triangleCollection := aCollection].
    	frontierPolygons := triangleCollection collect: 
    					[:eachTriangle | 
    					(JunOpenGL3dPolygon vertexes: (Array 
    								with: eachTriangle p1
    								with: eachTriangle p2
    								with: eachTriangle p3))
    						paint: aPolygon paint;
    						yourself].
    	^frontierPolygons
  57. frontierTriangles: aTriangle rejectedBy: aBall [frontier] xrefs
     
    	| aCollection trueCollection falseCollection firstPoint secondPoint thirdPoint aPoint aLine aPlane aTable |
    	aCollection := (Array 
    				with: aTriangle first
    				with: aTriangle second
    				with: aTriangle third) 
    					collect: [:eachPoint | (aBall containsPoint: eachPoint) -> eachPoint].
    	trueCollection := aCollection 
    				select: [:anAssociation | anAssociation key = true].
    	falseCollection := aCollection 
    				select: [:anAssociation | anAssociation key = false].
    	trueCollection size = 3 ifTrue: [^Array new].
    	falseCollection size = 3 ifTrue: [^Array with: aTriangle].
    	firstPoint := nil.
    	secondPoint := nil.
    	thirdPoint := nil.
    	trueCollection size = 2 
    		ifTrue: 
    			[firstPoint := falseCollection first value.
    			secondPoint := trueCollection first value.
    			thirdPoint := trueCollection last value].
    	falseCollection size = 2 
    		ifTrue: 
    			[firstPoint := trueCollection first value.
    			secondPoint := falseCollection first value.
    			thirdPoint := falseCollection last value].
    	secondPoint := self frontierPoint: (firstPoint to: secondPoint)
    				rejectedBy: aBall.
    	thirdPoint := self frontierPoint: (firstPoint to: thirdPoint)
    				rejectedBy: aBall.
    	aPoint := secondPoint center: thirdPoint.
    	aLine := aBall center to: aPoint.
    	aPoint := aLine atT: self defaultFrontierRevisedCoeffcient.
    	aPlane := aPoint plane: aLine normalUnitVector.
    	aTable := aTriangle tableDividedBy: aPlane.
    	^aTable at: #positives
  58. hasHydroxyl: atomObject [testing] xrefs
     
    	"
    	*-OH
    	^
    	"
    
    	| aTable |
    	aTable := self connectedAtomsAndConnectionsWith: atomObject.
    	aTable keysAndValuesDo: 
    			[:connectedAtom :connectedBond | 
    			(connectedBond isSingle and: [connectedAtom isOxygen]) 
    				ifTrue: [^self isHydroxyl: connectedAtom]].
    	^false
  59. informationString [accessing] xrefs
    	| aStream aCollection aString |
    	self
    		assert: [aStream := String new writeStream]
    		do: 
    			[aStream nextPutAll: super informationString.
    			aStream tab.
    			aStream nextPutAll: (#chemoJun_number_of_atoms__ >> 'number of atoms: ') asString.
    			aStream nextPutAll: self numberOfAtoms printString.
    			aStream cr.
    			aStream tab.
    			aStream nextPutAll: (#chemoJun_number_of_connections__ >> 'number of connections: ') asString.
    			aStream nextPutAll: self numberOfConnections printString.
    			aStream cr.
    			aStream tab.
    			aStream nextPutAll: (#chemoJun_atoms__ >> 'atoms: ') asString.
    			aCollection := self atomTable associations asSortedCollection.
    			aCollection with: (1 to: aCollection size)
    				do: 
    					[:assoc :index | 
    					aStream nextPutAll: assoc key asString.
    					aStream space.
    					aStream nextPutAll: assoc value printString.
    					index < aCollection size ifTrue: [aStream nextPutAll: ', ']].
    			aStream cr.
    			aStream tab.
    			aStream nextPutAll: (#chemoJun_connections__ >> 'connections: ') asString.
    			aCollection := self connectionTable associations asSortedCollection.
    			aCollection with: (1 to: aCollection size)
    				do: 
    					[:assoc :index | 
    					aStream nextPutAll: assoc key asString.
    					aStream space.
    					aStream nextPutAll: assoc value printString.
    					index < aCollection size ifTrue: [aStream nextPutAll: ', ']].
    			aStream cr]
    		ensure: 
    			[aString := aStream contents.
    			aStream close].
    	^aString
  60. initialize [initialize-release] xrefs
    	super initialize.
    	atomObjects := nil.
    	atomConnections := nil.
    	atomResolution := nil.
    	exceptHydrogen := self class defaultExceptHydrogen.
    	attributeTable := nil
  61. is2d [testing] xrefs
    	self fileName ifNil: [^false].
    	^(self default2dMolfilePatterns detect: 
    			[:patternString | 
    			JunStringUtility stringMatch: self fileName asString asLowercase
    				and: patternString asLowercase]
    		ifNone: [nil]) notNil
  62. is3d [testing] xrefs
    	^self is2d not
  63. isAldehyde: atomObject [testing] xrefs
     
    	"
    	-CHO
    	 ^
    	"
    
    	| aBoolean |
    	aBoolean := false.
    	atomObject isCarbon 
    		ifTrue: 
    			[| aTable |
    			aTable := self connectedAtomsAndConnectionsWith: atomObject.
    			aTable keysAndValuesDo: 
    					[:connectedAtom :connectedBond | 
    					(connectedBond isDouble and: [connectedAtom isOxygen]) 
    						ifTrue: [aBoolean := true]]].
    	(aBoolean and: [(self numberOfHydrogens: atomObject) = 1]) ifTrue: [^true].
    	^false
  64. isAmino: atomObject [testing] xrefs
     
    	"
    	-NH2 or -NH
    	 ^       ^
    	"
    
    	(atomObject isNitrogen and: 
    			[(self numberOfHydrogens: atomObject) = 2 
    				or: [(self numberOfHydrogens: atomObject) = 1]]) 
    		ifTrue: [^true].
    	^false
  65. isCarbonyl: atomObject [testing] xrefs
     
    	"
    	-C=O
    	 ^
    	"
    
    	(self isCarboxyl: atomObject) ifTrue: [^false].
    	(self isAldehyde: atomObject) ifTrue: [^false].
    	atomObject isCarbon 
    		ifTrue: 
    			[| aTable |
    			aTable := self connectedAtomsAndConnectionsWith: atomObject.
    			aTable keysAndValuesDo: 
    					[:connectedAtom :connectedBond | 
    					(connectedBond isDouble and: [connectedAtom isOxygen]) ifTrue: [^true]]].
    	^false
  66. isCarboxyl: atomObject [testing] xrefs
     
    	"
    	-COOH
    	 ^
    	"
    
    	| aBoolean |
    	aBoolean := false.
    	atomObject isCarbon 
    		ifTrue: 
    			[| aTable |
    			aTable := self connectedAtomsAndConnectionsWith: atomObject.
    			aTable keysAndValuesDo: 
    					[:connectedAtom :connectedBond | 
    					(connectedBond isDouble and: [connectedAtom isOxygen]) 
    						ifTrue: [aBoolean := true]]].
    	(aBoolean and: [self hasHydroxyl: atomObject]) ifTrue: [^true].
    	^false
  67. isHydroxyl: atomObject [testing] xrefs
     
    	"
    	-OH
    	 ^
    	"
    
    	(atomObject isOxygen and: [(self numberOfHydrogens: atomObject) = 1]) 
    		ifTrue: [^true].
    	^false
  68. isMethyl: atomObject [testing] xrefs
     
    	"
    	-CH3
    	 ^  
    	"
    
    	(atomObject isCarbon and: [(self numberOfHydrogens: atomObject) = 3]) 
    		ifTrue: [^true].
    	^false
  69. isSulfanyl: atomObject [testing] xrefs
     
    	"
    	-SH
    	 ^
    	"
    
    	(atomObject isSulfur and: [(self numberOfHydrogens: atomObject) = 1]) 
    		ifTrue: [^true].
    	^false
  70. modifierAssociation: atomObject normalPresentation: aBoolean [private] xrefs
     
    	| anAssociation fakeNumberOfHydrogens |
    	anAssociation := atomObject atomicSymbol asString -> 1.
    	fakeNumberOfHydrogens := (self numberOfHydrogensTable: atomObject) 
    				at: #fakeNumberOfHydrogens.
    	aBoolean 
    		ifTrue: 
    			[(self isMethyl: atomObject) 
    				ifTrue: 
    					[fakeNumberOfHydrogens = 0 ifTrue: [anAssociation := 'C' -> 1].
    					fakeNumberOfHydrogens = 1 ifTrue: [anAssociation := 'CH' -> 1].
    					fakeNumberOfHydrogens = 2 ifTrue: [anAssociation := 'CH2' -> 1].
    					fakeNumberOfHydrogens = 3 ifTrue: [anAssociation := 'CH3' -> 1]].
    			(self isHydroxyl: atomObject) 
    				ifTrue: 
    					[fakeNumberOfHydrogens = 0 ifTrue: [anAssociation := 'O' -> 1].
    					fakeNumberOfHydrogens = 1 ifTrue: [anAssociation := 'OH' -> 1]].
    			(self isAmino: atomObject) 
    				ifTrue: 
    					[fakeNumberOfHydrogens = 0 ifTrue: [anAssociation := 'N' -> 1].
    					fakeNumberOfHydrogens = 1 ifTrue: [anAssociation := 'NH' -> 1].
    					fakeNumberOfHydrogens = 2 ifTrue: [anAssociation := 'NH2' -> 1]].
    			(self isSulfanyl: atomObject) 
    				ifTrue: 
    					[fakeNumberOfHydrogens = 0 ifTrue: [anAssociation := 'S' -> 1].
    					fakeNumberOfHydrogens = 1 ifTrue: [anAssociation := 'SH' -> 1]]]
    		ifFalse: 
    			[(self isMethyl: atomObject) 
    				ifTrue: 
    					[fakeNumberOfHydrogens = 0 ifTrue: [anAssociation := 'C' -> 1].
    					fakeNumberOfHydrogens = 1 ifTrue: [anAssociation := 'HC' -> 2].
    					fakeNumberOfHydrogens = 2 ifTrue: [anAssociation := 'H2C' -> 3].
    					fakeNumberOfHydrogens = 3 ifTrue: [anAssociation := 'H3C' -> 3]].
    			(self isHydroxyl: atomObject) 
    				ifTrue: 
    					[fakeNumberOfHydrogens = 0 ifTrue: [anAssociation := 'O' -> 1].
    					fakeNumberOfHydrogens = 1 ifTrue: [anAssociation := 'HO' -> 2]].
    			(self isAmino: atomObject) 
    				ifTrue: 
    					[fakeNumberOfHydrogens = 0 ifTrue: [anAssociation := 'N' -> 1].
    					fakeNumberOfHydrogens = 1 ifTrue: [anAssociation := 'HN' -> 2].
    					fakeNumberOfHydrogens = 2 ifTrue: [anAssociation := 'H2N' -> 3]].
    			(self isSulfanyl: atomObject) 
    				ifTrue: 
    					[fakeNumberOfHydrogens = 0 ifTrue: [anAssociation := 'S' -> 1].
    					fakeNumberOfHydrogens = 1 ifTrue: [anAssociation := 'HS' -> 2]]].
    	^anAssociation
  71. moleculeAsBallAndStick [3d accessing] xrefs
    	self atomResolution = #low 
    		ifTrue: [^self moleculeAsBallAndStick: self defaultTubeDivisionNumberLow].
    	self atomResolution = #medium 
    		ifTrue: 
    			[^self moleculeAsBallAndStick: self defaultTubeDivisionNumberMedium].
    	self atomResolution = #high 
    		ifTrue: [^self moleculeAsBallAndStick: self defaultTubeDivisionNumberHigh].
    	^self moleculeAsBallAndStick: self defaultTubeDivisionNumber
  72. moleculeAsBallAndStick: divisionNumber [3d accessing] xrefs
     
    	| aBall compoundObject |
    	aBall := nil.
    	divisionNumber = self defaultTubeDivisionNumberLow 
    		ifTrue: [aBall := JunOpenGL3dObject ball: self defaultBallDivisionNumberLow].
    	divisionNumber = self defaultTubeDivisionNumberMedium 
    		ifTrue: 
    			[aBall := JunOpenGL3dObject ball: self defaultBallDivisionNumberMedium].
    	divisionNumber = self defaultTubeDivisionNumberHigh 
    		ifTrue: [aBall := JunOpenGL3dObject ball: self defaultBallDivisionNumberHigh].
    	aBall isNil 
    		ifTrue: [aBall := JunOpenGL3dObject ball: self defaultBallDivisionNumberLow].
    	compoundObject := self moleculeAsStick: divisionNumber.
    	self atomObjectsDo: 
    			[:atomObject | 
    			(atomObject isHydrogen and: [self exceptHydrogen]) 
    				ifFalse: 
    					[| centerPoint radiusValue colorValue aTransformation aSphere |
    					centerPoint := atomObject atomicPoint.
    					radiusValue := atomObject atomicRadius * (1 / 8).
    					colorValue := atomObject atomicColor blendWith: ColorValue white.
    					aTransformation := (Jun3dTransformation 
    								scale: radiusValue , radiusValue , radiusValue) 
    									product: (Jun3dTransformation translate: centerPoint).
    					aSphere := aBall transform: aTransformation.
    					aSphere polygonsDo: 
    							[:polygon | 
    							polygon normalVectors: (polygon vertexes 
    										collect: [:p | (centerPoint to: p) normalUnitVector])].
    					aSphere paint: colorValue.
    					compoundObject add: aSphere]].
    	^compoundObject
  73. moleculeAsPlane [3d accessing] xrefs
    	| compoundObject bondTypeSymbol firstPolylines secondPolylines thirdPolylines stereoTypeSymbol |
    	compoundObject := JunOpenGL3dCompoundObject new.
    	self atomConnections do: 
    			[:atomConnection | 
    			bondTypeSymbol := atomConnection bondTypeSymbol.
    			bondTypeSymbol = #single 
    				ifTrue: 
    					[| anArray |
    					anArray := self arrayOfPolylinesForSingleBondAsPlane: atomConnection.
    					firstPolylines := anArray at: 1].
    			bondTypeSymbol = #double 
    				ifTrue: 
    					[| anArray |
    					anArray := self arrayOfPolylinesForDoubleBondAsPlane: atomConnection.
    					firstPolylines := anArray at: 1.
    					secondPolylines := anArray at: 2].
    			bondTypeSymbol = #triple 
    				ifTrue: 
    					[| anArray |
    					anArray := self arrayOfPolylinesForTripleBondAsPlane: atomConnection.
    					firstPolylines := anArray at: 1.
    					secondPolylines := anArray at: 2.
    					thirdPolylines := anArray at: 3].
    			bondTypeSymbol = #aromatic 
    				ifTrue: 
    					[| anArray |
    					anArray := self arrayOfPolylinesForAromaticBondAsPlane: atomConnection.
    					firstPolylines := anArray at: 1.
    					secondPolylines := anArray at: 2].
    			stereoTypeSymbol := atomConnection stereoTypeSymbol.
    			(stereoTypeSymbol = #up or: [stereoTypeSymbol = #down]) 
    				ifTrue: 
    					[(stereoTypeSymbol = #up or: [stereoTypeSymbol = #down]) 
    						ifTrue: 
    							[firstPolylines do: [:each | each lineWidth: 4].
    							stereoTypeSymbol = #down 
    								ifTrue: [firstPolylines do: [:each | each halftone: 0.25]]]].
    			((atomConnection fromAtom isHydrogen 
    				or: [atomConnection toAtom isHydrogen]) and: [self exceptHydrogen]) 
    				ifFalse: 
    					[compoundObject addAll: firstPolylines.
    					bondTypeSymbol = #double ifTrue: [compoundObject addAll: secondPolylines].
    					bondTypeSymbol = #triple 
    						ifTrue: 
    							[compoundObject addAll: secondPolylines.
    							compoundObject addAll: thirdPolylines].
    					bondTypeSymbol = #aromatic 
    						ifTrue: [compoundObject addAll: secondPolylines]]].
    	^compoundObject
  74. moleculeAsSpaceFill [3d accessing] xrefs
    	^self moleculeAsSpaceFill: self defaultSpaceFillDivisionNumber
  75. moleculeAsSpaceFill: divisionNumber [3d accessing] xrefs
     
    	^self moleculeAsSpaceFill: divisionNumber offsetValue: 0
  76. moleculeAsSpaceFill: divisionNumber offsetValue: offsetValue [3d accessing] xrefs
     
    	^self 
    		moleculeAsSpaceFill: divisionNumber
    		offsetValue: offsetValue
    		smoothShading: true
  77. moleculeAsSpaceFill: divisionNumber offsetValue: offsetValue smoothShading: aBoolean [3d accessing] xrefs
     
    	| aBall areaCoefficient compoundObject |
    	aBall := JunOpenGL3dObject ball: divisionNumber.
    	areaCoefficient := (Jun3dBoundingBall center: 0 , 0 , 0 radius: 1) area 
    				/ aBall area.
    	compoundObject := JunOpenGL3dCompoundObject new.
    	self atomObjectsDo: 
    			[:atomObject | 
    			| centerPoint radiusValue colorValue aTransformation aSphere aBody |
    			centerPoint := atomObject atomicPoint.
    			radiusValue := atomObject atomicRadius + offsetValue.
    			colorValue := atomObject atomicColor blendWith: ColorValue white.
    			aTransformation := (Jun3dTransformation 
    						scale: radiusValue , radiusValue , radiusValue) 
    							product: (Jun3dTransformation translate: centerPoint).
    			aSphere := aBall transform: aTransformation.
    			aBody := JunOpenGL3dCompoundObject new.
    			aSphere polygonsDo: 
    					[:aPolygon | 
    					aBoolean 
    						ifTrue: 
    							[| collectionOfPolygons |
    							collectionOfPolygons := self 
    										frontierPolygons: aPolygon
    										of: atomObject
    										offset: offsetValue.
    							collectionOfPolygons do: 
    									[:each | 
    									each colors: (Array new: each vertexes size withAll: colorValue).
    									each 
    										normalVectors: (each vertexes 
    												collect: [:p | (atomObject atomicPoint to: p) normalUnitVector]) asArray].
    							aBody addAll: collectionOfPolygons]
    						ifFalse: 
    							[aPolygon paint: colorValue.
    							aBody addAll: (self 
    										frontierPolygons: aPolygon
    										of: atomObject
    										offset: offsetValue)]].
    			atomObject atomicBody: aBody.
    			atomObject areaCoefficient: areaCoefficient.
    			compoundObject add: aBody].
    	^compoundObject
  78. moleculeAsStick [3d accessing] xrefs
    	self atomResolution = #low 
    		ifTrue: [^self moleculeAsStick: self defaultTubeDivisionNumberLow].
    	self atomResolution = #medium 
    		ifTrue: [^self moleculeAsStick: self defaultTubeDivisionNumberMedium].
    	self atomResolution = #high 
    		ifTrue: [^self moleculeAsStick: self defaultTubeDivisionNumberHigh].
    	^self moleculeAsStick: self defaultTubeDivisionNumber
  79. moleculeAsStick: divisionNumber [3d accessing] xrefs
     
    	| compoundObject |
    	compoundObject := JunOpenGL3dCompoundObject new.
    	self atomConnections do: 
    			[:atomConnection | 
    			| aSymbol fromPoint toPoint midPoint aCylinder aColor aPoint |
    			aSymbol := atomConnection bondTypeSymbol.
    			fromPoint := atomConnection fromAtom atomicPoint.
    			toPoint := atomConnection toAtom atomicPoint.
    			midPoint := (toPoint - fromPoint) / 2 + fromPoint.
    			aCylinder := JunOpenGL3dObject 
    						cylinderFrom: fromPoint
    						to: midPoint
    						radius: self defaultBondThickness / 2
    						by: divisionNumber.
    			atomConnection hasConnectionColor 
    				ifTrue: [aColor := atomConnection connectionColor]
    				ifFalse: [aColor := atomConnection fromAtom atomicColor].
    			aCylinder polygonsDo: [:aPolygon | aPolygon paint: aColor].
    			((atomConnection fromAtom isHydrogen 
    				or: [atomConnection toAtom isHydrogen]) and: [self exceptHydrogen]) 
    				ifFalse: 
    					[aSymbol = #single ifTrue: [compoundObject add: aCylinder].
    					aSymbol = #double 
    						ifTrue: 
    							[aPoint := self translationOffsetOf: atomConnection.
    							compoundObject add: (aCylinder translatedBy: aPoint).
    							compoundObject add: (aCylinder translatedBy: aPoint negated)].
    					aSymbol = #triple 
    						ifTrue: 
    							[aPoint := self translationOffsetOf: atomConnection.
    							compoundObject add: (aCylinder translatedBy: aPoint).
    							compoundObject add: aCylinder.
    							compoundObject add: (aCylinder translatedBy: aPoint negated)].
    					aSymbol = #aromatic 
    						ifTrue: 
    							[aPoint := self translationOffsetOf: atomConnection.
    							compoundObject add: (aCylinder translatedBy: aPoint).
    							aCylinder := JunOpenGL3dObject 
    										cylinderFrom: fromPoint
    										to: midPoint
    										radius: self defaultBondThickness / 6
    										by: divisionNumber.
    							aCylinder polygonsDo: [:aPolygon | aPolygon paint: aColor].
    							compoundObject add: (aCylinder translatedBy: aPoint negated)]].
    			aCylinder := JunOpenGL3dObject 
    						cylinderFrom: midPoint
    						to: toPoint
    						radius: self defaultBondThickness / 2
    						by: divisionNumber.
    			atomConnection hasConnectionColor 
    				ifTrue: [aColor := atomConnection connectionColor]
    				ifFalse: [aColor := atomConnection toAtom atomicColor].
    			aCylinder polygonsDo: [:aPolygon | aPolygon paint: aColor].
    			((atomConnection toAtom isHydrogen 
    				or: [atomConnection fromAtom isHydrogen]) and: [self exceptHydrogen]) 
    				ifFalse: 
    					[aSymbol = #single ifTrue: [compoundObject add: aCylinder].
    					aSymbol = #double 
    						ifTrue: 
    							[aPoint := self translationOffsetOf: atomConnection.
    							compoundObject add: (aCylinder translatedBy: aPoint).
    							compoundObject add: (aCylinder translatedBy: aPoint negated)].
    					aSymbol = #triple 
    						ifTrue: 
    							[aPoint := self translationOffsetOf: atomConnection.
    							compoundObject add: (aCylinder translatedBy: aPoint).
    							compoundObject add: aCylinder.
    							compoundObject add: (aCylinder translatedBy: aPoint negated)].
    					aSymbol = #aromatic 
    						ifTrue: 
    							[aPoint := self translationOffsetOf: atomConnection.
    							compoundObject add: (aCylinder translatedBy: aPoint).
    							aCylinder := JunOpenGL3dObject 
    										cylinderFrom: midPoint
    										to: toPoint
    										radius: self defaultBondThickness / 3
    										by: divisionNumber.
    							aCylinder polygonsDo: [:aPolygon | aPolygon paint: aColor].
    							compoundObject add: (aCylinder translatedBy: aPoint negated)]]].
    	^compoundObject
  80. moleculeAsStickAndSpaceFill [3d accessing] xrefs
    	| molecule3dObject skeleton3dObject |
    	molecule3dObject := self moleculeAsSpaceFill.
    	molecule3dObject polygonsDo: [:polygon | polygon halftone: self defaultHalftoneValue].
    	skeleton3dObject := self moleculeAsStick.
    	skeleton3dObject components do: [:each | molecule3dObject add: each].
    	^molecule3dObject
  81. molfileHeaderBlock [attribute accessing] xrefs
    	^self attributeTable at: #molfileHeaderBlock
    		ifAbsent: 
    			[OrderedCollection 
    				with: (String with: Character cr)
    				with: (String with: Character cr)
    				with: (String with: Character cr)]
  82. molfileHeaderBlock: aCollection [attribute accessing] xrefs
     
    	self attributeTable at: #molfileHeaderBlock
    		put: aCollection asOrderedCollection
  83. numberOfAtoms [accessing atom] xrefs
    	^self atomObjects size
  84. numberOfConnections [accessing connection] xrefs
    	^self atomConnections size
  85. numberOfHydrogens: atomObject [accessing] xrefs
     
    	^(self numberOfHydrogensTable: atomObject) at: #numberOfHydrogens
  86. numberOfHydrogensTable: atomObject [private] xrefs
     
    	| aTable numberOfBonds realNumberOfHydrogens fakeNumberOfHydrogens numberOfHydrogens numberOfConnections |
    	aTable := self connectedAtomsAndConnectionsWith: atomObject.
    	numberOfBonds := self defaultAtomObjectClass 
    				atomicBondsAt: atomObject atomicSymbol.
    	realNumberOfHydrogens := 0.
    	fakeNumberOfHydrogens := 0.
    	numberOfHydrogens := 0.
    	numberOfConnections := 0.
    	aTable keysAndValuesDo: 
    			[:connectedAtom :connectedBond | 
    			connectedAtom isHydrogen 
    				ifTrue: [realNumberOfHydrogens := realNumberOfHydrogens + 1].
    			numberOfConnections := numberOfConnections + connectedBond bondType].
    	fakeNumberOfHydrogens := numberOfBonds - numberOfConnections.
    	numberOfHydrogens := realNumberOfHydrogens + fakeNumberOfHydrogens.
    	^(Dictionary new)
    		add: #numberOfHydrogens -> numberOfHydrogens;
    		add: #realNumberOfHydrogens -> realNumberOfHydrogens;
    		add: #fakeNumberOfHydrogens -> fakeNumberOfHydrogens;
    		yourself
  87. numberOfNitrogens: atomObject [accessing] xrefs
     
    	| aTable numberOfNitrogens |
    	aTable := self connectedAtomsAndConnectionsWith: atomObject.
    	numberOfNitrogens := 0.
    	aTable keysAndValuesDo: 
    			[:connectedAtom :connectedBond | 
    			connectedAtom isNitrogen 
    				ifTrue: [numberOfNitrogens := numberOfNitrogens + 1]].
    	^numberOfNitrogens
  88. numberOfOxygens: atomObject [accessing] xrefs
     
    	| aTable numberOfOxygens |
    	aTable := self connectedAtomsAndConnectionsWith: atomObject.
    	numberOfOxygens := 0.
    	aTable keysAndValuesDo: 
    			[:connectedAtom :connectedBond | 
    			connectedAtom isOxygen ifTrue: [numberOfOxygens := numberOfOxygens + 1]].
    	^numberOfOxygens
  89. postCopy [copying] xrefs
    	| aTable |
    	super postCopy.
    	aTable := Dictionary new.
    	self atomObjects do: [:each | aTable at: each put: each copy].
    	atomObjects := self atomObjects collect: [:each | aTable at: each].
    	atomConnections := self atomConnections collect: [:each | each copy].
    	atomConnections do: 
    			[:each | 
    			each fromAtom: (aTable at: each fromAtom).
    			each toAtom: (aTable at: each toAtom)].
    	attributeTable := attributeTable copy
  90. surfaceInformationString [accessing] xrefs
    	| aStream aString |
    	self 
    		assert: [aStream := String new writeStream]
    		do: 
    			[aStream 
    				nextPutAll: (#chemoJun_Surface_Information_ >> 'Surface Information:') asString.
    			aStream cr.
    			self atomObjectsAndIndexesDo: 
    					[:atomObject :atomIndex | 
    					aStream tab.
    					aStream nextPutAll: atomIndex printString , ':'.
    					aStream space.
    					aStream nextPutAll: atomObject atomicSymbol.
    					aStream space.
    					aStream nextPutAll: '('.
    					aStream 
    						nextPutAll: (atomObject atomicArea roundTo: 0.1) asFloat printString.
    					aStream nextPutAll: ' = '.
    					aStream 
    						nextPutAll: (atomObject interierArea roundTo: 0.1) asFloat printString.
    					aStream nextPutAll: ' + '.
    					aStream 
    						nextPutAll: (atomObject frontierArea roundTo: 0.1) asFloat printString.
    					aStream nextPutAll: ')'.
    					aStream cr]]
    		ensure: 
    			[aString := aStream contents.
    			aStream close].
    	^aString
  91. translationOffsetOf: atomConnection [3d aux] xrefs
     
    	| translationOffset aSymbol connectedAtoms anotherAtom aLine aPoint aPlane aCollection |
    	translationOffset := 0 , 0 , 0.
    	aSymbol := atomConnection bondTypeSymbol.
    	aSymbol = #single ifTrue: [translationOffset := 0 , 0 , 0].
    	(aSymbol = #double or: [aSymbol = #triple]) 
    		ifTrue: 
    			[aSymbol = #double 
    				ifTrue: [translationOffset := 0 , 0 , 0.075]
    				ifFalse: [translationOffset := 0 , 0 , 0.1].
    			connectedAtoms := Set new.
    			connectedAtoms 
    				addAll: ((self connectedAtomsWith: atomConnection fromAtom) 
    						reject: [:each | each = atomConnection fromAtom or: [each = atomConnection toAtom]]).
    			connectedAtoms addAll: ((self connectedAtomsWith: atomConnection toAtom) 
    						reject: [:each | each = atomConnection fromAtom or: [each = atomConnection toAtom]]).
    			connectedAtoms := connectedAtoms asArray.
    			connectedAtoms isEmpty 
    				ifFalse: 
    					[anotherAtom := connectedAtoms first.
    					aLine := atomConnection fromAtom atomicPoint 
    								to: atomConnection toAtom atomicPoint.
    					aPoint := aLine nearestPointFromPoint: anotherAtom atomicPoint.
    					(aPoint distance: anotherAtom atomicPoint) < JunGeometry accuracy 
    						ifFalse: 
    							[aLine := aPoint to: anotherAtom atomicPoint.
    							aPoint := aLine normalUnitVector.
    							aSymbol = #double 
    								ifTrue: [translationOffset := aPoint * 0.075]
    								ifFalse: [translationOffset := aPoint * 0.1]]]].
    	aSymbol = #aromatic 
    		ifTrue: 
    			[translationOffset := 0 , 0 , 0.075.
    			connectedAtoms := Set new.
    			connectedAtoms 
    				addAll: ((self connectedAtomsWith: atomConnection fromAtom) 
    						reject: [:each | each = atomConnection fromAtom or: [each = atomConnection toAtom]]).
    			connectedAtoms addAll: ((self connectedAtomsWith: atomConnection toAtom) 
    						reject: [:each | each = atomConnection fromAtom or: [each = atomConnection toAtom]]).
    			connectedAtoms := connectedAtoms asArray select: 
    							[:each | 
    							((self connectionsWith: each) 
    								detect: [:it | it bondTypeSymbol = #aromatic]
    								ifNone: [nil]) notNil].
    			connectedAtoms isEmpty 
    				ifFalse: 
    					[anotherAtom := connectedAtoms first.
    					connectedAtoms size < 2 
    						ifTrue: 
    							[aLine := atomConnection fromAtom atomicPoint 
    										to: atomConnection toAtom atomicPoint.
    							aPoint := aLine nearestPointFromPoint: anotherAtom atomicPoint.
    							aLine := aPoint to: anotherAtom atomicPoint.
    							aPoint := aLine normalUnitVector]
    						ifFalse: 
    							[aPlane := atomConnection fromAtom atomicPoint 
    										plane: atomConnection toAtom atomicPoint
    										and: anotherAtom atomicPoint.
    							aPlane := atomConnection fromAtom atomicPoint 
    										plane: atomConnection toAtom atomicPoint
    										and: atomConnection toAtom atomicPoint + aPlane normalUnitVector.
    							aCollection := connectedAtoms 
    										select: [:each | (each atomicPoint whichSideOf: aPlane) >= 0].
    							aCollection size > 1 
    								ifFalse: 
    									[aCollection := connectedAtoms 
    												select: [:each | (each atomicPoint whichSideOf: aPlane) < 0]].
    							aCollection isEmpty ifFalse: [anotherAtom := aCollection first].
    							aLine := atomConnection fromAtom atomicPoint 
    										to: atomConnection toAtom atomicPoint.
    							aPoint := aLine nearestPointFromPoint: anotherAtom atomicPoint.
    							aLine := anotherAtom atomicPoint to: aPoint.
    							aPoint := aLine normalUnitVector].
    					translationOffset := aPoint * 0.075]].
    	^translationOffset

class methods:

  1. copyright [copyright] xrefs
    	^'ChemoJun050 (2006/08/08) Copyright 2002-2006 National Institute of Informatics, Research Organization of Information and Systems.'
  2. defaultAtomConnectionClass [defaults] xrefs
    	^ChemoJunAtomConnection
  3. defaultAtomObjectClass [defaults] xrefs
    	^ChemoJunAtomObject
  4. defaultExceptHydrogen [defaults] xrefs
    	^false
  5. defaultGraphClass [defaults] xrefs
    	^ChemoJunGraph
  6. defaultGrapherClass [defaults] xrefs
    	^ChemoJunGrapher
  7. defaultMolFileReaderClass [defaults] xrefs
    	^ChemoJunMolFileReader
  8. example1 [examples] xrefs
    	"ChemoJunMoleculeObject example1."
    
    	| moleculeObject |
    	moleculeObject := ChemoJunMoleculeObject request.
    	moleculeObject isNil ifTrue: [^nil].
    	^moleculeObject
  9. example2 [examples] xrefs
    	"ChemoJunMoleculeObject example2."
    
    	| moleculeObject |
    	moleculeObject := ChemoJunMoleculeObject request.
    	moleculeObject isNil ifTrue: [^nil].
    	ChemoJunAbstractViewer show: moleculeObject moleculeAsStick.
    	^moleculeObject
  10. example3 [examples] xrefs
    	"ChemoJunMoleculeObject example3."
    
    	| moleculeObject |
    	moleculeObject := ChemoJunMoleculeObject request.
    	moleculeObject isNil ifTrue: [^nil].
    	moleculeObject exceptHydrogen: true.
    	ChemoJunAbstractViewer show: moleculeObject moleculeAsStick.
    	^moleculeObject
  11. example4 [examples] xrefs
    	"ChemoJunMoleculeObject example4."
    
    	| moleculeObject |
    	moleculeObject := ChemoJunMoleculeObject request.
    	moleculeObject isNil ifTrue: [^nil].
    	ChemoJunAbstractViewer show: moleculeObject moleculeAsSpaceFill.
    	^moleculeObject
  12. example5 [examples] xrefs
    	"ChemoJunMoleculeObject example5."
    
    	| moleculeObject |
    	moleculeObject := ChemoJunMoleculeObject request.
    	moleculeObject isNil ifTrue: [^nil].
    	ChemoJunAbstractViewer show: moleculeObject moleculeAsStickAndSpaceFill.
    	^moleculeObject
  13. example6 [examples] xrefs
    	"ChemoJunMoleculeObject example6."
    
    	| moleculeObject molecule3dObject offsetValue offset3dObject compoundObject |
    	moleculeObject := ChemoJunMoleculeObject request.
    	moleculeObject isNil ifTrue: [^nil].
    	molecule3dObject := moleculeObject moleculeAsSpaceFill.
    	offsetValue := 1.	"Angstrom"
    	offset3dObject := moleculeObject 
    				moleculeAsSpaceFill: moleculeObject defaultSpaceFillDivisionNumber
    				offsetValue: offsetValue.
    	offset3dObject polygonsDo: 
    			[:aPolygon | 
    			aPolygon paint: ColorValue lightGray.
    			aPolygon halftone: moleculeObject defaultHalftoneValue].
    	compoundObject := JunOpenGL3dCompoundObject new.
    	compoundObject add: molecule3dObject.
    	compoundObject add: offset3dObject.
    	ChemoJunAbstractViewer show: compoundObject.
    	^moleculeObject
  14. example7 [examples] xrefs
    	"ChemoJunMoleculeObject example7."
    
    	| moleculeObject molecule3dObject offsetValue offset3dObject compoundObject |
    	moleculeObject := ChemoJunMoleculeObject request.
    	moleculeObject isNil ifTrue: [^nil].
    	molecule3dObject := moleculeObject moleculeAsStickAndSpaceFill.
    	offsetValue := 1.	"Angstrom"
    	offset3dObject := moleculeObject 
    				moleculeAsSpaceFill: moleculeObject defaultSpaceFillDivisionNumber
    				offsetValue: offsetValue.
    	offset3dObject polygonsDo: 
    			[:aPolygon | 
    			aPolygon paint: ColorValue lightGray.
    			aPolygon halftone: moleculeObject defaultHalftoneValue / 2].
    	compoundObject := JunOpenGL3dCompoundObject new.
    	compoundObject add: molecule3dObject.
    	compoundObject add: offset3dObject.
    	ChemoJunAbstractViewer show: compoundObject.
    	^moleculeObject
  15. example8 [examples] xrefs
    	"ChemoJunMoleculeObject example8."
    
    	| firstMoleculeObject secondMoleculeObject firstMolecule3dObject secondMolecule3dObject compoundObject |
    	firstMoleculeObject := ChemoJunMoleculeObject request.
    	firstMoleculeObject isNil ifTrue: [^nil].
    	secondMoleculeObject := ChemoJunMoleculeObject request.
    	secondMoleculeObject isNil ifTrue: [^nil].
    	firstMolecule3dObject := firstMoleculeObject moleculeAsSpaceFill.
    	secondMolecule3dObject := secondMoleculeObject moleculeAsSpaceFill 
    				translatedBy: 0 , 10 , 0.
    	compoundObject := JunOpenGL3dCompoundObject new.
    	compoundObject add: firstMolecule3dObject.
    	compoundObject add: secondMolecule3dObject.
    	ChemoJunAbstractViewer show: compoundObject.
    	^Array with: firstMoleculeObject with: secondMoleculeObject
  16. example9 [examples] xrefs
    	"ChemoJunMoleculeObject example9."
    
    	| firstMoleculeObject secondMoleculeObject firstMolecule3dObject secondMolecule3dObject offsetValue firstOffset3dObject secondOffset3dObject compoundObject |
    	firstMoleculeObject := ChemoJunMoleculeObject request.
    	firstMoleculeObject isNil ifTrue: [^nil].
    	secondMoleculeObject := ChemoJunMoleculeObject request.
    	secondMoleculeObject isNil ifTrue: [^nil].
    	firstMolecule3dObject := firstMoleculeObject moleculeAsSpaceFill.
    	secondMolecule3dObject := secondMoleculeObject moleculeAsSpaceFill 
    				translatedBy: 0 , 10 , 0.
    	offsetValue := 1.	"Angstrom"
    	firstOffset3dObject := firstMoleculeObject 
    				moleculeAsSpaceFill: firstMoleculeObject 
    						defaultSpaceFillDivisionNumber
    				offsetValue: offsetValue.
    	firstOffset3dObject polygonsDo: 
    			[:aPolygon | 
    			aPolygon paint: ColorValue lightGray.
    			aPolygon halftone: firstMoleculeObject defaultHalftoneValue].
    	secondOffset3dObject := (secondMoleculeObject 
    				moleculeAsSpaceFill: secondMoleculeObject 
    						defaultSpaceFillDivisionNumber
    				offsetValue: offsetValue) translatedBy: 0 , 10 , 0.
    	secondOffset3dObject polygonsDo: 
    			[:aPolygon | 
    			aPolygon paint: ColorValue lightGray.
    			aPolygon halftone: secondMoleculeObject defaultHalftoneValue].
    	compoundObject := JunOpenGL3dCompoundObject new.
    	compoundObject add: firstMolecule3dObject.
    	compoundObject add: secondMolecule3dObject.
    	compoundObject add: firstOffset3dObject.
    	compoundObject add: secondOffset3dObject.
    	ChemoJunAbstractViewer show: compoundObject.
    	^Array with: firstMoleculeObject with: secondMoleculeObject
  17. exampleA [examples] xrefs
    	"ChemoJunMoleculeObject exampleA."
    
    	| moleculeObject moleculeViewer |
    	moleculeObject := ChemoJunMoleculeObject request.
    	moleculeObject isNil ifTrue: [^nil].
    	moleculeViewer := ChemoJunMoleculeViewer moleculeObject: moleculeObject.
    	moleculeViewer openAt: 100 @ 250.
    	^moleculeObject
  18. exampleB [examples] xrefs
    	"ChemoJunMoleculeObject exampleB."
    
    	| moleculeObject moleculeViewer messageSelectors |
    	moleculeObject := ChemoJunMoleculeObject request.
    	moleculeObject isNil ifTrue: [^nil].
    	moleculeViewer := ChemoJunMoleculeViewer moleculeObject: moleculeObject.
    	moleculeViewer indexExpression: '[:index | true]'.
    	moleculeViewer openAt: 100 @ 250.
    	messageSelectors := #(#isMethyl: #isHydroxyl: #isCarboxyl: #isCarbonyl: #isAldehyde: #hasHydroxyl:).
    	Transcript clear.
    	Transcript
    		show: 'Serial';
    		tab.
    	messageSelectors do: [:each | Transcript show: each asString]
    		separatedBy: [Transcript tab].
    	Transcript cr.
    	moleculeObject atomObjectsDo: 
    			[:atomObject | 
    			Transcript show: atomObject serialNumber printString.
    			Transcript tab.
    			messageSelectors do: 
    					[:each | 
    					Transcript 
    						show: (moleculeObject perform: each with: atomObject) printString]
    				separatedBy: [Transcript tab].
    			Transcript cr].
    	^moleculeObject
  19. fileName: aFilename [instance creation] xrefs
     
    	^self fromReader: (self defaultMolFileReaderClass fileName: aFilename)
  20. fromReader: aReader [instance creation] xrefs
     
    	^self moleculeObjectFromReader: aReader
  21. moleculeObjectFromReader: aReader [private] xrefs
     
    	| aStream atomObjects atomConnections moleculeObject |
    	JunControlUtility 
    		assert: [aStream := (Array new: aReader numberOfAtoms) writeStream]
    		do: 
    			[| atomObject |
    			1 to: aReader numberOfAtoms
    				do: 
    					[:index | 
    					| atom |
    					atom := aReader atomList at: index.
    					atomObject := self defaultAtomObjectClass atomicSymbol: atom first
    								atomicPoint: atom last.
    					atomObject serialNumber: index.
    					aStream nextPut: atomObject]]
    		ensure: 
    			[atomObjects := aStream contents.
    			aStream close].
    	JunControlUtility 
    		assert: [aStream := (Array new: aReader numberOfConnections) writeStream]
    		do: 
    			[| fromAtom toAtom bondType stereoType atomConnection |
    			1 to: aReader numberOfConnections
    				do: 
    					[:index | 
    					| connection |
    					connection := aReader connectionList at: index.
    					fromAtom := atomObjects at: (connection at: 1).
    					toAtom := atomObjects at: (connection at: 2).
    					connection size >= 3 
    						ifTrue: 
    							[bondType := connection at: 3.
    							connection size >= 4 
    								ifTrue: 
    									[stereoType := connection at: 4.
    									atomConnection := self defaultAtomConnectionClass 
    												fromAtom: fromAtom
    												toAtom: toAtom
    												bondType: bondType
    												stereoType: stereoType]
    								ifFalse: 
    									[atomConnection := self defaultAtomConnectionClass 
    												fromAtom: fromAtom
    												toAtom: toAtom
    												bondType: bondType]]
    						ifFalse: 
    							[atomConnection := self defaultAtomConnectionClass fromAtom: fromAtom
    										toAtom: toAtom].
    					aStream nextPut: atomConnection]]
    		ensure: 
    			[atomConnections := aStream contents.
    			aStream close].
    	moleculeObject := self new.
    	moleculeObject fileName: aReader fileName.
    	moleculeObject atomObjects: atomObjects.
    	moleculeObject atomConnections: atomConnections.
    	moleculeObject molfileHeaderBlock: aReader commentList.
    	^moleculeObject
  22. request [utilities] xrefs
    	"ChemoJunMoleculeObject request."
    
    	| aReader moleculeObject |
    	aReader := self defaultMolFileReaderClass request.
    	aReader isNil ifTrue: [^nil].
    	moleculeObject := self moleculeObjectFromReader: aReader.
    	^moleculeObject
  23. system [copyright] xrefs
    	^'ChemoJun'
  24. version [copyright] xrefs
    	^'050'

index xrefs