diff --git a/src/Athens-Cairo/CairoLibrary.class.st b/src/Athens-Cairo/CairoLibrary.class.st index cd3dbd8cf80..22d13d23d4a 100644 --- a/src/Athens-Cairo/CairoLibrary.class.st +++ b/src/Athens-Cairo/CairoLibrary.class.st @@ -8,11 +8,6 @@ Class { #category : #'Athens-Cairo-Library' } -{ #category : #'accessing platform' } -CairoLibrary >> macModuleName [ - ^ 'libcairo.2.dylib' -] - { #category : #'accessing platform' } CairoLibrary >> unix32ModuleName [ "On different flavors of linux the path to library may differ diff --git a/src/BaselineOfMorphic/BaselineOfMorphic.class.st b/src/BaselineOfMorphic/BaselineOfMorphic.class.st index f1404bbf21c..c5ba2d5173c 100644 --- a/src/BaselineOfMorphic/BaselineOfMorphic.class.st +++ b/src/BaselineOfMorphic/BaselineOfMorphic.class.st @@ -332,7 +332,6 @@ BaselineOfMorphic >> postload: loader package: packageSpec [ UIManager default: MorphicUIManager new. World displayWorldSafely. - World assuredCanvas. UIManager default uiProcess resume. PharoDarkTheme beCurrent. diff --git a/src/FreeType/FT2FFILibrary.class.st b/src/FreeType/FT2FFILibrary.class.st index f04de4afb21..879bad0247d 100644 --- a/src/FreeType/FT2FFILibrary.class.st +++ b/src/FreeType/FT2FFILibrary.class.st @@ -136,11 +136,6 @@ FT2FFILibrary class >> translateErrorCode: aCode [ ^ ErrorCodeTable at: aCode ifAbsent: [ 'Unknown Error code' ]. ] -{ #category : #'accessing platform' } -FT2FFILibrary >> macModuleName [ - ^ 'libfreetype.dylib' -] - { #category : #'accessing platform' } FT2FFILibrary >> unixModuleName [ ^ 'libfreetype.so.6' diff --git a/src/Graphics-Display Objects/Cursor.class.st b/src/Graphics-Display Objects/Cursor.class.st index 165985ce228..3bfc4655328 100644 --- a/src/Graphics-Display Objects/Cursor.class.st +++ b/src/Graphics-Display Objects/Cursor.class.st @@ -980,11 +980,6 @@ Cursor class >> square [ ^SquareCursor ] -{ #category : #'system startup' } -Cursor class >> startUp [ - self currentCursor: self currentCursor -] - { #category : #constants } Cursor class >> target [ "Answer the instance of me that is the shape of a gunsight." diff --git a/src/Graphics-Display Objects/DisplayScreen.class.st b/src/Graphics-Display Objects/DisplayScreen.class.st index a5d3ceb5db0..57bd9307a82 100644 --- a/src/Graphics-Display Objects/DisplayScreen.class.st +++ b/src/Graphics-Display Objects/DisplayScreen.class.st @@ -178,21 +178,6 @@ DisplayScreen class >> setWindowTitle: aTitle [ self refreshHostWindowTitle ] -{ #category : #'system startup' } -DisplayScreen class >> shutDown [ - "Minimize Display memory saved in image" - Display shutDown. -] - -{ #category : #'system startup' } -DisplayScreen class >> startUp [ - "DisplayScreen startUp" - - Display setExtent: self actualScreenSize depth: Display nativeDepth. - Display beDisplay. - self refreshHostWindowTitle -] - { #category : #displaying } DisplayScreen >> addExtraRegion: aRectangle for: regionDrawer [ "Register the given rectangle as a region which is drawn by the specified region drawer. The region will be excluded from any updates when #forceDamageToScreen: is called. Note that the rectangle is only valid for a single update cycle; once #forceDamageToScreen: has been called, the region drawer and its region are being removed from the list" @@ -410,7 +395,7 @@ DisplayScreen >> fullscreen [ DisplayScreen >> fullscreen: aBoolean [ Display fullscreenMode: (LastScreenModeSelected := aBoolean). - DisplayScreen checkForNewScreenSize. + self currentWorld worldState worldRenderer checkForNewScreenSize. ] diff --git a/src/Graphics-Display Objects/DummyUIManager.extension.st b/src/Graphics-Display Objects/DummyUIManager.extension.st index 39f8349a7a9..17ed6662e00 100644 --- a/src/Graphics-Display Objects/DummyUIManager.extension.st +++ b/src/Graphics-Display Objects/DummyUIManager.extension.st @@ -1,13 +1,5 @@ Extension { #name : #DummyUIManager } -{ #category : #'*Graphics-Display Objects' } -DummyUIManager >> checkForNewDisplaySize [ - - Display extent = DisplayScreen actualScreenSize ifTrue: [^ self]. - DisplayScreen startUp. - -] - { #category : #'*Graphics-Display Objects' } DummyUIManager >> newDisplayDepthNoRestore: pixelSize [ diff --git a/src/Morphic-Core/AbstractWorldRenderer.class.st b/src/Morphic-Core/AbstractWorldRenderer.class.st new file mode 100644 index 00000000000..064e3252bc7 --- /dev/null +++ b/src/Morphic-Core/AbstractWorldRenderer.class.st @@ -0,0 +1,44 @@ +Class { + #name : #AbstractWorldRenderer, + #superclass : #Object, + #instVars : [ + 'world' + ], + #category : #'Morphic-Core-Worlds' +} + +{ #category : #accessing } +AbstractWorldRenderer class >> forWorld: aWorld [ + + ^ self new + world: aWorld; + yourself +] + +{ #category : #accessing } +AbstractWorldRenderer class >> priority [ + + ^ 0 +] + +{ #category : #activation } +AbstractWorldRenderer >> activate [ + + self subclassResponsibility +] + +{ #category : #activation } +AbstractWorldRenderer >> deactivate [ + + self subclassResponsibility +] + +{ #category : #accessing } +AbstractWorldRenderer >> world [ + ^ world +] + +{ #category : #accessing } +AbstractWorldRenderer >> world: anObject [ + world := anObject +] diff --git a/src/Morphic-Core/MorphicCoreUIManager.class.st b/src/Morphic-Core/MorphicCoreUIManager.class.st index 553e8d93677..014713f033f 100644 --- a/src/Morphic-Core/MorphicCoreUIManager.class.st +++ b/src/Morphic-Core/MorphicCoreUIManager.class.st @@ -10,17 +10,6 @@ Class { #category : #'Morphic-Core-Support' } -{ #category : #'ui requests' } -MorphicCoreUIManager >> checkForNewDisplaySize [ - - "Check whether the screen size has changed and if so take appropriate actions" - - Display extent = DisplayScreen actualScreenSize ifTrue: [^ Display]. - DisplayScreen startUp. - self currentWorld restoreMorphicDisplay. - -] - { #category : #'ui requests' } MorphicCoreUIManager >> currentWorld [ diff --git a/src/Morphic-Core/NullWorldRenderer.class.st b/src/Morphic-Core/NullWorldRenderer.class.st new file mode 100644 index 00000000000..6a5716e14cd --- /dev/null +++ b/src/Morphic-Core/NullWorldRenderer.class.st @@ -0,0 +1,91 @@ +Class { + #name : #NullWorldRenderer, + #superclass : #AbstractWorldRenderer, + #category : #'Morphic-Core-Worlds' +} + +{ #category : #accessing } +NullWorldRenderer class >> priority [ + + ^ 0 +] + +{ #category : #activation } +NullWorldRenderer >> activate [ +] + +{ #category : #operations } +NullWorldRenderer >> activateCursor: aCursor withMask: maskForm [ + + "We don't activate nothing" +] + +{ #category : #accessing } +NullWorldRenderer >> actualScreenSize [ + + ^ 240@120 +] + +{ #category : #accessing } +NullWorldRenderer >> canvas [ + + ^ nil +] + +{ #category : #accessing } +NullWorldRenderer >> canvas: x [ + +] + +{ #category : #'display box access' } +NullWorldRenderer >> checkForNewScreenSize [ + + "Do nothing" +] + +{ #category : #activation } +NullWorldRenderer >> deactivate [ +] + +{ #category : #operations } +NullWorldRenderer >> deferUpdates: aValue [ + + ^ aValue value +] + +{ #category : #operations } +NullWorldRenderer >> displayWorldState: aWorldState ofWorld: aWorld submorphs: submorphs [ + + "Do Nothing" +] + +{ #category : #operations } +NullWorldRenderer >> doDeferredUpdatingFor: aWorld [ + + "Do Nothing" +] + +{ #category : #operations } +NullWorldRenderer >> forceDamageToScreen: allDamage [ + + "Do Nothing" + +] + +{ #category : #operations } +NullWorldRenderer >> forceDisplayUpdate [ + + " Do Nothing " +] + +{ #category : #'display box access' } +NullWorldRenderer >> usableArea [ + + ^ self actualScreenSize +] + +{ #category : #'display box access' } +NullWorldRenderer >> viewBox [ + + ^ self actualScreenSize +] diff --git a/src/Morphic-Core/VMWorldRenderer.class.st b/src/Morphic-Core/VMWorldRenderer.class.st new file mode 100644 index 00000000000..89dd08124da --- /dev/null +++ b/src/Morphic-Core/VMWorldRenderer.class.st @@ -0,0 +1,194 @@ +Class { + #name : #VMWorldRenderer, + #superclass : #AbstractWorldRenderer, + #instVars : [ + 'display', + 'canvas' + ], + #category : #'Morphic-Core-Worlds' +} + +{ #category : #accessing } +VMWorldRenderer class >> priority [ + + ^ 1 +] + +{ #category : #activation } +VMWorldRenderer >> activate [ + + InputEventFetcher default startUp. + InputEventSensor installMouseDecodeTable. + InputEventSensor default startUp. + + Display setExtent: self actualScreenSize depth: 32. + Display beDisplay. + + canvas := nil. + display := nil. + + self assuredCanvas. + DisplayScreen refreshHostWindowTitle. + Display forceDisplayUpdate. + World displayWorld. +] + +{ #category : #operations } +VMWorldRenderer >> activateCursor: aCursor withMask: maskForm [ + + aCursor beCursorWithMask: maskForm + +] + +{ #category : #accessing } +VMWorldRenderer >> actualScreenSize [ + + + + self primitiveFailed +] + +{ #category : #'display box access' } +VMWorldRenderer >> assuredCanvas [ + (self canvas isNil + or: [ self canvas extent ~= self viewBox extent + or: [ self canvas form depth ~= Display depth ] ]) + ifTrue: + [ "allocate a new offscreen canvas the size of the window" + self canvas: (Display defaultCanvasClass extent: self viewBox extent) ]. + ^ self canvas +] + +{ #category : #accessing } +VMWorldRenderer >> canvas [ + + ^ canvas +] + +{ #category : #accessing } +VMWorldRenderer >> canvas: x [ + canvas := x +] + +{ #category : #'display box access' } +VMWorldRenderer >> checkForNewDisplaySize [ + + "Check whether the screen size has changed and if so take appropriate actions" + + Display extent = DisplayScreen actualScreenSize ifTrue: [^ Display]. + + Display setExtent: self actualScreenSize depth: 32. + Display beDisplay. + + World restoreMorphicDisplay. + +] + +{ #category : #'display box access' } +VMWorldRenderer >> checkForNewScreenSize [ + + self checkForNewDisplaySize +] + +{ #category : #activation } +VMWorldRenderer >> deactivate [ + + WorldMorph currentWorld ifNotNil: [:world | world triggerEvent: #aboutToLeaveWorld ]. + WorldMorph extraWorldList do: [:world | world triggerEvent: #aboutToLeaveWorld ]. + + InputEventSensor default shutDown. + + Display shutDown. + + InputEventFetcher default shutDown. + +] + +{ #category : #operations } +VMWorldRenderer >> deferUpdates: aValue [ + + ^ Display deferUpdates: aValue +] + +{ #category : #operations } +VMWorldRenderer >> displayWorldState: aWorldState ofWorld: aWorld submorphs: submorphs [ + "Update this world's display." + + | deferredUpdateMode handsToDraw allDamage | + submorphs do: [ :m | m fullBounds ]. "force re-layout if needed" + + aWorldState checkIfUpdateNeeded + ifFalse: [ ^ self ]. "display is already up-to-date" + + deferredUpdateMode := self doDeferredUpdatingFor: aWorld. + deferredUpdateMode + ifFalse: [ self assuredCanvas ]. + + self canvas + ifNotNil: [ + self canvas + roundCornersOf: aWorld + during: [ | worldDamageRects handDamageRects | + worldDamageRects := aWorldState drawWorld: aWorld submorphs: submorphs invalidAreasOn: self canvas. "repair world's damage on canvas" + "self handsDo:[:h| h noticeDamageRects: worldDamageRects]." + handsToDraw := aWorldState selectHandsToDrawForDamage: worldDamageRects. + handDamageRects := handsToDraw collect: [ :h | h savePatchFrom: self canvas ]. + allDamage := worldDamageRects , handDamageRects. + handsToDraw reverseDo: [ :h | "draw hands onto world canvas" self canvas fullDrawMorph: h ] ] ]. + "*make this true to flash damaged areas for testing*" + + aWorldState class debugShowDamage + ifTrue: [ aWorld flashRects: allDamage color: Color black ]. + + "Check that the canvas is not already freed when we want to finish it" + self canvas ifNotNil: [ :c | c finish ]. + + "quickly copy altered rects of canvas to Display:" + deferredUpdateMode + ifTrue: [ self forceDamageToScreen: allDamage ] + ifFalse: [ self canvas showAt: aWorld viewBox origin invalidRects: allDamage ]. + + handsToDraw do: [ :h | h restoreSavedPatchOn: self canvas ]. "restore world canvas under hands" + + self + deferUpdates: false; + forceDisplayUpdate +] + +{ #category : #operations } +VMWorldRenderer >> doDeferredUpdatingFor: aWorld [ +"If this platform supports deferred updates, then make my canvas be the Display (or a rectangular portion of it), set the Display to deferred update mode, and answer true. Otherwise, do nothing and answer false. One can set the class variable DisableDeferredUpdates to true to completely disable the deferred updating feature." + + (Display deferUpdates: true) ifNil: [^ false]. "deferred updates not supported" + + (self canvas notNil and: [self canvas form == Display]) ifFalse: [ + aWorld viewBox: self viewBox. "do first since it may clear canvas" + self canvas: (Display getCanvas copyClipRect: Display boundingBox)]. + + ^ true +] + +{ #category : #operations } +VMWorldRenderer >> forceDamageToScreen: allDamage [ + + ^ Display forceDamageToScreen: allDamage. + +] + +{ #category : #operations } +VMWorldRenderer >> forceDisplayUpdate [ + + ^ Display forceDisplayUpdate +] + +{ #category : #'display box access' } +VMWorldRenderer >> usableArea [ + + ^ Display usableArea +] + +{ #category : #'display box access' } +VMWorldRenderer >> viewBox [ + + ^ Display boundingBox +] diff --git a/src/Morphic-Core/WorldMorph.class.st b/src/Morphic-Core/WorldMorph.class.st index a911aa479c2..39d3dbe163c 100644 --- a/src/Morphic-Core/WorldMorph.class.st +++ b/src/Morphic-Core/WorldMorph.class.st @@ -7,11 +7,6 @@ A World, the entire Smalltalk screen, is a PasteUpMorph. A World responds true Class { #name : #WorldMorph, #superclass : #PasteUpMorph, - #instVars : [ - 'osWindow', - 'osWindowMutex', - 'session' - ], #classVars : [ 'AllowDropFiles', 'CursorOwnerWorld', @@ -113,11 +108,6 @@ WorldMorph class >> extraWorldList [ ^ ExtraWorldList ] -{ #category : #'initialize-release' } -WorldMorph class >> initialize [ - SessionManager default registerGuiClassNamed: self name. -] - { #category : #'extra worlds' } WorldMorph class >> removeExtraWorld: aWorld [ ExtraWorldList := self extraWorldList copyWithout: aWorld. @@ -125,34 +115,11 @@ WorldMorph class >> removeExtraWorld: aWorld [ ] -{ #category : #'system startup' } -WorldMorph class >> shutDown [ - self currentWorld ifNotNil: [:world | world triggerEvent: #aboutToLeaveWorld ]. - self extraWorldList do: [:world | world triggerEvent: #aboutToLeaveWorld ]. -] - -{ #category : #'system startup' } -WorldMorph class >> startUp [ - self currentWorld ifNotNil: [:world | world restoreMorphicDisplay]. - self extraWorldList do: #restoreMorphicDisplay. -] +{ #category : #'as yet unclassified' } +WorldMorph >> activateCursor: aCursor withMask: maskForm [ -{ #category : #cursor } -WorldMorph >> activateCursor: aCursor [ - osWindow ifNil: [ - aCursor beCursor - ] ifNotNil: [ - osWindow setMouseCursor: aCursor - ] -] + worldState worldRenderer activateCursor: aCursor withMask: maskForm -{ #category : #cursor } -WorldMorph >> activateCursor: aCursor withMask: maskForm [ - osWindow ifNil: [ - aCursor beCursorWithMask: maskForm - ] ifNotNil: [ - osWindow setMouseCursor: aCursor mask: maskForm - ] ] { #category : #structure } @@ -171,12 +138,8 @@ WorldMorph >> activeHand: aHandMorph [ { #category : #accessing } WorldMorph >> actualScreenSize [ - "Obtains the screen size from VM. Since this may change depending on which world is installed - (worlds can change, yes), this needs to be delegated here allowing subclasses to redefine the way - they take screen size." - - self primitiveFailed + ^ self worldState worldRenderer actualScreenSize ] { #category : #'alarms-scheduler' } @@ -223,11 +186,6 @@ WorldMorph >> announcer [ ^ WorldAnnouncer ] -{ #category : #'world state' } -WorldMorph >> assuredCanvas [ - ^ worldState assuredCanvas -] - { #category : #cursor } WorldMorph >> beCursorOwner [ self class cursorOwnerWorld: self @@ -316,7 +274,7 @@ WorldMorph >> discoveredWorldMenu [ { #category : #accessing } WorldMorph >> displayArea [ - ^ Display usableArea. + ^ self worldState worldRenderer usableArea. ] { #category : #geometry } @@ -327,6 +285,7 @@ WorldMorph >> displayScaleFactor [ { #category : #'world state' } WorldMorph >> displayWorld [ + worldState displayWorld: self submorphs: submorphs ] @@ -362,8 +321,7 @@ WorldMorph >> extent: aPoint [ super extent: aPoint. worldState viewBox ifNotNil: [ - worldState canvas: nil. - worldState viewBox: bounds ] + worldState canvas: nil ] ] { #category : #'project state' } @@ -471,16 +429,6 @@ WorldMorph >> mouseDown: evt [ self currentWindow ifNotNil: [ :topWindow | SystemWindow passivateTopWindow ] ] -{ #category : #geometry } -WorldMorph >> position: aPoint [ - "Prevent moving a world (e.g. via HandMorph>>specialGesture:)" - - super position: aPoint. - self viewBox ifNotNil: [:viewBox | self viewBox: (aPoint extent: viewBox extent)]. - - -] - { #category : #printing } WorldMorph >> printOn: aStream [ "Reimplemented to add a tag showing that the receiver is currently functioning as a 'world', if it is" @@ -492,7 +440,8 @@ WorldMorph >> printOn: aStream [ { #category : #private } WorldMorph >> privateMoveBy: delta [ super privateMoveBy: delta. - worldState viewBox ifNotNil: [ worldState viewBox: bounds ] + + ] { #category : #'event handling' } @@ -608,7 +557,7 @@ WorldMorph >> viewBox: newViewBox [ (self viewBox isNil or: [ self viewBox extent ~= newViewBox extent ]) ifTrue: [ worldState canvas: nil ]. - worldState viewBox: newViewBox. + super viewBox: newViewBox. worldState handsDo: [ :hand | hand releaseKeyboardFocus ]. self fullRepaintNeeded @@ -649,3 +598,9 @@ WorldMorph >> worldMenu [ ^ worldState worldMenu ] + +{ #category : #accessing } +WorldMorph >> worldState [ + + ^ worldState +] diff --git a/src/Morphic-Core/WorldState.class.st b/src/Morphic-Core/WorldState.class.st index aa696a75fee..586b9ad1771 100644 --- a/src/Morphic-Core/WorldState.class.st +++ b/src/Morphic-Core/WorldState.class.st @@ -9,8 +9,6 @@ Class { #superclass : #Object, #instVars : [ 'hands', - 'viewBox', - 'canvas', 'damageRecorder', 'stepList', 'lastStepTime', @@ -20,7 +18,8 @@ Class { 'lastAlarmTime', 'menuBuilder', 'activeHand', - 'currentCursor' + 'currentCursor', + 'worldRenderer' ], #classVars : [ 'CanSurrenderToOS', @@ -346,25 +345,15 @@ WorldState >> alarms [ ^alarms ifNil: [alarms := Heap sortBlock: self alarmSortBlock] ] -{ #category : #canvas } -WorldState >> assuredCanvas [ - - (canvas isNil or: [(canvas extent ~= viewBox extent) or: [canvas form depth ~= Display depth]]) - ifTrue: - ["allocate a new offscreen canvas the size of the window" - self canvas: (Display defaultCanvasClass extent: viewBox extent)]. - ^ self canvas -] - { #category : #canvas } WorldState >> canvas [ - ^ canvas + ^ self worldRenderer canvas ] { #category : #canvas } WorldState >> canvas: x [ - canvas := x. + self worldRenderer canvas: x. damageRecorder ifNil: [damageRecorder := DamageRecorder new] ifNotNil: [damageRecorder doFullRepaint] @@ -373,8 +362,10 @@ WorldState >> canvas: x [ { #category : #'update cycle' } WorldState >> checkIfUpdateNeeded [ - damageRecorder updateIsNeeded ifTrue: [^true]. - hands do: [:h | (h hasChanged and: [h needsToBeDrawn]) ifTrue: [^true]]. + damageRecorder updateIsNeeded ifTrue: [ ^true ]. + + hands do: [:h | + (h hasChanged and: [h needsToBeDrawn]) ifTrue: [^true]]. ^false "display is already up-to-date" ] @@ -426,6 +417,12 @@ WorldState >> currentCursor: anObject [ currentCursor := anObject ] +{ #category : #accessing } +WorldState >> damageRecorder [ + + ^ damageRecorder +] + { #category : #'deferred message' } WorldState >> defer: aValuable [ "aValuable will be executed in the next UI rendering cycle" @@ -452,37 +449,7 @@ WorldState >> discoveredMenuTitle [ WorldState >> displayWorld: aWorld submorphs: submorphs [ "Update this world's display." - | deferredUpdateMode handsToDraw allDamage | - submorphs do: [ :m | m fullBounds ]. "force re-layout if needed" - self checkIfUpdateNeeded - ifFalse: [ ^ self ]. "display is already up-to-date" - deferredUpdateMode := self doDeferredUpdatingFor: aWorld. - deferredUpdateMode - ifFalse: [ self assuredCanvas ]. - canvas - ifNotNil: [ :c | - c - roundCornersOf: aWorld - during: [ | worldDamageRects handDamageRects | - worldDamageRects := self drawWorld: aWorld submorphs: submorphs invalidAreasOn: canvas. "repair world's damage on canvas" - "self handsDo:[:h| h noticeDamageRects: worldDamageRects]." - handsToDraw := self selectHandsToDrawForDamage: worldDamageRects. - handDamageRects := handsToDraw collect: [ :h | h savePatchFrom: canvas ]. - allDamage := worldDamageRects , handDamageRects. - handsToDraw reverseDo: [ :h | "draw hands onto world canvas" canvas fullDrawMorph: h ] ] ]. - "*make this true to flash damaged areas for testing*" - self class debugShowDamage - ifTrue: [ aWorld flashRects: allDamage color: Color black ]. - "Check that the canvas is not already freed when we want to finish it" - canvas ifNotNil: [ :c | c finish ]. - "quickly copy altered rects of canvas to Display:" - deferredUpdateMode - ifTrue: [ self forceDamageToScreen: allDamage ] - ifFalse: [ canvas showAt: aWorld viewBox origin invalidRects: allDamage ]. - handsToDraw do: [ :h | h restoreSavedPatchOn: canvas ]. "restore world canvas under hands" - Display - deferUpdates: false; - forceDisplayUpdate + worldRenderer displayWorldState: self ofWorld: aWorld submorphs: submorphs ] { #category : #'update cycle' } @@ -511,18 +478,6 @@ WorldState >> displayWorldSafely: aWorld [ ]. ] -{ #category : #'update cycle' } -WorldState >> doDeferredUpdatingFor: aWorld [ - "If this platform supports deferred updates, then make my canvas be the Display (or a rectangular portion of it), set the Display to deferred update mode, and answer true. Otherwise, do nothing and answer false. One can set the class variable DisableDeferredUpdates to true to completely disable the deferred updating feature." - - (Display deferUpdates: true) ifNil: [^ false]. "deferred updates not supported" - (canvas notNil and: [canvas form == Display]) ifFalse: [ - aWorld viewBox: Display boundingBox. "do first since it may clear canvas" - self canvas: (Display getCanvas copyClipRect: Display boundingBox)]. - ^ true - -] - { #category : #canvas } WorldState >> doFullRepaint [ @@ -543,7 +498,7 @@ WorldState >> doOneCycleNowFor: aWorld [ "Immediately do one cycle of the interaction loop. This should not be called directly, but only via doOneCycleFor:" - DisplayScreen checkForNewScreenSize. + self worldRenderer checkForNewScreenSize. "process user input events" LastCycleTime := Time millisecondClockValue. @@ -646,17 +601,10 @@ WorldState >> fallbackMenuOn: menu [ selector: #quitSession. ] -{ #category : #'update cycle' } -WorldState >> forceDamageToScreen: allDamage [ - - Display forceDamageToScreen: allDamage. - -] - { #category : #'update cycle' } WorldState >> handleFatalDrawingError: errMsg [ "Handle a fatal drawing error." - Display deferUpdates: false. "Just in case" + self worldRenderer deferUpdates: false. "Just in case" self primitiveError: errMsg. "Hm... we should jump into a 'safe' worldState here, but how do we find it?!" @@ -689,7 +637,7 @@ WorldState >> initialize [ stepList := Heap sortBlock: self stepListSortBlock. lastStepTime := 0. lastAlarmTime := 0. - self viewBox: Display boundingBox + ] { #category : #'update cycle' } @@ -899,16 +847,24 @@ WorldState >> triggerAlarmsBefore: nowTime [ { #category : #canvas } WorldState >> viewBox [ - ^ viewBox -] - -{ #category : #canvas } -WorldState >> viewBox: x [ - - viewBox := x + ^ self worldRenderer viewBox ] { #category : #'worldmenu building' } WorldState >> worldMenu [ ^self menuBuilder menuEntitled: self discoveredMenuTitle. ] + +{ #category : #hands } +WorldState >> worldRenderer [ + + ^ worldRenderer ifNil: [ worldRenderer := NullWorldRenderer new ] +] + +{ #category : #accessing } +WorldState >> worldRenderer: anObject [ + + worldRenderer deactivate. + worldRenderer := anObject. + worldRenderer activate +] diff --git a/src/NECompletion/NECController.class.st b/src/NECompletion/NECController.class.st index 207cf35b7fa..2566979718c 100644 --- a/src/NECompletion/NECController.class.st +++ b/src/NECompletion/NECController.class.st @@ -565,8 +565,9 @@ NECController >> smartStartIndexIn: currentText for: smartCharacter opposite: o { #category : #private } NECController >> stopCompletionDelay [ - - completionDelay ifNotNil: [ completionDelay terminate ]. + + completionDelay ifNotNil: [ + completionDelay isTerminating ifFalse: [ completionDelay terminate ] ] ] { #category : #accessing } diff --git a/src/OSWindow-Core/OSWindow.class.st b/src/OSWindow-Core/OSWindow.class.st index 1ab1a1d19be..3268d11cfbf 100644 --- a/src/OSWindow-Core/OSWindow.class.st +++ b/src/OSWindow-Core/OSWindow.class.st @@ -152,6 +152,7 @@ OSWindow >> deliverEvent: anEvent [ "TODO..." TraceEvents == true ifTrue: [ Transcript show: anEvent; cr ]. + eventHandler ifNotNil: [ eventHandler handleEvent: anEvent ]. anEvent performDefaultAction diff --git a/src/OSWindow-Core/OSWindowMorphicEventHandler.class.st b/src/OSWindow-Core/OSWindowMorphicEventHandler.class.st index 6f66bf69934..8e79653bf54 100644 --- a/src/OSWindow-Core/OSWindowMorphicEventHandler.class.st +++ b/src/OSWindow-Core/OSWindowMorphicEventHandler.class.st @@ -104,6 +104,7 @@ OSWindowMorphicEventHandler >> convertModifiers: modifiers [ { #category : #events } OSWindowMorphicEventHandler >> dispatchMorphicEvent: anEvent [ morphicWorld defer: [ + (morphicWorld activeHand isNotNil and: [ anEvent hand isNotNil ]) ifTrue: [ morphicWorld activeHand handleEvent: anEvent ] @@ -135,7 +136,7 @@ OSWindowMorphicEventHandler >> handleEvent: anEvent [ morphicEvent := anEvent accept: self. morphicEvent isMorphicEvent ifFalse: [ ^ self ]. - + self dispatchMorphicEvent: morphicEvent ] @@ -322,12 +323,6 @@ OSWindowMorphicEventHandler >> visitWindowCloseEvent: anEvent [ morphicWorld osWindowCloseButtonPressed ] -{ #category : #visiting } -OSWindowMorphicEventHandler >> visitWindowExposeEvent: anEvent [ - "Make sure that the renderer for this window exist." - morphicWorld osWindowRenderer -] - { #category : #visiting } OSWindowMorphicEventHandler >> visitWindowResizeEvent: anEvent [ diff --git a/src/OSWindow-Core/OSWindowWorldMorph.class.st b/src/OSWindow-Core/OSWindowWorldMorph.class.st index 8f564002a08..5335406866d 100644 --- a/src/OSWindow-Core/OSWindowWorldMorph.class.st +++ b/src/OSWindow-Core/OSWindowWorldMorph.class.st @@ -158,3 +158,9 @@ OSWindowWorldMorph >> updateDisplay [ worldState display: display ] ] + +{ #category : #accessing } +OSWindowWorldMorph >> worldState [ + + ^ worldState +] diff --git a/src/OSWindow-Core/WorldMorph.extension.st b/src/OSWindow-Core/WorldMorph.extension.st index 2b1473d3d72..e7b9caf94b8 100644 --- a/src/OSWindow-Core/WorldMorph.extension.st +++ b/src/OSWindow-Core/WorldMorph.extension.st @@ -10,14 +10,6 @@ WorldMorph >> checkNewWindowSize [ ] ] -{ #category : #'*OSWindow-Core' } -WorldMorph >> checkSession [ - session == Smalltalk session ifFalse: [ - self recreateOSWindow. - session := Smalltalk session. - ] -] - { #category : #'*OSWindow-Core' } WorldMorph >> clipboardText [ ^ self osWindow clipboardText @@ -27,99 +19,3 @@ WorldMorph >> clipboardText [ WorldMorph >> clipboardText: aString [ ^ self osWindow clipboardText: aString ] - -{ #category : #'*OSWindow-Core' } -WorldMorph >> osWindow [ - self osWindowCritical: [ - self checkSession. - ^ osWindow - ] - - -] - -{ #category : #'*OSWindow-Core' } -WorldMorph >> osWindowCritical: aBlock [ - self flag: 'HACK: Try to remove this lazy initialization'. - osWindowMutex ifNil: [ osWindowMutex := Mutex new ]. - ^ osWindowMutex critical: aBlock - -] - -{ #category : #'*OSWindow-Core' } -WorldMorph >> osWindowRenderer [ - self osWindowCritical: [ - ^ self osWindow ifNotNil: [:window | - window renderer ifNil: [ - self osWindow newFormRenderer: Display. - self osWindow renderer - ]. - ] - ] - - -] - -{ #category : #'*OSWindow-Core' } -WorldMorph >> pickMostSuitableWindowDriver [ - "TODO: check for headless mode" - | driver | - - driver := OSWindowDriver current. - - "well, lets try using the VM driver" - (driver isNullDriver and: [VMWindowDriver isSupported]) ifTrue: [ - ^ VMWindowDriver new ]. - - ^ driver -] - -{ #category : #'*OSWindow-Core' } -WorldMorph >> recreateOSWindow [ - | attributes driver | - session := Smalltalk session. - attributes := OSWindowAttributes new. - attributes - extent: self extent; - title: Smalltalk shortImageName; - icon: (self iconNamed: #pharoIcon). - driver := self pickMostSuitableWindowDriver. - attributes preferableDriver: driver. - osWindow := OSWindow createWithAttributes: attributes eventHandler: (OSWindowMorphicEventHandler for: self) -] - -{ #category : #'*OSWindow-Core' } -WorldMorph >> updateOnOSWindow [ - "Update this world's display." - - | handsToDraw allDamage worldDamageRects handDamageRects canvas | - - submorphs do: [:m | m fullBounds]. "force re-layout if needed" - worldState checkIfUpdateNeeded ifFalse: [^ self]. "display is already up-to-date" - - canvas := self osWindowRenderer getCanvas. - - self osWindowRenderer deferUpdatesWhile: [ - - worldDamageRects := worldState drawWorld: self submorphs: submorphs invalidAreasOn: canvas. "repair world's damage on canvas" - "self handsDo:[:h| h noticeDamageRects: worldDamageRects]." - handsToDraw := worldState selectHandsToDrawForDamage: worldDamageRects. - handDamageRects := handsToDraw collect: [:h | h savePatchFrom: canvas]. - allDamage := worldDamageRects, handDamageRects. - - handsToDraw reverseDo: [:h | canvas fullDrawMorph: h]. "draw hands onto world canvas" - - "*make this true to flash damaged areas for testing*" - WorldState debugShowDamage ifTrue: [self flashRects: allDamage color: Color black]. - - canvas finish. - "quickly copy altered rects of canvas to Display:" - - - self osWindowRenderer updateAreas: allDamage immediate: false. - - handsToDraw do: [:h | h restoreSavedPatchOn: canvas]. "restore world canvas under hands" - ]. -" self osWindowRenderer forceDisplayUpdate." - -] diff --git a/src/OSWindow-SDL2/OSSDL2Driver.class.st b/src/OSWindow-SDL2/OSSDL2Driver.class.st index 095c41a857b..e6e82e8a84b 100644 --- a/src/OSWindow-SDL2/OSSDL2Driver.class.st +++ b/src/OSWindow-SDL2/OSSDL2Driver.class.st @@ -65,8 +65,9 @@ OSSDL2Driver >> convertEvent: sdlEvent [ WindowMapMutex critical: [ window := WindowMap at: mappedEvent windowID ifAbsent: [ ^ nil ]. ]. - window handleNewSDLEvent: mappedEvent. - ^ nil + + ^ window handleNewSDLEvent: mappedEvent. + ] @@ -179,9 +180,10 @@ OSSDL2Driver >> initialize [ initializeWindowMap; initializeJoystickMap. SDL2 - initVideo; +" initVideo; initJoystick; - initGameController. + initGameController; +" initEverything. self setupEventLoop. ] @@ -244,8 +246,10 @@ OSSDL2Driver >> primitiveSetVMSDL2Input: semaIndex [ { #category : #'events-processing' } OSSDL2Driver >> processEvent: sdlEvent [ | event | + [ event := self convertEvent: sdlEvent. + event ifNotNil: [ eventQueue nextPut: event ]. ] on: Error do: [ :err | "It is critical, that event handling keep running despite errors. @@ -326,7 +330,8 @@ OSSDL2Driver >> shutDown [ remaining on restart)" WindowMap := nil. - JoystickMap := nil + JoystickMap := nil. + EventLoopProcess ifNotNil: [ EventLoopProcess terminate ]. ] { #category : #'global events' } diff --git a/src/OSWindow-SDL2/OSSDL2WindowHandle.class.st b/src/OSWindow-SDL2/OSSDL2WindowHandle.class.st index a38f1a3b2bb..76da4af3d3e 100644 --- a/src/OSWindow-SDL2/OSSDL2WindowHandle.class.st +++ b/src/OSWindow-SDL2/OSSDL2WindowHandle.class.st @@ -18,7 +18,7 @@ Class { } { #category : #'instance creation' } -OSSDL2WindowHandle class >> newWithHandle: handle attributes: attributes. [ +OSSDL2WindowHandle class >> newWithHandle: handle attributes: attributes [. ^ self basicNew initWithHandle: handle attributes: attributes; yourself ] diff --git a/src/OSWindow-SDL2/SDL2.class.st b/src/OSWindow-SDL2/SDL2.class.st index 60efe552bd3..5fbc3bb450c 100644 --- a/src/OSWindow-SDL2/SDL2.class.st +++ b/src/OSWindow-SDL2/SDL2.class.st @@ -182,6 +182,12 @@ SDL2 class >> init: flags [ ^ self ffiCall: #( int SDL_Init ( Uint32 flags ) ) ] +{ #category : #common } +SDL2 class >> initEverything [ + self initLibrary; + initSubSystem: SDL_INIT_EVERYTHING +] + { #category : #common } SDL2 class >> initGameController [ self initLibrary; diff --git a/src/Polymorph-Widgets/MorphicUIManager.class.st b/src/Polymorph-Widgets/MorphicUIManager.class.st index a1f64f2b70b..b405e163ee1 100644 --- a/src/Polymorph-Widgets/MorphicUIManager.class.st +++ b/src/Polymorph-Widgets/MorphicUIManager.class.st @@ -31,6 +31,13 @@ MorphicUIManager class >> isValidForCurrentSystemConfiguration [ { #category : #private } MorphicUIManager >> activate [ + + World worldState worldRenderer: (VMWorldRenderer forWorld: World). + Cursor currentCursor: Cursor currentCursor. + + WorldMorph currentWorld ifNotNil: [:world | world restoreMorphicDisplay]. + WorldMorph extraWorldList do: #restoreMorphicDisplay. + activeTranscript ifNil: [ Transcript class == ThreadSafeTranscript ifFalse: [ @@ -42,17 +49,6 @@ MorphicUIManager >> activate [ SystemProgressMorph enable. ] -{ #category : #'ui requests' } -MorphicUIManager >> checkForNewDisplaySize [ - - "Check whether the screen size has changed and if so take appropriate actions" - - Display extent = DisplayScreen actualScreenSize ifTrue: [^ Display]. - DisplayScreen startUp. - self currentWorld restoreMorphicDisplay. - -] - { #category : #'ui requests' } MorphicUIManager >> chooseDirectory: label from: dir [ "Answer the user choice of a directory." @@ -277,6 +273,8 @@ MorphicUIManager >> currentWorld [ MorphicUIManager >> deactivate [ activeTranscript := Transcript. SystemProgressMorph disable. + + World worldState worldRenderer: (NullWorldRenderer forWorld: World). ] { #category : #debug } diff --git a/src/System-SessionManager/UIManagerSessionHandler.class.st b/src/System-SessionManager/UIManagerSessionHandler.class.st index 292c4c4e257..ee6e895c6cc 100644 --- a/src/System-SessionManager/UIManagerSessionHandler.class.st +++ b/src/System-SessionManager/UIManagerSessionHandler.class.st @@ -35,12 +35,18 @@ UIManagerSessionHandler >> handledId [ { #category : #handlers } UIManagerSessionHandler >> shutdown: isImageQuitting [ + "Prepare the shutdown and the next startup" - UIManager default: StartupUIManager new + + UIManager default: StartupUIManager new. + ] { #category : #handlers } UIManagerSessionHandler >> startup: isImageStarting [ "Install the right UIManager" + UIManager default: UIManager forCurrentSystemConfiguration. + + ] diff --git a/src/System-VMEvents/InputEventFetcher.class.st b/src/System-VMEvents/InputEventFetcher.class.st index 934d4396a44..2240658efb6 100644 --- a/src/System-VMEvents/InputEventFetcher.class.st +++ b/src/System-VMEvents/InputEventFetcher.class.st @@ -99,10 +99,8 @@ InputEventFetcher class >> deinstall [ Default ifNotNil: [ Default shutDown. - SessionManager default unregisterClassNamed: Default class name. Default := nil]. - SessionManager default unregisterClassNamed: self name ] { #category : #'class initialization' } @@ -110,25 +108,6 @@ InputEventFetcher class >> install [ "InputEventFetcher install" Default := self new. Default startUp. - - SessionManager default - registerSystemClassNamed: self name - atPriority: 40. - -] - -{ #category : #'system startup' } -InputEventFetcher class >> shutDown [ - "InputEventFetcher shutDown" - - self default shutDown -] - -{ #category : #'system startup' } -InputEventFetcher class >> startUp [ - "InputEventFetcher startUp" - - self default startUp ] { #category : #private } diff --git a/src/System-VMEvents/InputEventSensor.class.st b/src/System-VMEvents/InputEventSensor.class.st index 5c3bace4472..59cd583c034 100644 --- a/src/System-VMEvents/InputEventSensor.class.st +++ b/src/System-VMEvents/InputEventSensor.class.st @@ -97,17 +97,6 @@ InputEventSensor class >> installMouseDecodeTable [ ifFalse: [ByteArray withAll: (0 to: 255)] ] -{ #category : #'system startup' } -InputEventSensor class >> shutDown [ - self default shutDown. -] - -{ #category : #'system startup' } -InputEventSensor class >> startUp [ - self installMouseDecodeTable. - self default startUp -] - { #category : #settings } InputEventSensor class >> swapMouseButtons [ ^ Smalltalk os isWindows not diff --git a/src/UIManager/CommandLineUIManager.class.st b/src/UIManager/CommandLineUIManager.class.st index e60d4df26eb..f69fa492d3d 100644 --- a/src/UIManager/CommandLineUIManager.class.st +++ b/src/UIManager/CommandLineUIManager.class.st @@ -90,11 +90,6 @@ CommandLineUIManager >> alert: aStringOrText title: aString configure: aBlock [ self alert: aStringOrText title: aString. ] -{ #category : #display } -CommandLineUIManager >> checkForNewDisplaySize [ - "do nothing" -] - { #category : #'ui requests' } CommandLineUIManager >> choose: questionsAnswerDict title: queryString [ diff --git a/src/UIManager/UIManager.class.st b/src/UIManager/UIManager.class.st index f3e6edd5280..63d4e52826f 100644 --- a/src/UIManager/UIManager.class.st +++ b/src/UIManager/UIManager.class.st @@ -105,12 +105,6 @@ UIManager >> beDefault [ self class default: self. ] -{ #category : #display } -UIManager >> checkForNewDisplaySize [ - - self subclassResponsibility -] - { #category : #'ui requests' } UIManager >> chooseDirectory [ "Let the user choose a directory"