-
asImage [converting]
| aView imageExtent |
aView := self getView.
(aView isNil or: [aView isOpen not])
ifTrue: [imageExtent := self defaultImageExtent]
ifFalse: [imageExtent := aView bounds extent].
^self asImageExtent: imageExtent
-
asImageExtent: imageExtent [converting]
| anImage aPixmap |
anImage := super asImageExtent: imageExtent.
JunControlUtility
assert: [aPixmap := Pixmap extent: anImage extent]
do:
[anImage displayOn: aPixmap graphicsContext.
superimposeBlock notNil
ifTrue:
[| arguments |
arguments := Array
with: self
with: aPixmap
with: nil.
superimposeBlock
valueWithArguments: (arguments copyFrom: 1 to: superimposeBlock numArgs)]]
ensure:
[anImage := aPixmap asImage.
aPixmap close].
^anImage
-
boundingBoxesFrom: a3dObject [pencil]
| width height depth denominator point boundingBoxes |
width := a3dObject boundingBox width.
height := a3dObject boundingBox height.
depth := a3dObject boundingBox depth.
denominator := width max: (height max: depth).
point := width / denominator , (height / denominator)
, (depth / denominator).
point := point * self defaultPartitionSize.
point := point rounded.
boundingBoxes := Jun3dBoundingBoxes fromObject: a3dObject howMany: point.
self pencilTrace:
[| aBody aViewfinder aViewport |
aBody := JunOpenGL3dCompoundObject new.
aBody add: self displayObject.
aBody add: a3dObject.
aBody
add: (boundingBoxes asJunOpenGL3dObjectColor: ColorValue cyan alpha: 0.1).
aViewfinder := JunOpenGLDisplayModel displayObject: aBody.
aViewfinder defaultProjectionTable: self projectionTable.
aViewfinder openAt: 200 @ 200.
aViewfinder parallelProjection.
aViewport := JunOpenGLShowModel displayModel: aViewfinder.
aViewport useTransparency: true.
aViewport openAt: 200 @ 200.
aViewport parallelProjection].
^boundingBoxes
-
classToSpawn [private]
(JunSensorUtility shiftDown or: [JunSensorUtility altDown])
ifTrue: [^JunOpenGLDisplayModel].
^ChemoJunAbstractViewer
-
clickAt: aPoint [actions]
^self
-
cloneViewer [private]
^self cloneViewerUseDisplayList: self useDisplayList
-
cloneViewerUseDisplayList: aBoolean [private]
| aViewer |
aViewer := self class new.
aBoolean = true
ifTrue: [aViewer useDisplayList: true]
ifFalse: [aViewer useDisplayList: false].
aViewer displayObject: self displayObject.
aViewer defaultProjectionTable: self projectionTable.
aViewer allButOpenInterface: #windowSpec.
aViewer projectionTable: self projectionTable.
^aViewer
-
convert: collectionOfPoints triangles: collectionOfTriangles controller: aController [pencil]
| aPlane aProjection pointCollection triangleCollection |
aProjection := self displayProjection.
pointCollection := collectionOfPoints collect:
[:point |
| aPoint |
aPoint := aController regularizePoint: point.
aPoint := aProjection translateTo3dPointFromPoint: aPoint.
aPoint := aPoint - self sightPoint.
aPoint yourself].
triangleCollection := collectionOfTriangles collect:
[:triangle |
| aTriangle |
aTriangle := triangle collect:
[:point |
| aPoint |
aPoint := aController regularizePoint: point.
aPoint := aProjection translateTo3dPointFromPoint: aPoint.
aPoint := aPoint - self sightPoint.
aPoint yourself].
aPlane := JunPlane
on: (aTriangle at: 1)
on: (aTriangle at: 2)
on: (aTriangle at: 3).
(aPlane valueF: self eyePoint) sign < 0
ifTrue: [aTriangle := aTriangle reverse].
aTriangle yourself].
self pencilTrace:
[| aLine aTransformation0 aTransformation1 aTransformation2 aBody aViewfinder aViewport |
aLine := (self sightPoint to: self eyePoint) normalized.
aTransformation0 := Jun3dTransformation
translate: (aLine atT: self zoomHeight / 2).
aTransformation1 := Jun3dTransformation
translate: (aLine atT: self zoomHeight / 1.99).
aTransformation2 := Jun3dTransformation
translate: (aLine atT: self zoomHeight / 1.98).
aBody := JunOpenGL3dCompoundObject new.
aBody add: self displayObject.
triangleCollection do:
[:triangle |
| aTriangle aPolyline |
aTriangle := (JunOpenGL3dPolygon vertexes: triangle asArray)
transform: aTransformation0.
aTriangle paint: (ColorValue red blendWith: ColorValue white).
aBody add: aTriangle.
aTriangle := (JunOpenGL3dPolylineLoop vertexes: triangle asArray)
transform: aTransformation1.
aTriangle lineWidth: 1.
aTriangle paint: ColorValue red.
aBody add: aTriangle.
aPolyline := (JunOpenGL3dPolylineLoop vertexes: pointCollection)
transform: aTransformation2.
aPolyline lineWidth: 3.
aPolyline paint: ColorValue magenta.
aBody add: aPolyline].
aViewfinder := JunOpenGLDisplayModel displayObject: aBody.
aViewfinder defaultProjectionTable: self projectionTable.
aViewfinder openAt: 200 @ 200.
aViewfinder parallelProjection.
aViewport := JunOpenGLShowModel displayModel: aViewfinder.
aViewport useTransparency: true.
aViewport openAt: 200 @ 200.
aViewport parallelProjection].
^Array with: pointCollection with: triangleCollection
-
cylinder: pointCollection triangles: triangleCollection [pencil]
| baseLine aRadius anInterval anArray aCylinder aPolygon aTransformation |
baseLine := (Jun3dLine from: self sightPoint to: self eyePoint)
normalizedLine.
aRadius := self zoomHeight / 2.
baseLine := Jun3dLine from: (baseLine atT: 0)
to: (baseLine atT: aRadius * 1.5).
anInterval := 0 to: 1 by: 0.1.
anArray := Array new: anInterval size.
(1 to: anArray size)
do: [:index | anArray at: index put: (OrderedCollection new: pointCollection size)].
pointCollection do:
[:aPoint |
| aLine |
aLine := baseLine translatedBy: aPoint.
anInterval with: (1 to: anArray size)
do: [:t :index | (anArray at: index) add: (aLine atT: t)]].
aCylinder := JunOpenGL3dCompoundObject new.
(1 to: anArray size - 1) do:
[:arrayIndex |
| fromPoints toPoints fp1 tp1 fp2 tp2 |
fromPoints := anArray at: arrayIndex.
toPoints := anArray at: arrayIndex + 1.
fp1 := fromPoints at: 1.
tp1 := toPoints at: 1.
(2 to: pointCollection size) do:
[:index |
fp2 := fromPoints at: index.
tp2 := toPoints at: index.
aPolygon := JunOpenGL3dPolygon vertexes: (Array
with: fp1
with: tp1
with: tp2
with: fp2).
self defaultTriangulationClass = JunFormTriangulation3
ifTrue: [aPolygon := aPolygon reversed].
aCylinder add: aPolygon.
fp1 := fp2.
tp1 := tp2]].
aTransformation := Jun3dTransformation translate: (baseLine atT: 0).
triangleCollection do:
[:aTriangle |
aPolygon := (JunOpenGL3dPolygon vertexes: aTriangle reverse)
transform: aTransformation.
aCylinder add: aPolygon].
aTransformation := Jun3dTransformation translate: (baseLine atT: 1).
triangleCollection do:
[:aTriangle |
aPolygon := (JunOpenGL3dPolygon vertexes: aTriangle yourself)
transform: aTransformation.
aCylinder add: aPolygon].
aCylinder
primitivesDo: [:primitive | primitive paint: ColorValue magenta alpha: 0.5].
self pencilTrace:
[| aBody aViewfinder aViewport |
aBody := JunOpenGL3dCompoundObject new.
aBody add: self displayObject.
aBody add: aCylinder.
aViewfinder := JunOpenGLDisplayModel displayObject: aBody.
aViewfinder defaultProjectionTable: self projectionTable.
aViewfinder openAt: 200 @ 200.
aViewfinder parallelProjection.
aViewport := JunOpenGLShowModel displayModel: aViewfinder.
aViewport useTransparency: true.
aViewport openAt: 200 @ 200.
aViewport parallelProjection].
^aCylinder
-
defaulSerialNumberSetting [defaults]
| aSerialNumberSetting |
aSerialNumberSetting := ChemoJunSerialNumberSetting new.
^aSerialNumberSetting
-
defaultBaseName [defaults]
^self displayObject name ifNil: [super defaultBaseName]
ifNotNil: [:aString | aString , '_' , JunSystem defaultBaseName]
-
defaultDisplayViewClass [defaults]
^ChemoJunAbstractViewerView
-
defaultEyePoint [defaults]
| box distance |
self displayObject isNil ifTrue: [^10000 , 0 , 0].
^self defaultProjectionTable at: #eyePoint
ifAbsent:
[box := self boundingBox.
distance := box origin distance: box corner.
distance := distance * 2.
^distance , 0 , 0]
-
defaultMinimumTriangleArea [defaults]
self featureResolution = #high ifTrue: [^0.001]
-
defaultPartitionSize [defaults]
^16
-
defaultResolution [defaults]
defaultResolution isNil ifTrue: [defaultResolution := #medium].
^defaultResolution
-
defaultResolution: aSymbol [defaults]
(#(#low #medium #high) includes: aSymbol)
ifTrue: [defaultResolution := aSymbol]
-
defaultShading [defaults]
^self defaultProjectionTable at: #shading ifAbsent: [^#smoothShading]
-
defaultString [defaults]
^String new
-
defaultTriangulationClass [defaults]
"{ JunFormTriangulation2 | JunFormTriangulation3 }"
^JunFormTriangulation2
-
defaultUpVector [defaults]
^self defaultProjectionTable at: #upVector ifAbsent: [0 , -1 , 1]
-
defaultWindowLabel [defaults]
^(#jun_Viewfinder >> 'Viewfinder') asString
-
extractPatchesFrom: boundingBoxes [pencil]
| compoundObject cursorAnimator |
compoundObject := JunOpenGL3dCompoundObject new.
cursorAnimator := JunCursorAnimator clockCursors.
cursorAnimator tick: 1000.
cursorAnimator showWhile:
[self displayObject polygonsDo:
[:aPolygon |
| anArray |
anArray := aPolygon asPointArray
collect: [:aPoint | boundingBoxes containsPoint: aPoint].
(anArray detect: [:aBoolean | aBoolean = false] ifNone: [nil]) isNil
ifTrue: [compoundObject add: aPolygon]]].
self pencilTrace:
[| aBody aViewfinder |
aBody := JunOpenGL3dCompoundObject new.
aBody add: compoundObject.
aBody
add: (boundingBoxes asJunOpenGL3dObjectColor: ColorValue cyan alpha: 0.1).
aViewfinder := JunOpenGLDisplayModel displayObject: aBody.
aViewfinder defaultProjectionTable: self projectionTable.
aViewfinder openAt: 200 @ 200.
aViewfinder parallelProjection].
"[| frontPatches |
frontPatches := JunOpenGL3dCompoundObject new.
compoundObject polygonsDo:
[:aPolygon |
| pointCollection aPlane |
pointCollection := aPolygon vertexes.
aPlane := JunPlane
on: (pointCollection at: 1)
on: (pointCollection at: pointCollection size // 3 + 1)
on: (pointCollection at: pointCollection size // 3 * 2 + 1).
(aPlane valueF: self eyePoint) >= 0 ifTrue: [frontPatches add: aPolygon]].
compoundObject := frontPatches] value."
^compoundObject
-
featureResolution [accessing]
^#medium
-
fileName [accessing]
^nil
-
flushDisplayObject [flushing]
self displayObject: nil
-
getInformationView [private]
| window |
window := self informationHolder dependents detect: [:each | each isKindOf: ComposedTextView]
ifNone: [nil].
window isNil ifTrue: [^nil].
^window
-
getInformationWindow [private]
| window |
window := self informationHolder dependents detect: [:each | each isKindOf: ScheduledWindow]
ifNone: [nil].
window isNil ifTrue: [^nil].
^window
-
highResolution [menu messages]
self defaultResolution: #high.
self updateViewMenuIndication
-
informationHolder [accessing]
informationHolder isNil
ifTrue:
[informationHolder := ValueHolder with: String new.
informationHolder compute: [:value | self setInformationWindowLabel]].
^informationHolder
-
initialize [initialize-release]
super initialize.
informationHolder := nil.
defaultResolution := nil.
withoutResetViewWhenOpen := false.
self serialNumberSetting
-
is2d [testing]
^false
-
is3d [testing]
^true
-
isElectroViewer [testing]
^false
-
isFeaturesViewer [testing]
^false
-
isMoleculeViewer [testing]
^false
-
isStericViewer [testing]
^false
-
lowResolution [menu messages]
self defaultResolution: #low.
self updateViewMenuIndication
-
mediumResolution [menu messages]
self defaultResolution: #medium.
self updateViewMenuIndication
-
noticeOfWindowClose: aWindow [interface closing]
| window |
super noticeOfWindowClose: aWindow.
window := self getInformationWindow.
window isNil ifFalse: [window sensor eventQuit: nil].
self serialNumberSetting closeRequest
-
numberOfPolygons [accessing]
| numberOfPolygons |
self displayObject isNil ifTrue: [^0].
numberOfPolygons := 0.
self displayObject polygonsDo: [:each | numberOfPolygons := numberOfPolygons + 1].
^numberOfPolygons
-
numberOfPrimitives [accessing]
| numberOfPrimitives |
self displayObject isNil ifTrue: [^0].
numberOfPrimitives := 0.
self displayObject primitivesDo: [:each | numberOfPrimitives := numberOfPrimitives + 1].
^numberOfPrimitives
-
openWithoutResetView [interface opening]
withoutResetViewWhenOpen := true.
self open
-
pencilClosedPointCollection: collectionOfPoints from: aController [pencil]
| aTriangulation anArray aCylinder boundingBoxes patchCollection |
self displayObject isNil ifTrue: [^nil].
collectionOfPoints size < 3 ifTrue: [^nil].
aController isNil ifTrue: [^nil].
self errorSignal handle:
[:exception |
JunDialog
warn: (#chemoJun_Can_not_perform_triangulation_
>> 'Can not perform triangulation.') asString.
^nil]
do:
[aTriangulation := self
triangulationClass: self defaultTriangulationClass
pointCollection: collectionOfPoints
controller: aController].
self errorSignal handle:
[:exception |
JunDialog
warn: (#chemoJun_Can_not_perform_conversion_ >> 'Can not perform conversion.')
asString.
^nil]
do:
[anArray := self
convert: aTriangulation points
triangles: aTriangulation triangles
controller: aController].
aCylinder := self cylinder: anArray first triangles: anArray last.
aCylinder components isEmpty ifTrue: [^nil].
boundingBoxes := self boundingBoxesFrom: aCylinder.
boundingBoxes isEmpty ifTrue: [^nil].
patchCollection := self extractPatchesFrom: boundingBoxes.
patchCollection components isEmpty ifTrue: [^nil].
self spawnObject: patchCollection
-
pencilOpenedPointCollection: collectionOfPoints from: aController [pencil]
| aPlane patchCollection |
self displayObject isNil ifTrue: [^nil].
collectionOfPoints size < 3 ifTrue: [^nil].
aController isNil ifTrue: [^nil].
aPlane := self plane: collectionOfPoints from: aController.
patchCollection := self splitPathesFrom: aPlane.
patchCollection components isEmpty ifTrue: [^nil].
self spawnObject: patchCollection
-
pencilTrace: aBlock [pencil]
"aBlock value"
-
pickedObjectAt: mouse2dPoint [actions]
| compoundObject pickedObject |
self displayObject isNil ifTrue: [^nil].
compoundObject := JunOpenGL3dCompoundObject new.
self displayObject polygonsDo: [:aPolygon | compoundObject add: aPolygon].
pickedObject := JunOpenGLObjectPicker
pickObjectAt: mouse2dPoint
fromCompound: compoundObject
projection: self displayProjection.
pickedObject isNil ifTrue: [^nil].
^pickedObject
-
plane: collectionOfPoints from: aController [pencil]
| aProjection pointCollection firstPoint secondPoint thirdPoint aLine aPlane |
self pencilTrace:
[aController notNil
ifTrue:
[| anImage aWindow |
anImage := aController view topComponent asImage.
aWindow := ScheduledWindow new.
aWindow label: self getWindow label.
aWindow component: anImage.
aWindow openIn: (200 @ 200 extent: anImage extent)]].
aProjection := self displayProjection.
pointCollection := collectionOfPoints collect:
[:point |
| aPoint |
aPoint := aController regularizePoint: point.
aPoint := aProjection translateTo3dPointFromPoint: aPoint.
aPoint := aPoint - self sightPoint.
aPoint yourself].
aLine := (Jun3dLine from: self sightPoint to: self eyePoint)
normalizedLine.
firstPoint := pointCollection first
translatedBy: (aLine atT: self zoomHeight / 2).
secondPoint := pointCollection last
translatedBy: (aLine atT: self zoomHeight / 2).
aLine := aLine
translatedBy: (firstPoint center: secondPoint) - (aLine atT: 0).
thirdPoint := aLine atT: (self zoomHeight * 1.5) negated.
aPlane := firstPoint plane: secondPoint and: thirdPoint.
^aPlane
-
postOpenWith: aBuilder [interface opening]
super postOpenWith: aBuilder.
self setWindowLabel.
withoutResetViewWhenOpen = false ifTrue: [self resetView]
-
serialNumberSetting [accessing]
serialNumberSetting ifNil:
[serialNumberSetting := self defaulSerialNumberSetting.
serialNumberSetting compute:
[:expression |
self indexExpression: expression.
self flushDisplayObject.
self changed: #object].
self indexExpression: serialNumberSetting expression].
^serialNumberSetting
-
setInformationWindowLabel [private]
| aWindow aString |
aWindow := self getInformationWindow.
aWindow isNil ifTrue: [^nil].
aString := (#chemoJun_Information >> 'Information') asString.
self fileName notNil ifTrue: [aString := aString , ' [' , (Filename splitPath: self fileName asString) last , ']'].
aWindow label: aString
-
settingIndex [menu messages]
self serialNumberSetting ifNotNil:
[:aSerialNumberSetting |
| aWindow |
(aWindow := aSerialNumberSetting getWindow) isNil
ifTrue:
[aWindow := self getWindow.
aWindow isNil
ifTrue: [self serialNumberSetting open]
ifFalse:
[self serialNumberSetting openAt: aWindow displayBox topRight + (8 @ 0)]]
ifFalse:
[aWindow isCollapsed ifTrue: [aWindow expand].
aWindow raise]]
-
setWindowLabel [interface opening]
| aWindow |
aWindow := self getWindow.
aWindow isNil ifTrue: [^nil].
aWindow model = self ifFalse: [^nil].
aWindow label: self defaultWindowLabel
-
showInformation [menu messages]
| aWindow myWindow aView |
(aWindow := self getInformationWindow) isNil
ifTrue:
[aWindow := ComposedTextView
createOn: self informationHolder
label: (#chemoJun_Information >> 'Information') asString
icon: (Icon constantNamed: #workspace).
(myWindow := self getWindow) isNil
ifTrue: [aWindow openWithExtent: 300 @ 300]
ifFalse: [aWindow openIn: (myWindow displayBox bottomRight + (8 @ 27) extent: 300 @ 300)].
aView := self getInformationView.
aView controller menuHolder: [self class editMenu].
self setInformationWindowLabel]
ifFalse:
[aWindow isCollapsed ifTrue: [aWindow expand].
aWindow raise]
-
spawnObject [menu messages]
| displayModel |
displayModel := super spawnObject.
self moleculeObject
ifNotNil: [:it | displayModel displayObject name: it baseName].
displayModel setWindowLabel.
displayModel updateMenuIndication.
^displayModel
-
spawnObject: spawningObject [menu messages]
| aViewer aWindow |
aViewer := self cloneViewer.
aViewer displayObject: spawningObject.
aWindow := aViewer builder window.
aWindow openWithExtent: aWindow bounds extent.
aWindow displayPendingInvalidation.
aViewer setWindowLabel.
aViewer updateMenuIndication.
^aWindow
-
splitPathesFrom: aPlane [pencil]
| compoundObject cursorAnimator |
self pencilTrace:
[| aCircle aBody aViewfinder |
aCircle := Jun3dCircle
center: aPlane asTriangle centerOfGravity
radius: self zoomHeight / 2
upVector: aPlane normalVector.
aBody := JunOpenGL3dCompoundObject new.
aBody add: self displayObject.
aBody
add: (aCircle asJunOpenGL3dObjectColor: ColorValue magenta alpha: 0.5)
reversed.
aBody
add: (aCircle asJunOpenGL3dObjectColor: ColorValue magenta alpha: 0.5).
aViewfinder := JunOpenGLDisplayModel displayObject: aBody.
aViewfinder defaultProjectionTable: self projectionTable.
aViewfinder openAt: 200 @ 200
"aViewfinder parallelProjection"].
compoundObject := JunOpenGL3dCompoundObject new.
cursorAnimator := JunCursorAnimator handCursors.
cursorAnimator tick: 1000.
cursorAnimator showWhile:
[self displayObject polygonsDo:
[:aPolygon |
| anArray |
anArray := aPolygon asPointArray
collect: [:aPoint | (aPlane valueF: aPoint) >= 0].
(anArray detect: [:aBoolean | aBoolean = false] ifNone: [nil]) isNil
ifTrue: [compoundObject add: aPolygon]]].
self pencilTrace:
[| aCircle aBody aViewfinder |
aCircle := Jun3dCircle
center: aPlane asTriangle centerOfGravity
radius: self zoomHeight / 2
upVector: aPlane normalVector.
aBody := JunOpenGL3dCompoundObject new.
aBody add: compoundObject.
aBody
add: (aCircle asJunOpenGL3dObjectColor: ColorValue magenta alpha: 0.5)
reversed.
aBody
add: (aCircle asJunOpenGL3dObjectColor: ColorValue magenta alpha: 0.5).
aViewfinder := JunOpenGLDisplayModel displayObject: aBody.
aViewfinder defaultProjectionTable: self projectionTable.
aViewfinder openAt: 200 @ 200
"aViewfinder parallelProjection"].
^compoundObject
-
triangulationClass: aClass pointCollection: collectionOfPoints controller: aController [pencil]
| formTriangulation |
self pencilTrace:
[aController notNil
ifTrue:
[| anImage aWindow |
anImage := aController view topComponent asImage.
aWindow := ScheduledWindow new.
aWindow label: self getWindow label.
aWindow component: anImage.
aWindow openIn: (200 @ 200 extent: anImage extent)]].
formTriangulation := aClass points: collectionOfPoints.
self pencilTrace:
[| aWindow aPixmap graphicsContext |
aWindow := ScheduledWindow new.
aWindow label: 'Triangulation'.
aWindow
openIn: (200 @ 200 extent: formTriangulation boundingBox extent rounded).
aPixmap := Pixmap extent: aWindow bounds extent.
[self errorSignal handle:
[:exception |
aWindow controller closeAndUnschedule.
exception reject]
do:
[graphicsContext := aPixmap graphicsContext.
graphicsContext paint: ColorValue white.
graphicsContext displayRectangle: aPixmap bounds.
JunApplicationModel displayPendingInvalidation.
Cursor wait showWhile:
[self defaultTriangulationClass = JunFormTriangulation2
ifTrue:
[formTriangulation trianglesInterim:
[:triangles :triangle :pending |
formTriangulation
displayOn: graphicsContext
triangles: triangles
triangle: triangle
pending: pending.
JunApplicationModel displayPendingInvalidation.
aWindow raise.
aWindow graphicsContext displayPixmap: aPixmap at: Point zero]].
self defaultTriangulationClass = JunFormTriangulation3
ifTrue:
[formTriangulation trianglesInterim:
[:triangles |
formTriangulation displayOn: graphicsContext triangles: triangles.
JunApplicationModel displayPendingInvalidation.
aWindow raise.
aWindow graphicsContext displayPixmap: aPixmap at: Point zero]]].
formTriangulation displayOn: graphicsContext.
JunApplicationModel displayPendingInvalidation.
aWindow raise.
aWindow graphicsContext displayPixmap: aPixmap at: Point zero.
aWindow component: aPixmap asImage.
aWindow display.
JunApplicationModel displayPendingInvalidation]]
ensure: [aPixmap close]].
^formTriangulation
-
updateStringHolder: aValue [updating]
^self
-
updateViewMenuIndication [menu accessing]
^self