Skip to content

Commit

Permalink
Taskbar option to close windows hidden behind other windows
Browse files Browse the repository at this point in the history
  • Loading branch information
pavel-krivanek committed Apr 29, 2024
1 parent 4ca1de3 commit 5e72f8f
Showing 1 changed file with 24 additions and 2 deletions.
26 changes: 24 additions & 2 deletions src/Morphic-Widgets-Taskbar/SystemWindow.extension.st
Original file line number Diff line number Diff line change
Expand Up @@ -216,6 +216,11 @@ SystemWindow >> taskbarButtonMenu: aMenu [
getStateSelector: nil
enablementSelector: true.
submenu
addToggle: 'hidden windows' translated
target: self
selector: #taskbarCloseHiddenWindows
getStateSelector: nil
enablementSelector: true. submenu
addToggle: 'close all debuggers' translated
target: OupsDebuggerSystem
selector: #closeAllDebuggers
Expand All @@ -238,9 +243,9 @@ SystemWindow >> taskbarButtonMenu: aMenu [
{ #category : '*Morphic-Widgets-Taskbar' }
SystemWindow >> taskbarCloseAllLikeThis [

(self confirm: 'Do you really want to close all windows like this ?') ifFalse: [
(self confirm: 'Do you really want to close all windows like this?') ifFalse: [
^ self ].
(SystemWindow allSubInstances select: [ :w | w labelString = self labelString]) do: [ :w | w delete ]
(self class allSubInstances select: [ :w | w labelString = self labelString]) do: [ :w | w delete ]
]

{ #category : '*Morphic-Widgets-Taskbar' }
Expand Down Expand Up @@ -278,6 +283,23 @@ SystemWindow >> taskbarCloseAllWindows [
worldTaskbar tasks do: [ :task | task morph delete ] ]
]

{ #category : '*Morphic-Widgets-Taskbar' }
SystemWindow >> taskbarCloseHiddenWindows [

| windows invisible parts other |
(self confirm: 'Do you really want to close all windows hidden behind other windows?') ifFalse: [
^ self ].
windows := (self world submorphs select: [:each | each isSystemWindow ]) reversed.
invisible := windows withIndexSelect: [ :win :index |
bounds := win fullBoundsInWorld.
parts := OrderedCollection new.
other := (windows copyFrom: index+1 to: windows size) collect: [:each | each fullBoundsInWorld] .
bounds allAreasOutsideList: other do: [ :each | parts add: each ].
parts isEmpty
].
invisible do: [ :each | each close ].
]

{ #category : '*Morphic-Widgets-Taskbar' }
SystemWindow >> taskbarLabel [
"Answer the label to use for a taskbar button for the receiver."
Expand Down

0 comments on commit 5e72f8f

Please sign in to comment.