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