-
addSelection: catalogueElement [selecting]
self selections: self selections , (Array with: catalogueElement)
-
arrangeColumnSize [menu messages]
| numberOfColumns aString savedSelections |
self isEmpty ifTrue: [^nil].
numberOfColumns := self columnSize.
aString := JunDialog
request: (#chemoJun_How_many_column_size_ >> 'How many column size?')
asString
initialAnswer: numberOfColumns printString.
(aString isNil or: [aString isEmpty]) ifTrue: [^nil].
numberOfColumns := aString asNumber asInteger.
numberOfColumns < 1 ifTrue: [^nil].
self
assert: [savedSelections := self selections]
do: [self columnSize: numberOfColumns]
ensure: [self selections: savedSelections].
self fitWindowSize
-
asImage [converting]
| anImage aPixmap |
anImage := nil.
JunControlUtility
assert: [aPixmap := Pixmap extent: self boundingBox extent]
do:
[| graphicsContext |
graphicsContext := aPixmap graphicsContext.
graphicsContext paint: self backgroundColor.
graphicsContext displayRectangle: aPixmap bounds.
self displayOn: graphicsContext.
anImage := aPixmap asImage]
ensure: [aPixmap close].
^anImage
-
asImageOfElement: element [converting]
^self
asImageOfElement: element
selectionColor: self selectionColor
backgroundColor: self backgroundColor
-
asImageOfElement: element selectionColor: selectionColor backgroundColor: backgroundColor [converting]
| aPixmap anImage |
JunControlUtility
assert: [aPixmap := Pixmap extent: self pixmapExtent]
do:
[self
displayElement: element
index: (self elements indexOf: element)
into: aPixmap
selectionColor: selectionColor
backgroundColor: backgroundColor.
anImage := aPixmap asImage]
ensure: [aPixmap close].
^anImage
-
asImageOfElements: elements [converting]
^self
asImageOfElements: elements
selectionColor: self selectionColor
backgroundColor: self backgroundColor
-
asImageOfElements: elements selectionColor: selectionColor backgroundColor: backgroundColor [converting]
| numberOfLimit elementImages offsetPoint aPixmap aMask pixmapContext maskContext aPoint figureImage shapeImage |
numberOfLimit := 16.
elementImages := (elements
copyFrom: (elements size - (numberOfLimit - 1) max: 1)
to: elements size) collect:
[:element |
self
asImageOfElement: element
selectionColor: selectionColor
backgroundColor: backgroundColor].
offsetPoint := 13 @ 13.
JunControlUtility
assert:
[aPixmap := Pixmap extent: self pixmapExtent
+ (offsetPoint * (elementImages size - 1) asPoint).
aMask := Mask extent: aPixmap extent]
do:
[pixmapContext := aPixmap graphicsContext.
pixmapContext paint: ColorValue white.
pixmapContext displayRectangle: aPixmap bounds.
maskContext := aMask graphicsContext.
maskContext paint: CoverageValue transparent.
maskContext displayRectangle: aMask bounds.
maskContext paint: CoverageValue opaque.
aPoint := aPixmap bounds bottomLeft - (0 @ self pixmapExtent y).
elementImages do:
[:elementImage |
elementImage displayOn: pixmapContext at: aPoint.
maskContext displayRectangle: (aPoint extent: elementImage extent).
aPoint := aPoint + (offsetPoint x @ offsetPoint y negated)].
figureImage := aPixmap asImage.
shapeImage := aMask asImage]
ensure:
[aPixmap close.
aMask close].
^OpaqueImage figure: figureImage shape: shapeImage
-
backgroundColor [displaying]
^ColorValue
scaledRed: 7700
scaledGreen: 7700
scaledBlue: 7700
-
boundingBox [bounds accessing]
boundingBox ifNil: [boundingBox := Point zero extent: Point zero].
^boundingBox
-
browseManual [menu messages]
JunURL browse: (ChemoJunUtility
manualUriStringConstruct: 'ChemoJunMoleculeCatalogue/index.html')
-
catalogueElementsToLispList [lisp support]
| aList |
aList := JunLispCons cell.
aList head: #catalogueElements.
self elements collect: [:element | aList add: element toLispList].
^aList
-
catalogueView [interface opening]
| aView |
aView := self class defaultMolecueCatalogueViewClass model: self.
(aView controller)
menuHolder: [self yellowButtonMenu];
performer: self.
^aView
-
clearAndRedisplay [displaying]
self changed: #clearAndRedisplay.
self updateMenuIndication
-
clearSelections [selecting]
self selections: Array new
-
columnSize [accessing]
columnSize ifNil: [columnSize := self class defaultColumnSize].
^columnSize
-
columnSize: numberOfColumns [accessing]
columnSize := numberOfColumns.
self elements: self elements
-
columnSizeToLispList [lisp support]
| alist |
alist := JunLispCons cell.
alist head: #columnSize.
alist tail: self columnSize.
^alist
-
condenseElements [menu messages]
| savedSelections |
self
assert: [savedSelections := self selections]
do: [self elements: (self elements select: [:element | element isNotVoid])]
ensure: [self selections: savedSelections].
self clearAndRedisplay
-
defaultWindowLabel [defaults]
^(#chemoJun_Molecular_Catalogue >> 'Molecular Catalogue') asString
-
displayElement: element index: index into: aPixmap [displaying]
^self
displayElement: element
index: index
into: aPixmap
selectionColor: self selectionColor
backgroundColor: self backgroundColor
-
displayElement: element index: index into: aPixmap selectionColor: selectionColor backgroundColor: backgroundColor [displaying]
| pixmapContext |
pixmapContext := aPixmap graphicsContext.
pixmapContext paint: ColorValue white.
pixmapContext displayRectangle: aPixmap bounds.
self
displaySelection: element
pixmapOn: pixmapContext
selectionColor: selectionColor
backgroundColor: backgroundColor.
self displayElement: element pixmapOn: pixmapContext.
self displayName: element pixmapOn: pixmapContext.
self displayIndex: index pixmapOn: pixmapContext.
^aPixmap
-
displayElement: element pixmapOn: pixmapContext [displaying]
element thumbnail ifNil:
[pixmapContext paint: element class defaultEmptyColor.
pixmapContext
displayRectangle: (self selectionMargin extent: element extent)]
ifNotNil: [:it | it displayOn: pixmapContext at: self selectionMargin]
-
displayIndex: index pixmapOn: pixmapContext [displaying]
| aStyle composedText aBox |
self visibleCatalogIndex
ifTrue:
[aStyle := TextAttributes styleNamed: #small
ifAbsent: [TextAttributes default].
composedText := ComposedText withText: index printString style: aStyle.
aBox := composedText bounds.
aBox := aBox align: aBox topLeft
with: pixmapContext medium bounds topLeft + self selectionMargin + (0 @ -3).
pixmapContext paint: ColorValue blue.
composedText displayOn: pixmapContext at: aBox origin]
-
displayName: element pixmapOn: pixmapContext [displaying]
| aString aStyle composedText howMany loopPredicate aBox |
self visibleFileName
ifTrue:
[aString := element baseNameString.
aStyle := TextAttributes styleNamed: #default
ifAbsent: [TextAttributes default].
composedText := ComposedText withText: aString asText style: aStyle.
howMany := 1.
loopPredicate :=
[composedText bounds width > element extent x
and: [aString size - howMany > 3]].
[loopPredicate value] whileTrue:
[composedText := ComposedText
withText: (aString contractTo: aString size - howMany) asText
style: aStyle.
howMany := howMany + 1].
aBox := composedText bounds.
aBox := aBox align: aBox corner
with: pixmapContext medium bounds corner - self selectionMargin + (0 @ 2).
pixmapContext paint: ColorValue black.
composedText displayOn: pixmapContext at: aBox origin]
-
displayOn: graphicsContext [displaying]
| aPixmap |
JunControlUtility
assert: [aPixmap := Pixmap extent: self pixmapExtent]
do:
[self elements with: (1 to: self elements size)
do:
[:element :index |
| box |
box := element bounds expandedBy: self class defaultThumbnailMargin.
(box intersects: graphicsContext clippingBounds)
ifTrue:
[self
displayElement: element
index: index
into: aPixmap.
aPixmap displayOn: graphicsContext
at: element bounds origin - self selectionMargin]]]
ensure: [aPixmap close]
-
displaySelection: element pixmapOn: pixmapContext selectionColor: selectionColor backgroundColor: backgroundColor [displaying]
(self selections includes: element)
ifTrue: [pixmapContext paint: selectionColor]
ifFalse: [pixmapContext paint: backgroundColor].
pixmapContext displayRectangle: pixmapContext medium bounds
-
dropElements: elements toCatalogue: catalogue [actions]
| selections |
catalogue ifNil: [^nil].
selections := (elements asSortedCollection:
[:e1 :e2 |
(self elements indexOf: e1) < (self elements indexOf: e2)])
collect: [:element | element copy].
catalogue elements: catalogue elements , selections.
catalogue selections: selections.
catalogue scrollFor: selections first.
catalogue clearAndRedisplay
-
dropTargetCatalogue [actions]
| aPoint aController aWindow aModel |
aPoint := JunSensorUtility cursorPoint.
aController := (ScheduledControllers
updateControllerOrder;
scheduledControllers) reverse
detect:
[:controller |
aWindow := controller view.
aWindow displayBox containsPoint: aPoint]
ifNone: [nil].
aController ifNil: [^nil].
aModel := aController model.
aModel = self ifTrue: [^nil].
(aModel isKindOf: self class) ifFalse: [^nil].
^aModel
-
elements [accessing]
catalogueElements ifNil: [catalogueElements := OrderedCollection new].
^catalogueElements
-
elements: aCollection [accessing]
catalogueElements := aCollection.
boundingBox := Point zero extent: Point zero.
catalogueElements with: (0 to: catalogueElements size - 1)
do:
[:element :n |
| y x |
y := n // self columnSize + 1.
x := n \\ self columnSize + 1.
element ifNotNil:
[:it |
| originPoint displayBox |
originPoint := it class defaultThumbnailExtent * ((x - 1) @ (y - 1)).
displayBox := originPoint
extent: (it thumbnail ifNil: [it class defaultThumbnailExtent]
ifNotNil: [:thumbnail | thumbnail extent]).
displayBox := displayBox
translatedBy: self class defaultThumbnailMargin * (x @ y).
it bounds: displayBox.
boundingBox := boundingBox merge: displayBox]].
boundingBox := boundingBox origin
corner: boundingBox corner + self class defaultThumbnailMargin.
selectedElements := nil
-
filename [accessing]
^catalogueFilename
-
filename: aFilename [accessing]
aFilename ifNil: [catalogueFilename := nil]
ifNotNil: [:it | catalogueFilename := it asFilename].
self setWindowLabel
-
fitWindowSize [interface opening]
| aWindow aView windowExtent viewExtent widgetExtent viewWidth |
(aWindow := self getWindow) ifNil: [^nil].
(aView := self getView) ifNil: [^nil].
windowExtent := aWindow displayBox extent.
viewExtent := aView bounds extent.
widgetExtent := windowExtent - viewExtent.
viewWidth := self class defaultThumbnailMargin x * (self columnSize + 1)
+ (self class defaultThumbnailExtent x * self columnSize).
windowExtent := viewWidth @ viewExtent y + widgetExtent.
windowExtent := windowExtent max: aWindow minimumSize.
aWindow displayBox extent = windowExtent ifTrue: [^nil].
aWindow displayBox: ((aWindow displayBox origin extent: windowExtent)
intersect: Screen default bounds)
-
getView [private]
| aView |
aView := self dependents detect:
[:each |
(each isKindOf: self class defaultMolecueCatalogueViewClass)
and: [each model = self]]
ifNone: [nil].
aView isNil ifTrue: [^nil].
^aView
-
hasVoidElement [testing]
^(self elements detect: [:element | element isVoid] ifNone: [nil]) notNil
-
htmlTo: aFilename with: aCollection [private]
JunProgress new do:
[:progress |
| aStream |
aCollection with: (1 to: aCollection size)
do:
[:assoc :index |
| element filename stream |
element := assoc key.
progress message: element baseNameString.
filename := assoc value last asFilename.
stream := JunJpegImageStream on: filename writeStream.
[Cursor write showWhile:
[element isVoid
ifTrue: [stream nextPutImage: element defaultThumbnail]
ifFalse: [stream nextPutImage: element thumbnail asImage]]]
ensure: [stream close].
filename := assoc value first asFilename.
stream := JunJpegImageStream on: filename writeStream.
[Cursor write showWhile:
[element isVoid
ifTrue: [stream nextPutImage: element defaultImage]
ifFalse: [stream nextPutImage: element image asImage]]]
ensure: [stream close].
progress value: index / aCollection size].
JunControlUtility
assert: [aStream := aFilename writeStream]
do:
[aStream
nextPutAll: '<!DOCTYPE HTML PUBLIC "-//W3C//DTD HTML 4.01 Transitional//EN">
<html lang="ja">
<head>
<meta http-equiv="Content-Type" content="text/html; charset=Shift_JIS">
<meta http-equiv="Content-Style-Type" content="text/css">
<link rev="made" href="mailto:cheminfo@nii.ac.jp">
<link rel="index" href="index.html">
<title>Molecular Catalogue</title>
<style type="text/css">
<!--
body {
background-color : #ffffff;
margin : 20px;
padding : 10px;
font-family : serif;
font-size : 10pt;
}
img.borderless {
border-width : 0px;
vertical-align : middle;
}
table.belt {
border-style : solid;
border-width : 0px;
border-color : #000000;
background-color : #cccccc;
padding : 0px 0px;
}
table.content {
border-style : solid;
border-width : 0px;
border-color : #000000;
padding : 2px 4px;
}
table.element {
border-style : solid;
border-width : 0px;
border-color : #000000;
padding : 0px 0px;
}
td.element {
text-align : right;
font-size : 8pt;
padding : 0px 0px;
background-color : #ffffff;
}
td.center-small-white {
text-align : center;
font-size : 8pt;
padding : 0px 0px;
background-color : #ffffff;
}
td.left-small-white {
text-align : left;
font-size : 8pt;
padding : 0px 0px;
background-color : #ffffff;
}
td.right-small-white {
text-align : right;
font-size : 8pt;
padding : 0px 0px;
background-color : #ffffff;
}
-->
</style>
</head>
<body>
<table class="belt" summary="belt">
<tbody>
<tr>
<td>
<table class="content" summary="content">
<tbody>
'.
10 timesRepeat: [aStream space].
aStream nextPutAll: '<tr>'.
aStream cr.
aCollection with: (1 to: aCollection size)
do:
[:assoc :index |
| element image thumbnail alt |
element := assoc key.
image := (Filename splitPath: assoc value first asString) last.
thumbnail := (Filename splitPath: assoc value last asString) last.
alt := (Filename splitExtension: thumbnail) first.
12 timesRepeat: [aStream space].
aStream nextPutAll: '<td class="element">'.
aStream cr.
12 timesRepeat: [aStream space].
aStream nextPutAll: '<table class="element" summary="element">'.
aStream cr.
14 timesRepeat: [aStream space].
aStream nextPutAll: '<tbody>'.
aStream cr.
self visibleCatalogIndex
ifTrue:
[16 timesRepeat: [aStream space].
aStream nextPutAll: '<tr>'.
aStream cr.
18 timesRepeat: [aStream space].
aStream nextPutAll: '<td class="left-small-white">'.
aStream nextPutAll: index printString.
aStream nextPutAll: '</td>'.
aStream cr.
16 timesRepeat: [aStream space].
aStream nextPutAll: '</tr>'.
aStream cr].
16 timesRepeat: [aStream space].
aStream nextPutAll: '<tr>'.
aStream cr.
18 timesRepeat: [aStream space].
aStream nextPutAll: '<td class="center-small-white">'.
aStream nextPutAll: '<a href="images/'.
aStream nextPutAll: image.
aStream nextPutAll: '">'.
aStream nextPutAll: '<img class="borderless" src="thumbnails/'.
aStream nextPutAll: thumbnail.
aStream nextPutAll: '" width="'.
aStream nextPutAll: element class defaultThumbnailExtent x printString.
aStream nextPutAll: '" height="'.
aStream nextPutAll: element class defaultThumbnailExtent y printString.
aStream nextPutAll: '" alt="'.
aStream nextPutAll: alt.
aStream nextPutAll: '">'.
aStream nextPutAll: '</a>'.
aStream nextPutAll: '</td>'.
aStream cr.
16 timesRepeat: [aStream space].
aStream nextPutAll: '</tr>'.
aStream cr.
self visibleFileName
ifTrue:
[16 timesRepeat: [aStream space].
aStream nextPutAll: '<tr>'.
aStream cr.
18 timesRepeat: [aStream space].
aStream nextPutAll: '<td class="right-small-white">'.
element baseNameString isEmpty
ifTrue: [aStream nextPutAll: ' ']
ifFalse: [aStream nextPutAll: element baseNameString].
aStream nextPutAll: '</td>'.
aStream cr.
16 timesRepeat: [aStream space].
aStream nextPutAll: '</tr>'.
aStream cr].
14 timesRepeat: [aStream space].
aStream nextPutAll: '</tbody>'.
aStream cr.
12 timesRepeat: [aStream space].
aStream nextPutAll: '</table>'.
aStream cr.
12 timesRepeat: [aStream space].
aStream nextPutAll: '</td>'.
aStream cr.
(index \\ columnSize = 0 and: [index ~= aCollection size])
ifTrue:
[10 timesRepeat: [aStream space].
aStream nextPutAll: '</tr>'.
aStream cr.
10 timesRepeat: [aStream space].
aStream nextPutAll: '<tr>'.
aStream cr]].
10 timesRepeat: [aStream space].
aStream nextPutAll: '</tr>'.
aStream cr.
aStream
nextPutAll: ' </tbody>
</table>
</td>
</tr>
</tbody>
</table>
</body>
</html>']
ensure: [aStream close]]
-
initialize [initialize-release]
super initialize.
catalogueElements := nil.
columnSize := nil.
boundingBox := nil.
selectedElements := nil.
catalogueFilename := nil.
preferenceTable := nil.
menuBar := nil
-
isAllSelections [testing]
self selections isEmpty ifTrue: [^false].
^(self elements reject: [:element | self selections includes: element])
isEmpty
-
isAllVoidSelections [testing]
self selections isEmpty ifTrue: [^false].
^(self selections select: [:element | element isNotVoid]) isEmpty
-
isEmpty [testing]
^self elements ifNil: [true] ifNotNil: [:it | it isEmpty]
-
keyboardDispatchTable [keyboard]
| aTable |
aTable := Dictionary new.
aTable add: #Left -> [self scrollLeft].
aTable add: #Right -> [self scrollRight].
aTable add: #Up -> [self scrollUp].
aTable add: #Down -> [self scrollDown].
^aTable
-
keyboardDispathDebug [keyboard]
^false
-
keyboardEvent: event fromController: controller [keyboard]
| dispatchTable keyValue messageSelector |
self keyboardDispathDebug
ifTrue:
[Transcript
cr;
show: event keyValue printString].
controller isControlActive ifFalse: [^event].
self getView ifNil: [^event].
controller viewHasCursor ifFalse: [^event].
dispatchTable := self keyboardDispatchTable.
dispatchTable isNil ifTrue: [^event].
keyValue := event keyValue.
messageSelector := dispatchTable at: keyValue ifAbsent: [nil].
((messageSelector isKindOf: Symbol)
and: [self respondsTo: messageSelector])
ifTrue:
[self perform: messageSelector.
^nil].
(messageSelector isKindOf: BlockClosure)
ifTrue:
[messageSelector value.
^nil].
^event
-
menuBar [menu accessing]
menuBar isNil ifTrue: [menuBar := self class menuBar].
^menuBar
-
moleculeObjects [accessing]
| moleculeObjects |
moleculeObjects := OrderedCollection new.
self elements
do: [:element | element moleculeObject ifNotNil: [:it | moleculeObjects add: it]].
^moleculeObjects
-
move1Elements: elements toElement: target [actions]
| attractiveElement attractiveElements elementCollection elementIndex targetIndex headCollection tailCollection |
attractiveElement := elements last.
attractiveElements := (elements asSortedCollection:
[:e1 :e2 |
(self elements indexOf: e1) < (self elements indexOf: e2)])
asOrderedCollection.
elementCollection := self elements copy asOrderedCollection.
elementIndex := elementCollection
findFirst: [:each | each = attractiveElement].
elementIndex < 1 ifTrue: [^nil].
targetIndex := elementCollection findFirst: [:each | each = target].
targetIndex < 1 ifTrue: [^nil].
elementIndex < targetIndex
ifTrue:
[headCollection := elementCollection copyFrom: 1 to: targetIndex.
tailCollection := elementCollection copyFrom: targetIndex + 1
to: elementCollection size]
ifFalse:
[headCollection := elementCollection copyFrom: 1 to: targetIndex - 1.
tailCollection := elementCollection copyFrom: targetIndex
to: elementCollection size].
attractiveElements
do: [:element | headCollection remove: element ifAbsent: [nil]].
attractiveElements
do: [:element | tailCollection remove: element ifAbsent: [nil]].
elementCollection := OrderedCollection new.
elementCollection addAll: headCollection.
attractiveElements remove: attractiveElement.
attractiveElements do:
[:element |
elementCollection size = (targetIndex - 1)
ifTrue: [elementCollection add: attractiveElement].
elementCollection add: element].
elementCollection size = (targetIndex - 1)
ifTrue: [elementCollection add: attractiveElement].
elementCollection addAll: tailCollection.
self elements: elementCollection.
self selections: elements.
self redisplay
-
move2Elements: elements toElement: target [actions]
| attractiveElement attractiveElements elementCollection elementIndex targetIndex headCollection tailCollection voidElements |
attractiveElement := elements last.
attractiveElements := (elements asSortedCollection:
[:e1 :e2 |
(self elements indexOf: e1) < (self elements indexOf: e2)])
asOrderedCollection.
attractiveElements remove: attractiveElement.
attractiveElements addFirst: attractiveElement.
elementCollection := self elements copy asOrderedCollection.
elementIndex := elementCollection
findFirst: [:element | element = attractiveElement].
elementIndex < 1 ifTrue: [^nil].
targetIndex := elementCollection findFirst: [:element | element = target].
targetIndex < 1 ifTrue: [^nil].
headCollection := elementCollection copyFrom: 1 to: targetIndex - 1.
tailCollection := elementCollection copyFrom: targetIndex
to: elementCollection size.
headCollection with: (1 to: headCollection size)
do:
[:element :index |
(attractiveElements includes: element)
ifTrue:
[headCollection at: index put: self class defaultCatalogueVoidClass new]].
tailCollection with: (1 to: tailCollection size)
do:
[:element :index |
(attractiveElements includes: element)
ifTrue:
[tailCollection at: index put: self class defaultCatalogueVoidClass new]].
voidElements := tailCollection select: [:element | element isVoid].
voidElements isEmpty
ifFalse:
[(voidElements copyFrom: 1
to: (attractiveElements size min: voidElements size))
do: [:void | tailCollection remove: void]].
elementCollection := OrderedCollection new.
elementCollection addAll: headCollection.
elementCollection addAll: attractiveElements.
elementCollection addAll: tailCollection.
self elements: elementCollection.
self selections: elements.
self clearAndRedisplay
-
moveElements: elements toElement: target [actions]
(JunSensorUtility shiftDown or: [JunSensorUtility altDown])
ifTrue: [self move2Elements: elements toElement: target]
ifFalse: [self move1Elements: elements toElement: target]
-
multiSelections [preferences]
^self preferenceTable at: #multiSelections ifAbsentPut: [true]
-
multiSelections: aBoolean [preferences]
self preferenceTable at: #multiSelections put: aBoolean = true
-
openCatalogueElement: element [menu messages]
^self openCatalogueElement: element at: nil
-
openCatalogueElement: element at: point [menu messages]
| viewer |
viewer := nil.
(element filename notNil and: [element filename exists])
ifTrue:
[Cursor wait showWhile:
[viewer := element class defaultMoleculeViewerClass
fileName: element filename.
element toPreferences: viewer.
self getWindow ifNil: [viewer open]
ifNotNil:
[:window |
| box |
element viewerExtent ifNil: [box := 0 @ 0 extent: 400 @ 400]
ifNotNil: [:it | box := 0 @ 0 extent: it].
point ifNil: [box := box align: box center with: window displayBox center]
ifNotNil: [box := box align: box origin with: point].
viewer openIn: box].
element projectionTable ifNil: [viewer resetView]
ifNotNil: [:it | viewer projectionTable: it].
viewer cameraButton
compute: [:value | self pressedCameraButtonOf: element in: viewer].
viewer beVisibleCameraButton]].
^viewer
-
openCatalogueFile [menu messages]
| catalogue |
catalogue := self class request.
catalogue ifNil: [^nil].
self columnSize: catalogue columnSize.
self elements: catalogue elements.
self selections: catalogue selections.
self filename: catalogue filename.
self preferenceTable: catalogue preferenceTable.
self fitWindowSize.
self updateMenuIndication
-
openMoleculeViewer [menu messages]
| collection point |
collection := OrderedCollection new.
point := nil.
self selections do:
[:element |
| viewer |
viewer := self openCatalogueElement: element at: point.
viewer ifNil: [point := nil]
ifNotNil:
[:it |
collection add: it.
point := it getWindow displayBox origin translatedBy: 25 @ 25].
(JunSensorUtility shiftDown or: [JunSensorUtility altDown])
ifTrue:
[collection
do: [:each | each closeTogetherWhenShiftDownOrAltDown: collection].
^nil]].
collection
do: [:each | each closeTogetherWhenShiftDownOrAltDown: collection]
-
openSDFile [menu messages]
| aReader moleculeObjects aDirectory filenameCollection elementCollection |
aReader := ChemoJunSdFileReader request.
aReader isNil ifTrue: [^nil].
(moleculeObjects := aReader moleculeObjects) isEmpty ifTrue: [^nil].
aDirectory := (aReader fileName asString , '.sbd') asFilename.
aDirectory exists ifFalse: [aDirectory makeDirectory].
filenameCollection := OrderedCollection new: moleculeObjects size.
moleculeObjects with: (1 to: moleculeObjects size)
do:
[:moleculeObject :nth |
| aWriter aString aCollection aFilename |
aWriter := ChemoJunMolFileWriter moleculeObject: moleculeObject.
aFilename := (aDirectory
construct: aReader baseName , aReader extension , '.' , nth printString
, '.mol')
asFilename.
aString := moleculeObject molfileHeaderBlock at: 2.
(aString size >= 10 and: [(aString copyFrom: 3 to: 10) = 'ChemoJun'])
ifTrue:
[aString := moleculeObject molfileHeaderBlock at: 1.
aCollection := aReader separate: aString.
(aCollection size = 3
and: [aCollection first = '-' and: [aCollection last = '-']])
ifTrue:
[aFilename := (aDirectory construct: (aCollection at: 2) , '.mol')
asFilename]].
aWriter fileName: aFilename.
aWriter write.
filenameCollection add: aFilename].
elementCollection := self class elementsFrom: filenameCollection.
self elements: self elements , elementCollection.
self redisplay
-
pixmapExtent [displaying]
| aBox |
aBox := (Point zero extent: self class defaultThumbnailExtent)
expandedBy: self selectionMargin.
^aBox extent
-
postOpenWith: aBuilder [interface opening]
super postOpenWith: aBuilder.
self fitWindowSize
-
preferenceTable [preferences]
preferenceTable ifNil: [preferenceTable := JunAttributeTable new].
^preferenceTable
-
preferenceTable: attributeTable [preferences]
preferenceTable := attributeTable
-
preferenceTableToLispList [lisp support]
| alist |
alist := JunLispCons cell.
alist head: #preferenceTable.
alist tail: self preferenceTable toLispList.
^alist
-
pressedCameraButtonOf: anElement in: aViewer [actions]
| anImage |
aViewer ifNil: [^nil].
anImage := aViewer asImage.
anImage ifNil: [^nil].
anImage := anElement decoratedImage: anImage.
anElement
fromPreferences: aViewer;
thumbnail: anImage;
computeMappingPoints: aViewer.
self changed
-
printOn: aStream [printing]
self toLispList printOn: aStream
-
quitDoing [menu messages]
self closeRequest
-
redisplay [displaying]
self changed: #redisplay.
self updateMenuIndication
-
removeElements [menu messages]
| selections elements |
(selections := self selections) isEmpty ifTrue: [^nil].
(JunDialog confirm: #jun_Really_remove_ >> 'Really remove?')
ifFalse: [^nil].
elements := self elements
reject: [:element | selections includes: element].
self elements: elements.
self clearSelections.
self changed
-
removeSelection: catalogueElement [selecting]
self selections: ((self selections copy)
remove: catalogueElement ifAbsent: [nil];
yourself)
-
requestNewImageFilename [menu messages]
"ChemoJunMoleculeCatalogue new requestNewImageFilename."
| labels values menu message aFilename |
labels := Array
with: (Array with: (#jun_Image_files >> 'Image files') asString).
values := Array with: JunSystem defaultImageExtensionPatterns.
menu := Menu labelList: labels values: values.
message := #jun_Input_an_image_file_ >> 'Input an image file.'
expandMacrosWith: 'image'.
aFilename := ChemoJunFileRequesterDialog
requestNewFilename: message
initialFilename: self defaultBaseName , '.jpg'
fileTypeMenu: menu
initialFileType: values first.
aFilename isNil ifTrue: [^nil].
^aFilename
-
saveAsCatalogue [menu messages]
| labels values menu filename |
self isEmpty ifTrue: [^nil].
labels := Array with: (Array
with: (#chemoJun_Molecular_catalogue_files >> 'Molecular catalogue files')
asString)
with: (Array with: (#jun_All_files >> 'All files') asString).
values := Array with: #('*.catalogue' '*.CATALOGUE') with: #('*').
menu := Menu labelList: labels values: values.
filename := ChemoJunFileRequesterDialog
requestNewFilename: (#chemoJun_Input_a_catalogue_file_
>> 'Input a catalogue file.') asString
initialFilename: self defaultBaseName , '.catalogue'
fileTypeMenu: menu
initialFileType: values first.
filename isNil ifTrue: [^nil].
self saveCatalogueTo: filename.
self filename: filename
-
saveAsHTML [menu messages]
| baseDirectory imageDirectory thumbnailDirectory aCollection aFilename |
self isEmpty ifTrue: [^nil].
baseDirectory := ChemoJunFileRequesterDialog
requestNewDirectory: (#jun_Input_a_directory_ >> 'Input a directory.')
asString
initialFilename: self defaultBaseName.
baseDirectory ifNil: [^nil].
baseDirectory exists ifFalse: [baseDirectory makeDirectory].
imageDirectory := baseDirectory construct: 'images'.
imageDirectory exists ifFalse: [imageDirectory makeDirectory].
thumbnailDirectory := baseDirectory construct: 'thumbnails'.
thumbnailDirectory exists ifFalse: [thumbnailDirectory makeDirectory].
aCollection := OrderedCollection new: self elements size.
self elements with: (1 to: self elements size)
do:
[:element :index |
| aString imageFilename thumbnailFilename |
aString := index printString.
8 - aString size timesRepeat: [aString := '0' , aString].
aString := aString , '.jpg'.
imageFilename := imageDirectory construct: aString.
thumbnailFilename := thumbnailDirectory construct: aString.
aCollection
add: element -> (Array with: imageFilename with: thumbnailFilename)].
aFilename := baseDirectory construct: 'index.html'.
Cursor write showWhile: [self htmlTo: aFilename with: aCollection].
JunURL browse: aFilename asURI asString
-
saveAsImage [menu messages]
| aBoolean anImage aFilename |
aBoolean := JunSensorUtility shiftDown or: [JunSensorUtility altDown].
anImage := self asImage.
anImage isNil ifTrue: [^nil].
aBoolean
ifTrue:
[anImage := anImage convertToPalette: JunImageProcessor grayPalette256
renderedBy: NearestPaint new].
aFilename := self requestNewImageFilename.
aFilename isNil ifTrue: [^nil].
self writeImage: anImage to: aFilename.
^anImage
-
saveAsSDFile [menu messages]
| aWriter moleculeObjects |
self elements isEmpty ifTrue: [^nil].
aWriter := ChemoJunSdFileWriter
requestInitialFileName: self defaultBaseName , '.sd'.
aWriter isNil ifTrue: [^nil].
moleculeObjects := self moleculeObjects.
aWriter moleculeObjects: moleculeObjects.
aWriter write.
^aWriter
-
saveCatalogue [menu messages]
self isEmpty ifTrue: [^nil].
self filename ifNil: [self saveAsCatalogue]
ifNotNil: [:it | self saveCatalogueTo: it]
-
saveCatalogueTo: aFilename [menu messages]
| aStream |
JunControlUtility
assert: [aStream := aFilename asFilename writeStream]
do:
[aStream
nextPutAll: '%';
cr.
aStream
nextPutAll: '%';
space;
nextPutAll: 'Molecular Catalogue';
space;
nextPutAll: 'created by';
space;
nextPutAll: ChemoJunSystem system , ChemoJunSystem version;
space;
nextPutAll: 'at';
space;
nextPutAll: JunCalendarModel stringFromDateAndTime;
cr.
aStream
nextPutAll: '%';
cr.
self toLispList saveOn: aStream]
ensure: [aStream close]
-
scrollDown [scrolling]
self selections size = 1
ifTrue:
[| index down |
index := self elements indexOf: self selection.
down := OrderedCollection new.
(index + self columnSize to: self elements size by: self columnSize)
do: [:i | down add: (self elements at: i)].
index := index
+ (self columnSize * (down findFirst: [:element | element isNotVoid])).
index <= self elements size
ifTrue:
[| element |
element := self elements at: index.
self selection: element.
self scrollFor: element.
self redisplay]]
ifFalse:
[self getView
ifNotNil: [:aView | aView scrollBy: 0 @ self scrollGrid y negated]]
-
scrollFor: element [scrolling]
self getView ifNotNil:
[:aView |
| elementBox viewBox mergeBox |
elementBox := element bounds.
viewBox := aView bounds.
mergeBox := elementBox merge: viewBox.
mergeBox = viewBox
ifFalse:
[| scrollAmount marginPoint |
scrollAmount := aView scrollOffset negated.
marginPoint := self class defaultThumbnailMargin.
elementBox top < viewBox top
ifTrue: [scrollAmount := scrollAmount x @ (elementBox top - marginPoint y)].
elementBox bottom > viewBox bottom
ifTrue:
[scrollAmount := scrollAmount x
@ (elementBox bottom - viewBox height + marginPoint y)].
elementBox left < viewBox left
ifTrue: [scrollAmount := (elementBox left - marginPoint x) @ scrollAmount y].
elementBox right > viewBox right
ifTrue:
[scrollAmount := (elementBox right - viewBox width + marginPoint x)
@ scrollAmount y].
scrollAmount := scrollAmount negated.
aView scrollTo: scrollAmount]]
-
scrollGrid [scrolling]
^self class defaultThumbnailExtent + self class defaultThumbnailMargin
-
scrollLeft [scrolling]
self selections size = 1
ifTrue:
[| index left |
index := self elements indexOf: self selection.
left := (self elements copyFrom: 1 to: index - 1) reverse.
index := index - (left findFirst: [:element | element isNotVoid]).
index > 0
ifTrue:
[| element |
element := self elements at: index.
self selection: element.
self scrollFor: element.
self redisplay]]
ifFalse:
[self getView ifNotNil: [:aView | aView scrollBy: self scrollGrid x @ 0]]
-
scrollRight [scrolling]
self selections size = 1
ifTrue:
[| index right |
index := self elements indexOf: self selection.
right := self elements copyFrom: index + 1 to: self elements size.
index := index + (right findFirst: [:element | element isNotVoid]).
index <= self elements size
ifTrue:
[| element |
element := self elements at: index.
self selection: element.
self scrollFor: element.
self redisplay]]
ifFalse:
[self getView
ifNotNil: [:aView | aView scrollBy: self scrollGrid x negated @ 0]]
-
scrollUp [scrolling]
self selections size = 1
ifTrue:
[| index up |
index := self elements indexOf: self selection.
up := OrderedCollection new.
(index - self columnSize to: 1 by: self columnSize negated)
do: [:i | up add: (self elements at: i)].
index := index
- (self columnSize * (up findFirst: [:element | element isNotVoid])).
index > 0
ifTrue:
[| element |
element := self elements at: index.
self selection: element.
self scrollFor: element.
self redisplay]]
ifFalse:
[self getView ifNotNil: [:aView | aView scrollBy: 0 @ self scrollGrid y]]
-
selectAll [menu messages]
self selections: self elements.
self redisplay
-
selectDirectory [menu messages]
| directory catalogue |
directory := ChemoJunFileRequesterDialog requestDirectory.
directory isNil ifTrue: [^nil].
catalogue := self class directory: directory.
self elements: self elements , catalogue elements.
self filename: catalogue filename.
self redisplay
-
selectedElementsToLispList [lisp support]
| aList |
aList := JunLispCons cell.
aList head: #selectedElements.
self selections
collect: [:element | aList add: (self elements indexOf: element)].
^aList
-
selection [selecting]
self selections isEmpty ifTrue: [^nil].
^self selections last
-
selection: element [selecting]
element ifNil: [self selections: Array new]
ifNotNil: [:it | self selections: (Array with: it)]
-
selectionColor [displaying]
^ColorValue red
-
selectionMargin [displaying]
^2 @ 2
-
selections [selecting]
selectedElements ifNil: [selectedElements := OrderedCollection new].
^selectedElements
-
selections: elementCollection [selecting]
selectedElements := elementCollection asOrderedCollection
select: [:element | element notNil and: [element isNotVoid]].
selectedElements isEmpty
ifTrue: [self updateEditMenuIndication]
ifFalse: [self redisplay]
-
setWindowLabel [interface opening]
| aWindow aFilename aString |
aWindow := self getWindow.
aWindow isNil ifTrue: [^nil].
aWindow model = self ifFalse: [^nil].
self filename isNil ifTrue: [^aWindow label: self defaultWindowLabel].
aFilename := self filename asFilename.
aString := (Filename splitPath: aFilename asString) last.
aWindow label: self defaultWindowLabel , ' [' , aString , ']'
-
singleSelection [preferences]
^self multiSelections not
-
singleSelection: aBoolean [preferences]
^self multiSelections: (aBoolean = true) not
-
toggleCatalogIndex [menu messages]
self visibleCatalogIndex: self visibleCatalogIndex not.
self redisplay
-
toggleFileName [menu messages]
self visibleFileName: self visibleFileName not.
self redisplay
-
toLispList [lisp support]
| aList |
aList := JunLispCons cell.
aList head: self class name.
aList add: self columnSizeToLispList.
aList add: self catalogueElementsToLispList.
self selections isEmpty
ifFalse: [aList add: self selectedElementsToLispList].
self preferenceTable isEmpty
ifFalse: [aList add: self preferenceTableToLispList].
^aList
-
updateEditMenuIndication [menu accessing]
| menuItem aMenu |
menuItem := self menuItemLabeled: 'Edit' inMenu: self menuBar.
menuItem isNil ifTrue: [^self].
aMenu := menuItem submenu.
aMenu notNil
ifTrue:
[menuItem := aMenu menuItemWithValue: #openMoleculeViewer ifNone: [nil].
menuItem notNil
ifTrue:
[(self isEmpty or: [self selections isEmpty or: [self isAllVoidSelections]])
ifTrue: [menuItem disable]
ifFalse: [menuItem enable]].
menuItem := aMenu menuItemWithValue: #removeElements ifNone: [nil].
menuItem notNil
ifTrue:
[(self isEmpty or: [self selections isEmpty or: [self isAllVoidSelections]])
ifTrue: [menuItem disable]
ifFalse: [menuItem enable]].
menuItem := aMenu menuItemWithValue: #selectAll ifNone: [nil].
menuItem notNil
ifTrue:
[(self isEmpty or: [self isAllSelections])
ifTrue: [menuItem disable]
ifFalse: [menuItem enable]]]
-
updateFileMenuIndication [menu accessing]
| menuItem aMenu |
menuItem := self menuItemLabeled: 'File' inMenu: self menuBar.
menuItem isNil ifTrue: [^self].
aMenu := menuItem submenu.
aMenu notNil
ifTrue:
[menuItem := aMenu menuItemWithValue: #saveCatalogue ifNone: [nil].
menuItem notNil
ifTrue: [self isEmpty ifTrue: [menuItem disable] ifFalse: [menuItem enable]].
menuItem := aMenu menuItemWithValue: #saveAsCatalogue ifNone: [nil].
menuItem notNil
ifTrue: [self isEmpty ifTrue: [menuItem disable] ifFalse: [menuItem enable]].
menuItem := aMenu menuItemWithValue: #saveAsSDFile ifNone: [nil].
menuItem notNil
ifTrue: [self isEmpty ifTrue: [menuItem disable] ifFalse: [menuItem enable]].
menuItem := aMenu menuItemWithValue: #saveAsImage ifNone: [nil].
menuItem notNil
ifTrue: [self isEmpty ifTrue: [menuItem disable] ifFalse: [menuItem enable]].
menuItem := aMenu menuItemWithValue: #saveAsHTML ifNone: [nil].
menuItem notNil
ifTrue: [self isEmpty ifTrue: [menuItem disable] ifFalse: [menuItem enable]]]
-
updateMenuIndication [menu accessing]
self updateFileMenuIndication.
self updateEditMenuIndication.
self updateViewMenuIndication
-
updateViewMenuIndication [menu accessing]
| menuItem aMenu |
menuItem := self menuItemLabeled: 'View' inMenu: self menuBar.
menuItem isNil ifTrue: [^self].
aMenu := menuItem submenu.
aMenu notNil
ifTrue:
[menuItem := aMenu menuItemWithValue: #toggleCatalogIndex ifNone: [nil].
menuItem notNil
ifTrue:
[menuItem enable.
self visibleCatalogIndex ifTrue: [menuItem beOn] ifFalse: [menuItem beOff]].
menuItem := aMenu menuItemWithValue: #toggleFileName ifNone: [nil].
menuItem notNil
ifTrue:
[menuItem enable.
self visibleFileName ifTrue: [menuItem beOn] ifFalse: [menuItem beOff]].
menuItem := aMenu menuItemWithValue: #arrangeColumnSize ifNone: [nil].
menuItem notNil
ifTrue: [self isEmpty ifTrue: [menuItem disable] ifFalse: [menuItem enable]].
menuItem := aMenu menuItemWithValue: #condenseElements ifNone: [nil].
menuItem notNil
ifTrue:
[self hasVoidElement ifTrue: [menuItem enable] ifFalse: [menuItem disable]]]
-
visibleCatalogIndex [preferences]
^self preferenceTable at: #visibleCatalogIndex ifAbsentPut: [false]
-
visibleCatalogIndex: aBoolean [preferences]
self preferenceTable at: #visibleCatalogIndex put: aBoolean = true
-
visibleFileName [preferences]
^self preferenceTable at: #visibleFileName ifAbsentPut: [true]
-
visibleFileName: aBoolean [preferences]
self preferenceTable at: #visibleFileName put: aBoolean = true
-
where: aPoint [selecting]
^self elements detect: [:element | element bounds containsPoint: aPoint]
ifNone: [nil]
-
which: aPoint [selecting]
^(self where: aPoint) ifNil: [nil]
ifNotNil: [:element | element isVoid ifTrue: [nil] ifFalse: [element]]
-
yellowButtonMenu [menu accessing]
self updateEditMenuIndication.
^(self menuItemLabeled: 'Edit' inMenu: self menuBar) submenu
-
catalogueElementsFromTable: aTable for: aCatalogue [lisp support]
| aList catalogueElements |
aList := aTable at: #catalogueElements ifAbsent: [^aCatalogue].
catalogueElements := OrderedCollection new: aList size.
(self catalogueProgress)
message: String new;
value: 0;
do:
[aList do:
[:list |
| element |
list ifNil: [element := nil]
ifNotNil:
[element := ((Smalltalk at: list head) fromLispList: list)
thumbnail;
yourself].
catalogueElements add: element.
self catalogueProgress value: catalogueElements size / aList size]].
aCatalogue elements: catalogueElements.
^aCatalogue
-
catalogueProgress [accessing]
catalogueProgress ifNil: [catalogueProgress := JunProgress new].
^catalogueProgress
-
columnSizeFromTable: aTable for: aCatalogue [lisp support]
| columnSize |
columnSize := aTable at: #columnSize ifAbsent: [^aCatalogue].
aCatalogue columnSize: columnSize.
^aCatalogue
-
copyright [copyright]
^'ChemoJun050 (2006/08/08) Copyright 2002-2006 National Institute of Informatics, Research Organization of Information and Systems.'
-
defaultCatalogueElementClass [defaults]
^ChemoJunMoleculeCatalogueElement
-
defaultCatalogueVoidClass [defaults]
^ChemoJunMoleculeCatalogueVoid
-
defaultColumnSize [defaults]
^5
-
defaultMolecueCatalogueViewClass [defaults]
^ChemoJunMoleculeCatalogueView
-
defaultThumbnailExtent [defaults]
^self defaultCatalogueElementClass defaultThumbnailExtent
-
defaultThumbnailMargin [defaults]
^6 @ 6
-
directories: directoryFilenames [instance creation]
| filenameCollection |
filenameCollection := OrderedCollection new.
directoryFilenames do:
[:each |
| directoryName |
directoryName := each asFilename.
(directoryName exists and: [directoryName isDirectory])
ifTrue:
[filenameCollection addAll: (JunFileModel
dive: directoryName
level: 1
patterns: #('*.mol' '*.MOL'))]].
^(self new)
elements: (self elementsFrom: filenameCollection);
yourself
-
directory: directoryFilename [instance creation]
^self directories: (Array with: directoryFilename)
-
elementsFrom: filenameCollection [utilities]
| elementCollection |
elementCollection := OrderedCollection new: filenameCollection size.
(self catalogueProgress)
message: String new;
value: 0;
do:
[filenameCollection do:
[:aFilename |
| anElement |
aFilename ifNil:
[self catalogueProgress message: String new.
anElement := self defaultCatalogueElementClass new]
ifNotNil:
[self catalogueProgress
message: (Filename splitPath: aFilename asString) last.
anElement := (self defaultCatalogueElementClass filename: aFilename)
thumbnail;
yourself].
elementCollection add: anElement.
self catalogueProgress
value: elementCollection size / filenameCollection size.
JunSensorUtility shiftDown ifTrue: [^elementCollection]]].
^elementCollection
-
example1 [examples]
"ChemoJunMoleculeCatalogue example1."
| moleculeCatalogue |
(moleculeCatalogue := ChemoJunMoleculeCatalogue request) ifNil: [^nil].
JunImageDisplayModel show: moleculeCatalogue asImage.
^moleculeCatalogue
-
example2 [examples]
"ChemoJunMoleculeCatalogue example2."
| moleculeCatalogue |
moleculeCatalogue := ChemoJunMoleculeCatalogue new.
moleculeCatalogue open.
^moleculeCatalogue
-
example3 [examples]
"ChemoJunMoleculeCatalogue example3."
| moleculeCatalogue selectedElements |
(moleculeCatalogue := ChemoJunMoleculeCatalogue request) ifNil: [^nil].
moleculeCatalogue multiSelections: true.
selectedElements := OrderedCollection new.
moleculeCatalogue elements with: (1 to: moleculeCatalogue elements size)
do: [:element :index | index even ifTrue: [selectedElements add: element]].
moleculeCatalogue selections: selectedElements.
moleculeCatalogue open.
^moleculeCatalogue
-
example4 [examples]
"ChemoJunMoleculeCatalogue example4."
| aDirectory moleculeCatalogue |
(aDirectory := ChemoJunFileRequesterDialog requestDirectory) ifNil: [^nil].
moleculeCatalogue := ChemoJunMoleculeCatalogue directory: aDirectory.
moleculeCatalogue open.
^moleculeCatalogue
-
example5 [examples]
"ChemoJunMoleculeCatalogue example5."
| aDirectory moleculeCatalogue |
(aDirectory := ChemoJunFileRequesterDialog requestDirectory) ifNil: [^nil].
moleculeCatalogue := ChemoJunMoleculeCatalogue
directories: (Array with: aDirectory with: aDirectory).
moleculeCatalogue open.
^moleculeCatalogue
-
example6 [examples]
"ChemoJunMoleculeCatalogue example6."
| aDirectory moleculeCatalogue lispList |
(aDirectory := ChemoJunFileRequesterDialog requestDirectory) ifNil: [^nil].
moleculeCatalogue := ChemoJunMoleculeCatalogue directory: aDirectory.
lispList := moleculeCatalogue toLispList.
Transcript
clear;
show: lispList saveString.
moleculeCatalogue := moleculeCatalogue class fromLispList: lispList.
lispList := moleculeCatalogue toLispList.
Transcript
cr;
show: lispList saveString.
^moleculeCatalogue
-
filename: catalogueFilename [instance creation]
| aStream aList aCatalogue |
JunControlUtility
assert: [aStream := catalogueFilename asFilename readStream]
do: [Cursor read showWhile: [aList := JunLispParser parse: aStream]]
ensure: [aStream close].
Cursor wait showWhile:
[aCatalogue := (self fromLispList: aList)
filename: catalogueFilename;
yourself].
^aCatalogue
-
fromLispList: aList [lisp support]
| aClass aTable aCatalogue |
aClass := Smalltalk at: aList head.
aTable := self tableFromLispList: aList tail.
aCatalogue := aClass new.
self columnSizeFromTable: aTable for: aCatalogue.
self catalogueElementsFromTable: aTable for: aCatalogue.
self selectedElementsFromTable: aTable for: aCatalogue.
self preferenceTableFromTable: aTable for: aCatalogue.
^aCatalogue
-
menuBar [resources]
"Tools.MenuEditor new openOnClass: self andSelector: #menuBar"
<resource: #menu>
^#(#{UI.Menu} #(
#(#{UI.MenuItem}
#rawLabel:
#(#{Kernel.UserMessage}
#key: #jun_File
#defaultString: 'File' )
#submenu: #(#{UI.Menu} #(
#(#{UI.MenuItem}
#rawLabel:
#(#{Kernel.UserMessage}
#key: #jun_New
#defaultString: 'New' )
#value: #newModel )
#(#{UI.MenuItem}
#rawLabel:
#(#{Kernel.UserMessage}
#key: #chemoJun_Select_Directory
#defaultString: 'Select Directory' )
#value: #selectDirectory )
#(#{UI.MenuItem}
#rawLabel:
#(#{Kernel.UserMessage}
#key: #chemoJun_Open_Catalogue_File
#defaultString: 'Open Catalogue File' )
#value: #openCatalogueFile )
#(#{UI.MenuItem}
#rawLabel:
#(#{Kernel.UserMessage}
#key: #chemoJun_Open_SD_File
#defaultString: 'Open SD File' )
#value: #openSDFile )
#(#{UI.MenuItem}
#rawLabel:
#(#{Kernel.UserMessage}
#key: #chemoJun_Save_Catalogue_File
#defaultString: 'Save Catalogue File' )
#value: #saveCatalogue )
#(#{UI.MenuItem}
#rawLabel:
#(#{Kernel.UserMessage}
#key: #chemoJun_Save_as_Catalogue_File
#defaultString: 'Save as Catalogue File' )
#value: #saveAsCatalogue )
#(#{UI.MenuItem}
#rawLabel:
#(#{Kernel.UserMessage}
#key: #chemoJun_Save_as_SD_File
#defaultString: 'Save as SD File' )
#value: #saveAsSDFile )
#(#{UI.MenuItem}
#rawLabel:
#(#{Kernel.UserMessage}
#key: #chemoJun_Save_as_Image
#defaultString: 'Save as Image' )
#value: #saveAsImage )
#(#{UI.MenuItem}
#rawLabel:
#(#{Kernel.UserMessage}
#key: #chemoJun_Save_as_HTML
#defaultString: 'Save as HTML' )
#value: #saveAsHTML )
#(#{UI.MenuItem}
#rawLabel:
#(#{Kernel.UserMessage}
#key: #jun_Quit
#defaultString: 'Quit' )
#value: #quitDoing ) ) #(1 3 3 2 1 ) nil ) )
#(#{UI.MenuItem}
#rawLabel:
#(#{Kernel.UserMessage}
#key: #jun_Edit
#defaultString: 'Edit' )
#submenu: #(#{UI.Menu} #(
#(#{UI.MenuItem}
#rawLabel:
#(#{Kernel.UserMessage}
#key: #chemoJun_Open_Molecular_Viewer
#defaultString: 'Open Molecular Viewer' )
#value: #openMoleculeViewer )
#(#{UI.MenuItem}
#rawLabel:
#(#{Kernel.UserMessage}
#key: #jun_Remove
#defaultString: 'Remove' )
#value: #removeElements )
#(#{UI.MenuItem}
#rawLabel:
#(#{Kernel.UserMessage}
#key: #jun_Select_all
#defaultString: 'Select All' )
#value: #selectAll ) ) #(2 1 ) nil ) )
#(#{UI.MenuItem}
#rawLabel:
#(#{Kernel.UserMessage}
#key: #chemoJun_View
#defaultString: 'View' )
#submenu: #(#{UI.Menu} #(
#(#{UI.MenuItem}
#rawLabel:
#(#{Kernel.UserMessage}
#key: #chemoJun_Show_Indexes
#defaultString: 'Indexes' )
#value: #toggleCatalogIndex )
#(#{UI.MenuItem}
#rawLabel:
#(#{Kernel.UserMessage}
#key: #chemoJun_Show_File_Name
#defaultString: 'File Name' )
#value: #toggleFileName )
#(#{UI.MenuItem}
#rawLabel:
#(#{Kernel.UserMessage}
#key: #chemoJun_Column_Size
#defaultString: 'Column Size' )
#value: #arrangeColumnSize )
#(#{UI.MenuItem}
#rawLabel:
#(#{Kernel.UserMessage}
#key: #chemoJun_Condense
#defaultString: 'Condense' )
#value: #condenseElements ) ) #(2 2 ) nil ) )
#(#{UI.MenuItem}
#rawLabel:
#(#{Kernel.UserMessage}
#key: #jun_Misc
#defaultString: 'Misc' )
#submenu: #(#{UI.Menu} #(
#(#{UI.MenuItem}
#rawLabel:
#(#{Kernel.UserMessage}
#key: #jun_Manual
#defaultString: 'Manual' )
#value: #browseManual )
#(#{UI.MenuItem}
#rawLabel:
#(#{Kernel.UserMessage}
#key: #jun_Inspect
#defaultString: 'Inspect' )
#value: #inspectModel ) ) #(1 1 ) nil ) ) ) #(4 ) nil ) decodeAsLiteralArray
-
preferenceTableFromTable: aTable for: aCatalogue [lisp support]
| aList preferenceTable |
aList := aTable at: #preferenceTable ifAbsent: [^aCatalogue].
preferenceTable := JunAttributeTable fromLispList: aList.
aCatalogue preferenceTable: preferenceTable.
^aCatalogue
-
request [utilities]
"ChemoJunMoleculeCatalogue request."
| labels values menu filename catalogue |
labels := Array with: (Array
with: (#chemoJun_Molecular_catalogue_files >> 'Molecular catalogue files')
asString)
with: (Array with: (#jun_All_files >> 'All files') asString).
values := Array with: #('*.catalogue' '*.CATALOGUE') with: #('*').
menu := Menu labelList: labels values: values.
filename := ChemoJunFileRequesterDialog
requestFilename: (#chemoJun_Select_a_catalogue_file_
>> 'Select a catalogue file.') asString
fileTypeMenu: menu
initialFileType: values first.
filename isNil ifTrue: [^nil].
catalogue := self filename: filename.
^catalogue
-
selectedElementsFromTable: aTable for: aCatalogue [lisp support]
| aList |
aList := aTable at: #selectedElements ifAbsent: [^aCatalogue].
aCatalogue
selections: (aList collect: [:index | aCatalogue elements at: index])
asArray.
^aCatalogue
-
system [copyright]
^'ChemoJun'
-
tableFromLispList: aList [lisp support]
| aTable |
aTable := JunAttributeTable new.
aList do: [:pair | aTable at: pair head put: pair tail].
^aTable
-
version [copyright]
^'050'
-
windowSpec [interface specs]
"Tools.UIPainter new openOnClass: self andSelector: #windowSpec"
<resource: #canvas>
^#(#{UI.FullSpec}
#window:
#(#{UI.WindowSpec}
#label:
#(#{Kernel.UserMessage}
#key: #chemoJun_Molecular_Catalogue
#defaultString: 'Molecular Catalogue' )
#min: #(#{Core.Point} 300 300 )
#max: #(#{Core.Point} 0 0 )
#bounds: #(#{Graphics.Rectangle} 700 468 1397 1050 )
#flags: 4
#menu: #menuBar
#colors:
#(#{UI.LookPreferences}
#setBackgroundColor: #(#{Graphics.ColorValue} 7700 7700 7700 ) ) )
#component:
#(#{UI.SpecCollection}
#collection: #(
#(#{UI.ArbitraryComponentSpec}
#layout: #(#{Graphics.LayoutFrame} 1 0 1 0 -1 1 -1 1 )
#name: #catalogueView
#flags: 11
#component: #catalogueView ) ) ) )