[squeak-dev] The Trunk: Morphic-mt.1150.mcz

commits at source.squeak.org commits at source.squeak.org
Fri May 20 09:39:49 UTC 2016


Marcel Taeumel uploaded a new version of Morphic to project The Trunk:
http://source.squeak.org/trunk/Morphic-mt.1150.mcz

==================== Summary ====================

Name: Morphic-mt.1150
Author: mt
Time: 20 May 2016, 11:39:09.641411 am
UUID: 8a07253b-8809-3842-80be-d1b520c4ff6c
Ancestors: Morphic-pre.1149

Refactors system windows wrt. having active background windows as introduced in October 2015.

Two preferences control this:
Windows Active On First Click
Windows Active Only On Top

See their preference descriptions for details. Note that #activeOnlyOnTop used to be a regular message in system windows but was changed into a system-wide preference.

Thanks to Chris for continuous feedback on this!

=============== Diff against Morphic-pre.1149 ===============

Item was added:
+ ----- Method: BorderedMorph>>grips (in category 'resize handling') -----
+ grips
+ 
+ 	^ self submorphsSatisfying: [:each | each isKindOf: CornerGripMorph]!

Item was removed:
- ----- Method: CornerGripMorph>>mouseDown: (in category 'as yet unclassified') -----
- mouseDown: aMouseButtonEvent 
- 	target isSystemWindow ifTrue:
- 		[ target == SystemWindow topWindow ifFalse: [ target activate ] ].
- 	super mouseDown: aMouseButtonEvent!

Item was removed:
- ----- Method: HandMorph>>windowUnderneath (in category 'accessing') -----
- windowUnderneath
- 	ActiveWorld submorphsDo:
- 		[ : each | (each isSystemWindow and: [ each containsPoint: self position ]) ifTrue: [ ^ each ] ].
- 	^ nil!

Item was changed:
+ ----- Method: Morph>>containingWindow (in category 'structure') -----
- ----- Method: Morph>>containingWindow (in category 'e-toy support') -----
  containingWindow
+ 	"Answer a window that contains the receiver. Try to use the model to find the right window. If I do not have a model, use the model of one of my owners. We could also just use #isSystemWindow. This, however, gives system windows the chance to refrain from taking ownership of this morph."
- 	"Answer a window or window-with-mvc that contains the receiver"
  
  	| component |
  	component := self.
  	component model isNil ifTrue: [component := self firstOwnerSuchThat: [:m| m model notNil]].
  	^(component isNil or: [component isWindowForModel: component model])
  		ifTrue: [component]
  		ifFalse: [component firstOwnerSuchThat:[:m| m isWindowForModel: component model]]!

Item was changed:
  ----- Method: Morph>>embedInWindow (in category 'e-toy support') -----
  embedInWindow
  
  	| window worldToUse |
  
  	worldToUse := self world.		"I'm assuming we are already in a world"
  	window := (SystemWindow labelled: self defaultLabelForInspector) model: nil.
  	window bounds: ((self position - ((0 at window labelHeight) + window borderWidth))
  						corner: self bottomRight + window borderWidth).
  	window addMorph: self frame: (0 at 0 extent: 1 at 1).
  	window updatePaneColors.
  	worldToUse addMorph: window.
+ 	window beKeyWindow.!
- 	window activate!

Item was changed:
  ----- Method: Morph>>handleMouseDown: (in category 'events-processing') -----
  handleMouseDown: anEvent
  	"System level event handling."
  	anEvent wasHandled ifTrue:[^self]. "not interested"
  	anEvent hand removePendingBalloonFor: self.
  	anEvent hand removePendingHaloFor: self.
  	anEvent wasHandled: true.
  
  	(anEvent controlKeyPressed
  			and: [anEvent blueButtonChanged not
  				and: [Preferences cmdGesturesEnabled]])
  		ifTrue: [^ self invokeMetaMenu: anEvent].
  
  	"Make me modal during mouse transitions"
  	anEvent hand newMouseFocus: self event: anEvent.
  	(anEvent blueButtonChanged and:[Preferences cmdGesturesEnabled]) ifTrue:[^self blueButtonDown: anEvent].
  	
  	"this mouse down could be the start of a gesture, or the end of a gesture focus"
  	(self isGestureStart: anEvent)
  		ifTrue: [^ self gestureStart: anEvent].
  
+ 	self mouseDown: anEvent.
- 	"Filter events sent to the subwidgets of non-MorphicModels in inactive windows, if they are not supposed to receive them due to windowActiveOnFirstClick being set to false.  I don't like having this check for owningWindow here, is there another way?"
- 	SystemWindow allWindowsAcceptInput 
- 		ifTrue: 
- 			[ self owningWindow
- 				ifNil: [ self mouseDown: anEvent ]
- 				ifNotNil:
- 					[ : owningWindow |
- 					(owningWindow canProcessMouseDown: anEvent)
- 						ifTrue: [ self mouseDown: anEvent ]
- 						ifFalse: [ owningWindow activate ] ] ]
- 		ifFalse: [ self mouseDown: anEvent ].
  
  	Preferences maintainHalos
  		ifFalse:[ anEvent hand removeHaloFromClick: anEvent on: self ].
  
  	(self handlesMouseStillDown: anEvent) ifTrue:[
  		self startStepping: #handleMouseStillDown: 
  			at: Time millisecondClockValue + self mouseStillDownThreshold
  			arguments: {anEvent copy resetHandlerFields}
  			stepTime: self mouseStillDownStepRate ].
  !

Item was changed:
  ----- Method: Morph>>keyboardFocusChange: (in category 'event handling') -----
+ keyboardFocusChange: aBoolean
- keyboardFocusChange: aBoolean 
  	"The message is sent to a morph when its keyboard focus change. The given argument indicates that the receiver is gaining keyboard focus (versus losing) the keyboard focus. Morphs that accept keystrokes should change their appearance in some way when they are the current keyboard focus."
+ 
+ 	self eventHandler
+ 		ifNotNil: [:h | h keyboardFocusChange: aBoolean fromMorph: self].
+ 
+ 	self indicateKeyboardFocus
+ 		ifTrue: [self changed].!
- 	self eventHandler ifNotNil:
- 		[ : h | h
- 			keyboardFocusChange: aBoolean
- 			fromMorph: self ].
- 	"Support for 'Focus Follows Mouse'.  Want the window to maintain focus even after the pointer moves into its title bar."
- 	self owningWindow ifNotNil: [ : window | window lookFocused: (aBoolean or: [ window containsPoint: ActiveHand position]) ].
- 	self indicateKeyboardFocus ifTrue: [ self changed ]!

Item was changed:
  ----- Method: Morph>>openInWindowLabeled:inWorld: (in category 'initialization') -----
  openInWindowLabeled: aString inWorld: aWorld
  
  	| window extent |
  
  	window := (SystemWindow labelled: aString) model: nil.
  	window 
  		" guess at initial extent"
  		bounds:  (RealEstateAgent initialFrameFor: window initialExtent: self fullBounds extent world: aWorld);
  		addMorph: self frame: (0 at 0 extent: 1 at 1);
  		updatePaneColors.
  	" calculate extent after adding in case any size related attributes were changed.  Use
  	fullBounds in order to trigger re-layout of layout morphs"
  	extent := self fullBounds extent + 
  			(window borderWidth at window labelHeight) + window borderWidth.
  	window extent: extent.
  	aWorld addMorph: window.
+ 	window beKeyWindow.
- 	window activate.
  	aWorld startSteppingSubmorphsOf: window.
  	^window
  !

Item was removed:
- ----- Method: Morph>>owningWindow (in category 'private') -----
- owningWindow
- 	self withAllOwnersDo: [ : each | each isSystemWindow ifTrue: [ ^ each ] ].
- 	^ nil!

Item was changed:
  ----- Method: Morph>>undoMove:redo:owner:bounds:predecessor: (in category 'undo') -----
  undoMove: cmd redo: redo owner: formerOwner bounds: formerBounds predecessor: formerPredecessor 
  	"Handle undo and redo of move commands in morphic"
  
  	self owner ifNil: [^Beeper beep].
  	redo 
  		ifFalse: 
  			["undo sets up the redo state first"
  
  			cmd 
  				redoTarget: self
  				selector: #undoMove:redo:owner:bounds:predecessor:
  				arguments: { 
  						cmd.
  						true.
  						owner.
  						bounds.
  						owner morphPreceding: self}].
  	formerOwner ifNotNil: 
  			[formerPredecessor ifNil: [formerOwner addMorphFront: self]
  				ifNotNil: [formerOwner addMorph: self after: formerPredecessor]].
  	self bounds: formerBounds.
+ 	(self isSystemWindow) ifTrue: [self beKeyWindow]!
- 	(self isSystemWindow) ifTrue: [self activate]!

Item was removed:
- ----- Method: MorphicModel>>handleMouseDown: (in category 'events-processing') -----
- handleMouseDown: aMouseEvent 
- 	SystemWindow allWindowsAcceptInput ifTrue:
- 		[ "This override is needed so that, when 'Window Active On First Click' is false, clicking on a PluggableListMorph of an inactive window will, correctly, NOT update the selection in the list; it will only activate the window."
- 		aMouseEvent blueButtonChanged ifFalse:
- 			[ self owningWindow ifNotNil:
- 				[ : window | (window canProcessMouseDown: aMouseEvent) ifFalse: [ ^ window activate ].
- 				Model windowActiveOnFirstClick ifTrue: [ window activate ] ] ] ].
- 	super handleMouseDown: aMouseEvent!

Item was changed:
  ----- Method: PasteUpMorph>>findAWindowSatisfying:orMakeOneUsing: (in category 'world menu') -----
  findAWindowSatisfying: qualifyingBlock orMakeOneUsing: makeBlock 
  	"Locate a window satisfying a block, open it, and bring it to the front.  Create one if necessary, by using the makeBlock"
  
  	submorphs do:
  		[:aMorph | | aWindow | 
  		(((aWindow := aMorph renderedMorph) isSystemWindow) 
  		and: [qualifyingBlock value: aWindow]) ifTrue:
  			[aWindow isCollapsed ifTrue: [aWindow expand].
  			self addMorphFront: aWindow.
+ 			aWindow beKeyWindow.
- 			aWindow activateAndForceLabelToShow.
  			^self]].
  	"None found, so create one"
  	makeBlock value!

Item was changed:
  ----- Method: PasteUpMorph>>findDirtyBrowsers: (in category 'world menu') -----
  findDirtyBrowsers: evt 
  	"Present a menu of window titles for browsers with changes,
  	and activate the one that gets chosen."
  
  	| menu |
  	menu := MenuMorph new.
  	(SystemWindow windowsIn: self
  		satisfying: [:w | (w model isKindOf: Browser) and: [w model canDiscardEdits not]]) 
  			do: 
  				[:w | 
  				menu 
  					add: w label
  					target: w
+ 					action: #beKeyWindow].
- 					action: #activate].
  	menu submorphs notEmpty ifTrue: [menu popUpEvent: evt in: self]!

Item was changed:
  ----- Method: PasteUpMorph>>findDirtyWindows: (in category 'world menu') -----
  findDirtyWindows: evt 
  	"Present a menu of window titles for all windows with changes,
  	and activate the one that gets chosen."
  
  	| menu |
  	menu := MenuMorph new.
  	(SystemWindow windowsIn: self
  		satisfying: [:w | w model canDiscardEdits not]) do: 
  				[:w | 
  				menu 
  					add: w label
  					target: w
+ 					action: #beKeyWindow].
- 					action: #activate].
  	menu submorphs notEmpty ifTrue: [menu popUpEvent: evt in: self]!

Item was changed:
  ----- Method: PasteUpMorph>>findWindow: (in category 'world menu') -----
  findWindow: evt
  	"Present a menu names of windows and naked morphs, and activate the one that gets chosen.  Collapsed windows appear below line, expand if chosen; naked morphs appear below second line; if any of them has been given an explicit name, that is what's shown, else the class-name of the morph shows; if a naked morph is chosen, bring it to front and have it don a halo."
  	| menu expanded collapsed nakedMorphs |
  	menu := MenuMorph new.
  	expanded := SystemWindow windowsIn: self satisfying: [:w | w isCollapsed not].
  	collapsed := SystemWindow windowsIn: self satisfying: [:w | w isCollapsed].
  	nakedMorphs := self submorphsSatisfying:
  		[:m | (m isSystemWindow not and: [(m isStickySketchMorph) not]) and:
  			[(m isFlapTab) not]].
  	(expanded isEmpty & (collapsed isEmpty & nakedMorphs isEmpty)) ifTrue: [^ Beeper beep].
  	(expanded asSortedCollection: [:w1 :w2 | w1 label caseInsensitiveLessOrEqual: w2 label]) do:
+ 		[:w | menu add: w label target: w action: #beKeyWindow.
- 		[:w | menu add: w label target: w action: #activateAndForceLabelToShow.
  			w model canDiscardEdits ifFalse: [menu lastItem color: Color red]].
  	(expanded isEmpty | (collapsed isEmpty & nakedMorphs isEmpty)) ifFalse: [menu addLine].
  	(collapsed asSortedCollection: [:w1 :w2 | w1 label caseInsensitiveLessOrEqual: w2 label]) do: 
  		[:w | menu add: w label target: w action: #collapseOrExpand.
  		w model canDiscardEdits ifFalse: [menu lastItem color: Color red]].
  	nakedMorphs isEmpty ifFalse: [menu addLine].
  	(nakedMorphs asSortedCollection: [:w1 :w2 | w1 nameForFindWindowFeature caseInsensitiveLessOrEqual: w2 nameForFindWindowFeature]) do:
  		[:w | menu add: w nameForFindWindowFeature target: w action: #comeToFrontAndAddHalo].
  	menu addTitle: 'find window' translated.
  	
  	menu popUpEvent: evt in: self.!

Item was changed:
  ----- Method: PluggableListMorph>>mouseEnter: (in category 'events') -----
+ mouseEnter: event
+ 
- mouseEnter: event 
  	super mouseEnter: event.
+ 	Preferences mouseOverForKeyboardFocus
+ 		ifTrue: [event hand newKeyboardFocus: self].!
- 	(SystemWindow allWindowsAcceptInput or: [ Preferences mouseOverForKeyboardFocus ]) ifTrue: [ event hand newKeyboardFocus: self ]!

Item was changed:
  ----- Method: PluggableListMorph>>mouseLeave: (in category 'events') -----
  mouseLeave: event 
+ 
- 	"The mouse has left the bounds of the receiver"
  	super mouseLeave: event.
  	self hoverRow: nil.
+ 
+ 	Preferences mouseOverForKeyboardFocus
+ 		ifTrue: [event hand releaseKeyboardFocus: self].!
- 	(SystemWindow allWindowsAcceptInput or: [ Preferences mouseOverForKeyboardFocus ]) ifTrue: [ event hand releaseKeyboardFocus: self ]!

Item was changed:
  ----- Method: PluggableTextMorph>>mouseEnter: (in category 'event handling') -----
  mouseEnter: event
+ 	"Restore the selection in the text morph if there was a selection."
+ 
  	super mouseEnter: event.
+ 	
+ 	selectionInterval ifNotNil: [:interval |
+ 		textMorph editor
+ 			selectInterval: selectionInterval;
+ 			setEmphasisHere].
+ 		
+ 	Preferences mouseOverForKeyboardFocus
+ 		ifTrue:[event hand newKeyboardFocus: self]!
- 	selectionInterval ifNotNil:
- 		[textMorph editor selectInterval: selectionInterval; setEmphasisHere].
- 	textMorph selectionChanged.
- 	(SystemWindow allWindowsAcceptInput or: [ Preferences mouseOverForKeyboardFocus ]) ifTrue:[
- 		event hand newKeyboardFocus: self]!

Item was changed:
  ----- Method: PluggableTextMorph>>mouseLeave: (in category 'event handling') -----
  mouseLeave: event
+ 	"Save the selection interval for later."
+ 
+ 	selectionInterval := textMorph editor selectionInterval.
+ 
- 	"The mouse has left the bounds of the receiver"
- 	textMorph ifNotNil: [selectionInterval := textMorph editor selectionInterval].
  	super mouseLeave: event.
+ 
+ 	Preferences mouseOverForKeyboardFocus
+ 		ifTrue: [event hand releaseKeyboardFocus: self]!
- 	(SystemWindow allWindowsAcceptInput or: [ Preferences mouseOverForKeyboardFocus ]) ifTrue:
- 		[event hand releaseKeyboardFocus: self]!

Item was changed:
  ----- Method: ProportionalSplitterMorph>>mouseDown: (in category 'events') -----
  mouseDown: anEvent 
  	"If the user manually drags me, don't override him with auto positioning."
+ 
- 	self owningWindow ifNotNil: [ : systemWindow | systemWindow == SystemWindow topWindow ifFalse: [ systemWindow activate ]].
  	anEvent redButtonChanged
  		ifTrue: [ self withSiblingSplittersDo: [ : each | each stopStepping ] ]
  		ifFalse:
  			[ anEvent shiftPressed
  				ifTrue: [ self startStepping ]
  				ifFalse:
  					[ self startStepping.
  					self withSiblingSplittersDo: [ : each | each startStepping ] ] ].
  	(self class showSplitterHandles not and: [ self bounds containsPoint: anEvent cursorPoint ]) ifTrue:
  		[ oldColor := self color.
  		self color: Color black ].
  	^ super mouseDown: anEvent!

Item was changed:
  ----- Method: ProportionalSplitterMorph>>proposedCorrectionWouldCauseFocusChange: (in category 'layout') -----
  proposedCorrectionWouldCauseFocusChange: correction 
+ 	^ Preferences mouseOverForKeyboardFocus and:
- 	^ (SystemWindow allWindowsAcceptInput or: [ Preferences mouseOverForKeyboardFocus ]) and:
  		[ | edge | splitsTopAndBottom
  			ifTrue:
  				[ edge := correction positive
  					ifTrue: [ self bottom + 3 ]
  					ifFalse: [ self top - 3 ].
+ 				self activeHand position y
- 				ActiveHand position y
  					inRangeOf: edge
  					and: edge + correction ]
  			ifFalse:
  				[ edge := correction positive
  					ifTrue: [ self right ]
  					ifFalse: [ self left ].
+ 				self activeHand position x
- 				ActiveHand position x
  					inRangeOf: edge
  					and: edge + correction ] ]!

Item was changed:
  ----- Method: ScrollPane>>mouseEnter: (in category 'event handling') -----
  mouseEnter: event
+ 	Preferences mouseOverForKeyboardFocus ifTrue: [hasFocus := true].
+ 	owner isSystemWindow ifTrue: [owner paneTransition: event].
+ 	retractableScrollBar ifTrue: [self hideOrShowScrollBars].!
- 	(SystemWindow allWindowsAcceptInput or: [ Preferences mouseOverForKeyboardFocus ]) ifTrue:[hasFocus := true].
- 	(owner isSystemWindow) ifTrue: [owner paneTransition: event].
- 	retractableScrollBar ifTrue:[ self hideOrShowScrollBars ].
- !

Item was changed:
  ----- Method: ScrollPane>>mouseLeave: (in category 'event handling') -----
  mouseLeave: event
+ 	Preferences mouseOverForKeyboardFocus ifTrue: [hasFocus := false].
- 	(SystemWindow allWindowsAcceptInput or: [ Preferences mouseOverForKeyboardFocus ]) ifTrue:[hasFocus := false].
  	retractableScrollBar ifTrue: [self hideScrollBars].
+ 	owner isSystemWindow ifTrue: [owner paneTransition: event].!
- 	(owner isSystemWindow) ifTrue: [owner paneTransition: event]
- !

Item was changed:
  ----- Method: SelectionMorph>>undoMove:redo:owner:bounds:predecessor: (in category 'undo') -----
  undoMove: cmd redo: redo owner: oldOwners bounds: oldBoundses predecessor: oldPredecessors 
  	"Handle undo and redo of move commands in morphic"
  
  	| item |
  	redo 
  		ifFalse: 
  			["undo sets up the redo state first"
  
  			cmd 
  				redoTarget: self
  				selector: #undoMove:redo:owner:bounds:predecessor:
  				arguments: { 
  						cmd.
  						true.
  						selectedItems collect: [:m | m owner].
  						selectedItems collect: [:m | m bounds].
  						selectedItems collect: [:m | m owner morphPreceding: m]}].
  	1 to: selectedItems size do: 
  				[:i | 
  				item := selectedItems at: i.
  				(oldOwners at: i) ifNotNil: 
  						[(oldPredecessors at: i) ifNil: [(oldOwners at: i) addMorphFront: item]
  							ifNotNil: [(oldOwners at: i) addMorph: item after: (oldPredecessors at: i)]].
  				item bounds: (oldBoundses at: i).
+ 				item isSystemWindow ifTrue: [item beKeyWindow]]!
- 				item isSystemWindow ifTrue: [item activate]]!

Item was changed:
  ----- Method: SimpleHierarchicalListMorph>>mouseEnter: (in category 'event handling') -----
  mouseEnter: event
  
  	super mouseEnter: event.
  	
+ 	Preferences mouseOverForKeyboardFocus
- 	(SystemWindow allWindowsAcceptInput or: [Preferences mouseOverForKeyboardFocus])
  		ifTrue: [event hand newKeyboardFocus: self].!

Item was changed:
  ----- Method: SimpleHierarchicalListMorph>>mouseLeave: (in category 'event handling') -----
  mouseLeave: aMouseEvent 
+ 
  	super mouseLeave: aMouseEvent.
  	self hoveredMorph: nil.
+ 	
+ 	Preferences mouseOverForKeyboardFocus
+ 		ifTrue: [aMouseEvent hand releaseKeyboardFocus: self].!
- 	(SystemWindow allWindowsAcceptInput or: [ Preferences mouseOverForKeyboardFocus ]) ifTrue: [ aMouseEvent hand releaseKeyboardFocus: self ]!

Item was changed:
  MorphicModel subclass: #SystemWindow
+ 	instanceVariableNames: 'labelString stripes label closeBox collapseBox paneMorphs paneRects collapsedFrame fullFrame isCollapsed isActive menuBox mustNotClose labelWidgetAllowance updatablePanes allowReframeHandles labelArea expandBox'
+ 	classVariableNames: 'ClickOnLabelToEdit CloseBoxFrame CloseBoxImageFlat CloseBoxImageGradient CollapseBoxImageFlat CollapseBoxImageGradient DoubleClickOnLabelToExpand ExpandBoxFrame ExpandBoxImageFlat ExpandBoxImageGradient FocusFollowsMouse GradientWindow HideExpandButton MenuBoxFrame MenuBoxImageFlat MenuBoxImageGradient ResizeAlongEdges ReuseWindows TopWindow WindowsActiveOnlyOnTop'
- 	instanceVariableNames: 'labelString stripes label closeBox collapseBox activeOnlyOnTop paneMorphs paneRects collapsedFrame fullFrame isCollapsed menuBox mustNotClose labelWidgetAllowance updatablePanes allowReframeHandles labelArea expandBox'
- 	classVariableNames: 'ClickOnLabelToEdit CloseBoxFrame CloseBoxImageFlat CloseBoxImageGradient CollapseBoxImageFlat CollapseBoxImageGradient DoubleClickOnLabelToExpand ExpandBoxFrame ExpandBoxImageFlat ExpandBoxImageGradient FocusFollowsMouse GradientWindow HideExpandButton MenuBoxFrame MenuBoxImageFlat MenuBoxImageGradient ResizeAlongEdges ReuseWindows TopWindow WindowsRaiseOnClick'
  	poolDictionaries: ''
  	category: 'Morphic-Windows'!
  
  !SystemWindow commentStamp: '<historical>' prior: 0!
  SystemWindow is the Morphic equivalent of StandardSystemView -- a labelled container for rectangular views, with iconic facilities for close, collapse/expand, and resizing.
  
  The attribute onlyActiveOnTop, if set to true (and any call to activate will set this), determines that only the top member of a collection of such windows on the screen shall be active.  To be not active means that a mouse click in any region will only result in bringing the window to the top and then making it active.!

Item was removed:
- ----- Method: SystemWindow class>>allWindowsAcceptInput (in category 'private') -----
- allWindowsAcceptInput
- 	"With either of these two preferences settings, inactive windows will not have their widgets locked.  All windows accept input as if they were active."
- 	^ self focusFollowsMouse or: [ self windowsRaiseOnClick not ]!

Item was removed:
- ----- Method: SystemWindow class>>focusFollowsMouse (in category 'preferences') -----
- focusFollowsMouse
- 	<preference: 'Focus Follows Mouse'
- 		category: 'windows'
- 		description: 'When true, the widget under the hand has keyboard focus.'
- 		type: #Boolean>
- 	^ FocusFollowsMouse ifNil: [ false ]!

Item was removed:
- ----- Method: SystemWindow class>>focusFollowsMouse: (in category 'preferences') -----
- focusFollowsMouse: aBoolean 
- 	(FocusFollowsMouse := aBoolean) == true.
- 	self reconfigureWindowsForFocus!

Item was added:
+ ----- Method: SystemWindow class>>keyWindow (in category 'top window') -----
+ keyWindow
+ 	"Multiple windows may appear to be on top, especially on large screens. Only one window, however, can be the key window, which gets the programmers primary attention."
+ 	
+ 	^ TopWindow!

Item was changed:
  ----- Method: SystemWindow class>>noteTopWindowIn: (in category 'top window') -----
  noteTopWindowIn: aWorld
+ 	"Look for a new top window in the given world. We have to reset the former top window because this is global state shared between all worlds."
+ 
+ 	| newTopWindow |
- 	| newTop |
- 	"TopWindow must be nil or point to the top window in this project."
  	TopWindow := nil.
+ 	newTopWindow := nil.
+ 
  	aWorld ifNil: [^ self].
+ 
+ 	aWorld submorphsDo: [:m |
+ 		(m isSystemWindow and: [newTopWindow isNil])
+ 			ifTrue: [newTopWindow := m].
+ 		
+ 		self flag: #refactor. "This really belongs in a special ProjWindow class"
+ 		(m model isKindOf: Project)
+ 			ifTrue: [m label ~= m model name ifTrue: [m setLabel: m model name]]].
+ 
+ 	newTopWindow ifNotNil: [newTopWindow beKeyWindow].!
- 	newTop := nil.
- 	aWorld submorphsDo:
- 		[:m | (m isSystemWindow) ifTrue:
- 			[(newTop == nil and: [m activeOnlyOnTop])
- 				ifTrue: [newTop := m].
- 			(m model isKindOf: Project)
- 				ifTrue: ["This really belongs in a special ProjWindow class"
- 						m label ~= m model name ifTrue: [m setLabel: m model name]]]].
- 	newTop == nil ifFalse: [newTop activate]!

Item was changed:
+ ----- Method: SystemWindow class>>rebuildAllWindowLabels (in category 'private') -----
- ----- Method: SystemWindow class>>rebuildAllWindowLabels (in category 'preferences') -----
  rebuildAllWindowLabels
  
  	self withAllSubclasses do: [:c | c allInstances do: [:w | w replaceBoxes]].!

Item was changed:
  ----- Method: SystemWindow class>>reconfigureWindowsForFocus (in category 'private') -----
  reconfigureWindowsForFocus
+ 
+ 	self allSubInstancesDo: [:window |
+ 		window
+ 			passivate;
+ 			activate;
+ 			unlockWindowDecorations;
+ 			passivateIfNeeded].
+ 	self topWindow activate.!
- 	self withAllSubclasses do:
- 		[ : eachSubclass | eachSubclass allInstances do:
- 			[ : eachInstance | eachInstance configureFocus ] ]!

Item was added:
+ ----- Method: SystemWindow class>>topWindow (in category 'top window') -----
+ topWindow
+ 	^ TopWindow!

Item was added:
+ ----- Method: SystemWindow class>>windowsActiveOnlyOnTop (in category 'preferences') -----
+ windowsActiveOnlyOnTop
+ 	<preference: 'Windows Active Only On Top'
+ 		category: 'windows'
+ 		description: 'If true, a click anywhere within a background window will raise it above all other windows to become the active window. If false, all windows remain active and occluded windows will only raise when clicking in the title bar, splitters, or grips.'
+ 		type: #Boolean>
+ 	^ WindowsActiveOnlyOnTop ifNil: [ true ]!

Item was added:
+ ----- Method: SystemWindow class>>windowsActiveOnlyOnTop: (in category 'preferences') -----
+ windowsActiveOnlyOnTop: aBoolean 
+ 	
+ 	aBoolean = WindowsActiveOnlyOnTop ifTrue: [^ self].
+ 	WindowsActiveOnlyOnTop := aBoolean.		
+ 	self reconfigureWindowsForFocus.!

Item was added:
+ ----- Method: SystemWindow class>>windowsIn: (in category 'top window') -----
+ windowsIn: aWorld
+ 
+ 	^ self windowsIn: aWorld satisfying: [:window | true].!

Item was removed:
- ----- Method: SystemWindow class>>windowsRaiseOnClick (in category 'preferences') -----
- windowsRaiseOnClick
- 	<preference: 'Windows Raise On Click'
- 		category: 'windows'
- 		description: 'If true, a click anywhere within a window will raise it above all other windows to become the active window.  If false, it won''t.'
- 		type: #Boolean>
- 	^ WindowsRaiseOnClick ifNil: [ true ]!

Item was removed:
- ----- Method: SystemWindow class>>windowsRaiseOnClick: (in category 'preferences') -----
- windowsRaiseOnClick: aBoolean 
- 	(WindowsRaiseOnClick := aBoolean == true).
- 	self reconfigureWindowsForFocus!

Item was changed:
+ ----- Method: SystemWindow>>activate (in category 'focus') -----
- ----- Method: SystemWindow>>activate (in category 'top window') -----
  activate
+ 	"Bring the receiver to the top.  If I am modal, bring along my modal owning window and my model child as well."
+ 
+ 	self isActive ifTrue: [self lookFocused. ^ self].
+ 	self topRendererOrSelf owner ifNil: [^ self "avoid spurious activate when drop in trash"].
+ 	
+ 	self isActive: true.
+ 			
+ 	"Special handling for expanded windows."
+ 	self isCollapsed ifFalse: [
+ 		model modelWakeUpIn: self.
+ 		self positionSubmorphs].
+ 
+ 	self submorphsDo: [:each | each unlock].
+ 
+ 	self
+ 		lookFocused;
+ 		updateFocusLookAtHand.!
- 	"Bring the receiver to the top.  If I am modal, bring along my owning window as well."
- 	| modalOwner |
- 	self modalChild ifNotNil:
- 		[ : modalChild | modalChild owner ifNotNil:
- 			[ modalChild activate.
- 			^ modalChild modalChild ifNil: [ modalChild flash ] ] ].
- 	(isCollapsed not and:
- 		[ self paneMorphs size > 1 and: [ self splitters isEmpty ] ]) ifTrue: [ self addPaneSplitters ].
- 	self activateWindow.
- 	PasteUpMorph globalCommandKeysEnabled ifTrue: [self activeHand addKeyboardListener: self].
- 	modalOwner := self modalOwner.
- 	(modalOwner notNil and: [ modalOwner isSystemWindow ]) ifTrue: [ modalOwner bringBehind: self ]!

Item was removed:
- ----- Method: SystemWindow>>activateAndForceLabelToShow (in category 'top window') -----
- activateAndForceLabelToShow
- 	self activate.
- 	bounds top < 0 ifTrue:
- 		[self position: (self position x @ 0)]!

Item was removed:
- ----- Method: SystemWindow>>activateWindow (in category 'top window') -----
- activateWindow
- 	"Bring me to the front and make me able to respond to mouse and keyboard.
- 	Was #activate (sw 5/18/2001 23:20)"
- 	| oldTop outerMorph sketchEditor pal windowUnderneath |	
- 	outerMorph := self topRendererOrSelf.
- 	outerMorph owner ifNil: [^ self "avoid spurious activate when drop in trash"].
- 	self hasDropShadow: Preferences menuAppearance3d.
- 	oldTop := TopWindow.
- 	oldTop = self ifTrue: [^self].
- 	TopWindow := self.
- 	oldTop ifNotNil: [oldTop passivate].
- 	outerMorph owner firstSubmorph == outerMorph
- 		ifFalse: ["Bring me (with any flex) to the top if not already"
- 				outerMorph owner addMorphFront: outerMorph].
- 	self configureFocus.
- 	self isCollapsed ifFalse:
- 		[model modelWakeUpIn: self.
- 		self positionSubmorphs.
- 		labelArea ifNil: [self adjustBorderUponActivationWhenLabeless]].
- 	(sketchEditor := self extantSketchEditor) ifNotNil:
- 		[sketchEditor comeToFront.
- 		(pal := self world findA: PaintBoxMorph) ifNotNil:
- 			[pal comeToFront]].
- 	self updatePaneColors.
- 	"Newly spawned windows are normally active, but if focusFollowsMouse is set, then the focused window can only be the one under the hand."
- 	(self class allWindowsAcceptInput not or: [ (windowUnderneath := ActiveHand windowUnderneath) isNil or: [ windowUnderneath == self ] ])
- 		ifTrue: [ self lookFocused ]
- 		ifFalse: [ self lookUnfocused ]!

Item was removed:
- ----- Method: SystemWindow>>activeOnlyOnTop (in category 'top window') -----
- activeOnlyOnTop
- 	^ activeOnlyOnTop ifNil: [false]!

Item was removed:
- ----- Method: SystemWindow>>activeOnlyOnTop: (in category 'top window') -----
- activeOnlyOnTop: trueOrFalse
- 	activeOnlyOnTop := trueOrFalse!

Item was removed:
- ----- Method: SystemWindow>>adjustBorderUponActivationWhenLabeless (in category 'top window') -----
- adjustBorderUponActivationWhenLabeless
- 	"Adjust the border upon, um, activation when, um, labelless"
- 
- 	| aWidth |
- 	(aWidth := self valueOfProperty: #borderWidthWhenActive) ifNotNil:
- 		[self acquireBorderWidth: aWidth]!

Item was removed:
- ----- Method: SystemWindow>>adjustBorderUponDeactivationWhenLabeless (in category 'top window') -----
- adjustBorderUponDeactivationWhenLabeless
- 	"Adjust the border upon deactivation when, labelless"
- 
- 	| aWidth |
- 	(aWidth := self valueOfProperty: #borderWidthWhenInactive) ifNotNil:
- 		[self acquireBorderWidth: aWidth]!

Item was changed:
+ ----- Method: SystemWindow>>adoptPaneColor: (in category 'colors') -----
- ----- Method: SystemWindow>>adoptPaneColor: (in category 'colors handling') -----
  adoptPaneColor: aPaneColor
  
  	super adoptPaneColor: (self class gradientWindow
  		ifTrue: [aPaneColor ifNotNil: [:c | c duller]]
  		ifFalse: [aPaneColor]).!

Item was added:
+ ----- Method: SystemWindow>>assureLabelAreaVisible (in category 'layout') -----
+ assureLabelAreaVisible
+ 	"Label should be visible to interact with."
+ 
+ 	(RealEstateAgent maximumUsableAreaInWorld: self world) in: [:rect |
+ 		 self innerBounds top < rect top ifTrue: [self top: rect top]].!

Item was added:
+ ----- Method: SystemWindow>>beKeyWindow (in category 'top window') -----
+ beKeyWindow
+ 	"Let me be the most important window on the screen. I am at the top and I can have a shadow to get more attention by the user. I am the window that is responsible for window keyboard shortcuts."
+ 
+ 	| oldKeyWindow |
+ 	self isKeyWindow ifTrue: [^ self].
+ 
+ 	oldKeyWindow := TopWindow.
+ 	TopWindow := self.
+ 
+ 	PasteUpMorph globalCommandKeysEnabled ifTrue:
+ 		[ self activeHand addKeyboardListener: self ].
+ 	
+ 	self
+ 		unlockWindowDecorations; "here, because all windows might be active anyway"
+ 		activate; "if not already active, activate now"
+ 		comeToFront. "key windows are on top"
+ 
+ 	"Change appearance to get noticed."
+ 	self hasDropShadow: Preferences menuAppearance3d.
+ 	(self valueOfProperty: #borderWidthWhenActive)
+ 		ifNotNil: [:bw | self acquireBorderWidth: bw].
+ 
+ 	oldKeyWindow ifNotNil: [:wnd |
+ 		wnd passivateIfNeeded.
+ 		
+ 		self activeHand removeKeyboardListener: oldKeyWindow.	
+ 		
+ 		"Change appearance to not look prettier than the new key window."
+ 		wnd hasDropShadow: false.
+ 		(wnd valueOfProperty: #borderWidthWhenInactive)
+ 			ifNotNil: [:bw | wnd acquireBorderWidth: bw]].!

Item was removed:
- ----- Method: SystemWindow>>bringBehind: (in category 'polymorph') -----
- bringBehind: aMorph
- 	"Make the receiver be directly behind the given morph.
- 	Take into account any modal owner and propagate."
- 
- 	|outerMorph|
- 	outerMorph := self topRendererOrSelf.
- 	outerMorph owner ifNil: [^ self "avoid spurious activate when drop in trash"].
- 	outerMorph owner addMorph: outerMorph after: aMorph topRendererOrSelf.
- 	self modalOwner ifNotNil: [:mo | mo bringBehind: self]!

Item was removed:
- ----- Method: SystemWindow>>canProcessMouseDown: (in category 'top window') -----
- canProcessMouseDown: anEvent
- 	"In case 'Focus Follows Mouse' is set, then there are two possibilities for mouse input on a background window:  if 'Window Active On First Click' is set, it must be honored and the window must be activated.  If it is not set, then the behavior depends on 'Windows Raise On Click' setting.  If its true, then just activate the window and DON'T process aMouseEvent.  If false, then process the event in any case."
- 	^ self isActive or: [ Model windowActiveOnFirstClick or: [ SystemWindow windowsRaiseOnClick not ] ]!

Item was changed:
  ----- Method: SystemWindow>>collapseOrExpand (in category 'resize/collapse') -----
  collapseOrExpand
  	"Collapse or expand the window, depending on existing state"
  	| cf |
  	isCollapsed
  		ifTrue: 
  			["Expand -- restore panes to morphics structure"
  			isCollapsed := false.
+ 			self beKeyWindow.  "Bring to frint first"
- 			self activate.  "Bring to frint first"
  			Preferences collapseWindowsInPlace
  				ifTrue: 
  					[fullFrame := fullFrame align: fullFrame topLeft with: self getBoundsWithFlex topLeft]
  				ifFalse:
  					[collapsedFrame := self getBoundsWithFlex].
  			collapseBox ifNotNil: [collapseBox setBalloonText: 'collapse this window' translated].
  			self setBoundsWithFlex: fullFrame.
  			paneMorphs reverseDo: 
  					[:m |  self addMorph: m unlock.
  					self world startSteppingSubmorphsOf: m].
  			self addPaneSplitters]
  		ifFalse: 
  			["Collapse -- remove panes from morphics structure"
  			isCollapsed := true.
  			fullFrame := self getBoundsWithFlex.
  			"First save latest fullFrame"
  			paneMorphs do: [:m | m delete; releaseCachedState].
  			self removePaneSplitters.
  			self removeCornerGrips.
  			model modelSleep.
  			cf := self getCollapsedFrame.
  			(collapsedFrame isNil and: [Preferences collapseWindowsInPlace not]) ifTrue:
  				[collapsedFrame := cf].
  			self setBoundsWithFlex: cf.
  			collapseBox ifNotNil: [collapseBox setBalloonText: 'expand this window' translated ].
  			expandBox ifNotNil: [expandBox setBalloonText: 'expand this window' translated ].
  			self sendToBack].
  	self layoutChanged!

Item was added:
+ ----- Method: SystemWindow>>comeToFront (in category 'top window') -----
+ comeToFront
+ 	"If I am modal, bring along my modal owning window and my model child as well. Ensure that my label is visible."
+ 
+ 	"Model window: Bring up my modal owner behind me."
+ 	self modalOwner ifNotNil:
+ 		[ : mo | mo isSystemWindow ifTrue:
+ 			[ mo comeToFront ] ].
+ 
+ 	"Now show me."
+ 	super comeToFront.
+ 	
+ 	"Modal window: Bring up my modal children in front of me."
+ 	self modalChild ifNotNil:
+ 		[ : modalChild | modalChild owner ifNotNil:
+ 			[ modalChild comeToFront.
+ 			^ modalChild modalChild ifNil: [ modalChild flash ] ] ].
+ 	
+ 	"Label should be visible to interact with."
+ 	self assureLabelAreaVisible.
+ 	
+ 	"Handle historic companions. May be removed in the future."
+ 	self extantSketchEditor ifNotNil: [:sketchEditor | 
+ 		sketchEditor comeToFront.
+ 		(self world findA: PaintBoxMorph) ifNotNil: [:pal | pal comeToFront]].!

Item was removed:
- ----- Method: SystemWindow>>configureFocus (in category 'top window') -----
- configureFocus
- 	"Make me unable to respond to mouse and keyboard unless allWindowsAcceptInput is set or 'Window Active On First Click' is unset. Otherwise, the classic Squeak behavior of Control boxes remaining active, except in novice mode."
- 	self submorphsDo:
- 		[ : each | each lock:
- 			(self isActive not and:
- 				[ each == labelArea
- 					ifTrue: [ self class windowsRaiseOnClick not ]
- 					ifFalse: [ self class allWindowsAcceptInput not ] ]) ].
- 	labelArea
- 		ifNil: [ "i.e. label area is nil, so we're titleless"
- 			self adjustBorderUponDeactivationWhenLabeless ]
- 		ifNotNil:
- 			[ labelArea submorphsDo:
- 				[ : each | | classicSqueakBehavior |
- 				classicSqueakBehavior := self class allWindowsAcceptInput not.
- 				each lock:
- 					(classicSqueakBehavior
- 						ifTrue:
- 							[ self isActive not and:
- 								[ Preferences noviceMode or:
- 									[ each ~~ closeBox and: [ each ~~ collapseBox ] ] ] ]
- 						ifFalse:
- 							[ self isActive not and: [ Model windowActiveOnFirstClick not ] ]) ] ]!

Item was changed:
  ----- Method: SystemWindow>>delete (in category 'open/close') -----
  delete
  	| thisWorld sketchEditor aPaintBox |
  	self mustNotClose ifTrue: [^self].
  	model okToClose ifFalse: [^self].
  	thisWorld := self world.
  	sketchEditor := self extantSketchEditor.
+ 	
+ 	self activeHand removeKeyboardListener: self.
+ 	
  	self isFlexed
  		ifTrue: [owner delete]
  		ifFalse: [super delete].
  	model windowIsClosing; release.
  	model := nil.
  	sketchEditor ifNotNil:
  		[sketchEditor deleteSelfAndSubordinates.
  		 (thisWorld notNil 
  		  and: [(aPaintBox := thisWorld paintBoxOrNil) notNil]) ifTrue:
  			[aPaintBox delete]].
  		
  	SystemWindow noteTopWindowIn: thisWorld!

Item was changed:
  ----- Method: SystemWindow>>dimWindowButtons (in category 'top window') -----
  dimWindowButtons
+ 	{closeBox. collapseBox. menuBox. expandBox}
+ 		do: [:b | b ifNotNil: [b dim]]!
- 	self == TopWindow ifFalse: [
- 		{closeBox. collapseBox. menuBox. expandBox}
- 			do: [:b | b ifNotNil: [b dim]]]!

Item was changed:
+ ----- Method: SystemWindow>>existingPaneColor (in category 'colors') -----
- ----- Method: SystemWindow>>existingPaneColor (in category 'colors handling') -----
  existingPaneColor
  	"Answer the existing pane color for the window, obtaining it from the first paneMorph if any, and fall back on using the second stripe color if necessary."
  
  	| aColor |
  	aColor := self valueOfProperty: #paneColor.
  	aColor ifNil: [self setProperty: #paneColor toValue: (aColor := self paneColor)].
  	^aColor.!

Item was changed:
+ ----- Method: SystemWindow>>gradientWithColor: (in category 'colors') -----
- ----- Method: SystemWindow>>gradientWithColor: (in category 'colors handling') -----
  gradientWithColor: aColor
  
  	| gradient |
  	gradient := GradientFillStyle ramp: {
  		0.0 -> Color white. 
  		0.2 -> (aColor duller mixed: 0.5 with: (Color gray: 0.9)) lighter. 
  		1.0 -> aColor duller.
  	}.
  	gradient origin: self topLeft.
  	gradient direction: 0 @ self labelHeight.
  	^gradient!

Item was changed:
  ----- Method: SystemWindow>>handleListenEvent: (in category 'events') -----
  handleListenEvent: aUserInputEvent 
+ 
+ 	"1) Handle keyboard shortcuts"
  	aUserInputEvent type = #keystroke ifTrue:
  		[ aUserInputEvent commandKeyPressed ifTrue:
  			[ aUserInputEvent keyValue = $\ asciiValue ifTrue: [ self class sendTopWindowToBack ].
  			"Command+Escape"
  			aUserInputEvent keyValue = 27 ifTrue:
  				[ aUserInputEvent wasHandled: true.
- 				ActiveHand removeKeyboardListener: self.
  				self delete ] ].
  		aUserInputEvent controlKeyPressed ifTrue:
+ 			[ aUserInputEvent keyValue = 27 ifTrue: [ self world findWindow: aUserInputEvent ] ] ].
+ 
+ 	"2) See #mouseEnterDragging:. Watch for finished drag-and-drop action and lock contents accordingly."
+ 	(aUserInputEvent isMouse and: [ aUserInputEvent hand hasSubmorphs not ]) ifTrue: 
+ 		[ self isKeyWindow ifFalse: [ self passivateIfNeeded ].
+ 		aUserInputEvent hand removeMouseListener: self ].!
- 			[ aUserInputEvent keyValue = 27 ifTrue: [ World findWindow: aUserInputEvent ] ] ].
- 	aUserInputEvent isMouse ifFalse: [ ^ self ].
- 	"Still dragging?"
- 	aUserInputEvent hand hasSubmorphs ifTrue: [ ^ self ].
- 	"Make sure we lock our contents after drag-and-drop has finished."
- 	(self isActive and: [ self class allWindowsAcceptInput not ]) ifFalse: [ self configureFocus ].
- 	aUserInputEvent hand removeMouseListener: self!

Item was changed:
  ----- Method: SystemWindow>>initialize (in category 'initialization') -----
  initialize
  	"Initialize a system window. Add label, stripes, etc., if desired"
  
  	super initialize.
  
  	self layoutPolicy: ProportionalLayout new.
  
  	self wantsPaneSplitters: true.
  	self layoutInset: ProportionalSplitterMorph gripThickness.
  	self cellInset: ProportionalSplitterMorph gripThickness.
  
  	self initializeLabelArea.				
  	self addCornerGrips.
  	self setDefaultParameters.
  
  	allowReframeHandles := true.
  	isCollapsed := false.
- 	activeOnlyOnTop := true.
  	paneMorphs := Array new.
  	mustNotClose := false.
  	updatablePanes := Array new.!

Item was changed:
+ ----- Method: SystemWindow>>isActive (in category 'focus') -----
- ----- Method: SystemWindow>>isActive (in category 'top window') -----
  isActive
+ 	
+ 	^ isActive ifNil: [false]!
- 	self activeOnlyOnTop ifTrue: [^ self == TopWindow].
- 	^ true!

Item was added:
+ ----- Method: SystemWindow>>isActive: (in category 'focus') -----
+ isActive: aBoolean
+ 	
+ 	isActive := aBoolean.!

Item was added:
+ ----- Method: SystemWindow>>isKeyWindow (in category 'top window') -----
+ isKeyWindow
+ 	"The key window is the window with the user's main attention. It usually has a shadow or other visual hints to separate it from other windows. Usually, the key window is at the top of the screen. On large screens, however, many windows may appear at the top."
+ 
+ 	^ self == self class keyWindow!

Item was changed:
  ----- Method: SystemWindow>>justDroppedInto:event: (in category 'geometry') -----
  justDroppedInto: aMorph event: anEvent
  
  	(ToolBuilder openToolsAttachedToMouseCursor and: (self hasProperty: #initialDrop))
  		ifTrue: [
  			self removeProperty: #initialDrop.
  			(self submorphs detect: [:m | m isKindOf: BottomRightGripMorph] ifNone: [])
  				ifNotNil: [:grip | 
  					grip referencePoint: anEvent position.
  					anEvent hand newMouseFocus: grip]].
  
+ 	self hasDropShadow: (self isKeyWindow and: [Preferences menuAppearance3d]).
- 	self hasDropShadow: (self isActive and: [Preferences menuAppearance3d]).
  
  	isCollapsed
  		ifTrue: [self position: ((self position max: 0 at 0) grid: 8 at 8).
  				collapsedFrame := self bounds]
  		ifFalse: [fullFrame := self bounds.
+ 				self beKeyWindow].
+ 			
+ 	aMorph == self world ifTrue: [self assureLabelAreaVisible].
+ 			
- 				TopWindow ~~ self ifTrue: [self activate]].
  	^super justDroppedInto: aMorph event: anEvent!

Item was added:
+ ----- Method: SystemWindow>>lockWindowDecorations (in category 'focus') -----
+ lockWindowDecorations
+ 	"Lock all window decrations, that is grips, splitters, and title bar."
+ 	
+ 	self submorphsDo: [:m |
+ 		(self paneMorphs includes: m)
+ 			ifFalse: [m lock]].!

Item was changed:
+ ----- Method: SystemWindow>>lookFocused (in category 'focus') -----
- ----- Method: SystemWindow>>lookFocused (in category 'top window') -----
  lookFocused
  	label ifNotNil: [ label color: Color black ].
+ 
+ 	(self isKeyWindow or: [model windowActiveOnFirstClick])
+ 		ifTrue: [self undimWindowButtons].
+ 
+ 	self paneColorToUse in: [ : col |
+ 		self
+ 			 setStripeColorsFrom: col ;
+ 			 adoptPaneColor: col].!
- 	(self isActive or: [Model windowActiveOnFirstClick]) ifTrue: [ self undimWindowButtons ].
- 	self
- 		 updatePaneColors ;
- 		 adoptPaneColor: self paneColorToUse!

Item was removed:
- ----- Method: SystemWindow>>lookFocused: (in category 'top window') -----
- lookFocused: aBoolean 
- 	aBoolean
- 		ifTrue: [ self lookFocused ]
- 		ifFalse: [ self lookUnfocused ]!

Item was changed:
+ ----- Method: SystemWindow>>lookUnfocused (in category 'focus') -----
- ----- Method: SystemWindow>>lookUnfocused (in category 'top window') -----
  lookUnfocused
  	label ifNotNil: [ label color: Color darkGray ].
  	self dimWindowButtons.
+ 	self paneColorToUseWhenNotActive in: [ : col |
+ 		self
- 	self paneColorToUseWhenNotActive in:
- 		[ : col | self
  			 setStripeColorsFrom: col ;
  			 adoptPaneColor: col ]!

Item was changed:
  ----- Method: SystemWindow>>makeSecondTopmost (in category 'menu') -----
  makeSecondTopmost
+ 
  	| aWorld nextWindow |
  	aWorld := self world.
  	nextWindow := aWorld submorphs 
  				detect: [:m | (m isSystemWindow) and: [m ~~ self]]
  				ifNone: [^self].
+ 
+ 	self comeToFront.
+ 	nextWindow beKeyWindow.!
- 	nextWindow activate.
- 	aWorld addMorph: self behind: nextWindow!

Item was changed:
  ----- Method: SystemWindow>>modalUnlockFrom: (in category 'polymorph') -----
  modalUnlockFrom: aSystemWindow
  	"Unlock the receiver as a modal owner of the given window."
  
  	aSystemWindow removeProperty: #modalOwner.
  	self removeProperty: #modalChild.
+ 	self beKeyWindow.!
- 	self activate!

Item was changed:
  ----- Method: SystemWindow>>mouseDown: (in category 'events') -----
  mouseDown: evt
  
+ 	| wasKeyWindow |
+ 	(wasKeyWindow := self isKeyWindow) ifFalse: [
- 	| wasActive |
- 	(wasActive := self isActive) ifFalse: [
  		evt hand releaseKeyboardFocus.
+ 		self beKeyWindow].
- 		self activate].
  
+ 	"If the window was locked, we did unlock it by now. If the user does not want to invest an additional click to interact with an actual widget, re-process the event."
+ 	(wasKeyWindow not and: [model windowActiveOnFirstClick])
- 	wasActive
- 		ifFalse: [	
- 			"the window was locked, thus we got the event.
- 			re-send it now that the window is unlocked again"
- 			evt wasHandled: false.
- 			model windowActiveOnFirstClick
- 				ifTrue: [self processEvent: evt] "re-dispatch to any submorphs"
- 				ifFalse: [label processEvent: evt]. "dispatch to label so dragging works"
- 			]
  		ifTrue: [
+ 			evt wasHandled: false.
+ 			^ self processEvent: evt]. 
+ 
+ 	evt hand 
+ 		waitForClicksOrDrag: self 
+ 		event: evt 
+ 		selectors: { nil. nil. nil. #startDragFromLabel: }
+ 		threshold: HandMorph dragThreshold.!
- 			evt hand 
- 				waitForClicksOrDrag: self 
- 				event: evt 
- 				selectors: { nil. nil. nil. #startDragFromLabel: }
- 				threshold: HandMorph dragThreshold.
- 			].
- 	evt wasHandled: true.!

Item was changed:
  ----- Method: SystemWindow>>mouseEnter: (in category 'events') -----
  mouseEnter: anEvent 
  	"Handle a mouseEnter event, meaning the mouse just entered my bounds with no button pressed. The default response is to let my eventHandler, if any, handle it."
  	super mouseEnter: anEvent.
+ 
+ 	self isActive
+ 		ifTrue: [self lookFocused]
+ 		ifFalse: [model windowActiveOnFirstClick
+ 			ifTrue: [self undimWindowButtons]].!
- 	self class allWindowsAcceptInput ifTrue: [ self lookFocused ]!

Item was changed:
  ----- Method: SystemWindow>>mouseEnterDragging: (in category 'events') -----
  mouseEnterDragging: evt
  	"unlock children for drop operations"
+ 	
+ 	self flag: #performance. "mt: There may be no need to change appearance if no widget wants the drop."
+ 	self isActive
+ 		ifTrue: [self lookFocused]
+ 		ifFalse: [model windowActiveOnFirstClick
+ 			ifTrue: [self undimWindowButtons]].
+ 		
+ 	(self isActive not and: [evt hand hasSubmorphs]) ifTrue: [
+ 		self activate. "unlock contents for drop"
- 	(self ~~ TopWindow and:[evt hand hasSubmorphs]) ifTrue:[
- 		self submorphsDo:[:m| m unlock].
  		evt hand addMouseListener: self. "for drop completion on submorph"
  	].!

Item was changed:
  ----- Method: SystemWindow>>mouseLeave: (in category 'events') -----
  mouseLeave: anEvent 
  	"Handle a mouseEnter event, meaning the mouse just entered my bounds with no button pressed. The default response is to let my eventHandler, if any, handle it."
  	super mouseLeave: anEvent.
+ 	
+ 	(self isActive and: [self class windowsActiveOnlyOnTop not])
+ 		ifTrue: [self lookUnfocused]
+ 		ifFalse: [self isKeyWindow
+ 			ifFalse: [self dimWindowButtons]].!
- 	self class allWindowsAcceptInput ifTrue: [ self lookUnfocused ]!

Item was changed:
  ----- Method: SystemWindow>>mouseLeaveDragging: (in category 'events') -----
  mouseLeaveDragging: evt
+ 	"Passivate after drop operations if needed."
+ 	
+ 	(self isActive and: [self class windowsActiveOnlyOnTop not])
+ 		ifTrue: [self lookUnfocused]
+ 		ifFalse: [self isKeyWindow
+ 			ifFalse: [self dimWindowButtons]].
+ 		
+ 	(self isKeyWindow not and: [evt hand hasSubmorphs]) ifTrue:[
+ 		self passivateIfNeeded.
+ 		evt hand removeMouseListener: self. "no more drop completion possible on submorph"
- 	"lock children after drop operations"
- 	(self isActive and:[evt hand hasSubmorphs and: [self class allWindowsAcceptInput not]]) ifTrue:[
- 		self configureFocus.
- 		evt hand removeMouseListener: self.
  	].!

Item was removed:
- ----- Method: SystemWindow>>mouseUp: (in category 'events') -----
- mouseUp: evt
- 	| cp |
- 	model windowActiveOnFirstClick ifTrue:
- 		["Normally window takes control on first click.
- 		Need explicit transmission for first-click activity."
- 		cp := evt cursorPoint.
- 		submorphs do: [:m | (m containsPoint: cp) ifTrue: [m mouseUp: evt]]]!

Item was changed:
  ----- Method: SystemWindow>>openAsIsIn: (in category 'open/close') -----
  openAsIsIn: aWorld
  	"This msg and its callees result in the window being activeOnlyOnTop"
  	aWorld addMorph: self.
+ 	self beKeyWindow.
- 	self activate.
  	aWorld startSteppingSubmorphsOf: self.
  	self activeHand
  		releaseKeyboardFocus;
  		releaseMouseFocus.!

Item was changed:
  ----- Method: SystemWindow>>openInWorld: (in category 'open/close') -----
  openInWorld: aWorld
  	"This msg and its callees result in the window being activeOnlyOnTop"
  	[^ self anyOpenWindowLikeMe
  		ifEmpty: 
  			[ self 
  				bounds: (RealEstateAgent initialFrameFor: self world: aWorld) ;
  				openAsIsIn: aWorld ]
  		ifNotEmptyDo:
  			[ : windows | 
  			windows anyOne
  				expand ;
+ 				beKeyWindow ; 
- 				activate ; 
  				postAcceptBrowseFor: self ].
  	] ensure: [ 
  		self activeHand
  			releaseKeyboardFocus;
  			releaseMouseFocus. ]!

Item was changed:
  ----- Method: SystemWindow>>openInWorld:extent: (in category 'open/close') -----
  openInWorld: aWorld extent: extent
  	"This msg and its callees result in the window being activeOnlyOnTop"
  	[^ self anyOpenWindowLikeMe
  		ifEmpty:
  			[ self 
  				position: (RealEstateAgent initialFrameFor: self initialExtent: extent world: aWorld) topLeft ;
  				extent: extent.
  			self openAsIsIn: aWorld ]
  		ifNotEmptyDo:
  			[ : windows | 
  			windows anyOne
  				expand ;
+ 				beKeyWindow ; 
- 				activate ; 
  				postAcceptBrowseFor: self ].
  	] ensure: [ 
  		self activeHand
  			releaseKeyboardFocus;
  			releaseMouseFocus. ]!

Item was changed:
+ ----- Method: SystemWindow>>paneColor (in category 'colors') -----
- ----- Method: SystemWindow>>paneColor (in category 'colors handling') -----
  paneColor
  	| cc |
  	(cc := self valueOfProperty: #paneColor) ifNotNil: [^cc].
  	Display depth > 2 
  		ifTrue: 
  			[model ifNotNil: 
  					[model isInMemory 
  						ifTrue: 
  							[cc := Color colorFrom: model defaultBackgroundColor]].
  	cc ifNil: [cc := paneMorphs isEmptyOrNil ifFalse: [paneMorphs first color]]].
  	cc ifNil: [cc := self defaultBackgroundColor].
  	self paneColor: cc.
  	^cc!

Item was changed:
+ ----- Method: SystemWindow>>paneColor: (in category 'colors') -----
- ----- Method: SystemWindow>>paneColor: (in category 'colors handling') -----
  paneColor: aColor
  	self setProperty: #paneColor toValue: aColor.
  
  	self adoptPaneColor: aColor.!

Item was changed:
+ ----- Method: SystemWindow>>paneColorToUse (in category 'colors') -----
- ----- Method: SystemWindow>>paneColorToUse (in category 'colors handling') -----
  paneColorToUse
  	^ Display depth <= 2
  		ifTrue:
  			[Color white]
  		ifFalse:
  			[self paneColor]!

Item was changed:
+ ----- Method: SystemWindow>>paneColorToUseWhenNotActive (in category 'colors') -----
- ----- Method: SystemWindow>>paneColorToUseWhenNotActive (in category 'colors handling') -----
  paneColorToUseWhenNotActive
  
  	^ self paneColorToUse darker!

Item was changed:
  ----- Method: SystemWindow>>paneMorphs (in category 'geometry') -----
  paneMorphs
  	"Nominally private but a need for obtaining this from the outside arose"
+ 	^ paneMorphs!
- 	^ paneMorphs copy!

Item was changed:
+ ----- Method: SystemWindow>>passivate (in category 'focus') -----
- ----- Method: SystemWindow>>passivate (in category 'top window') -----
  passivate
+ 	"Reconfigure my focus according to preferences."
+ 
+ 	self isActive ifFalse: [^ self].
+ 	self isActive: false.
+ 	
+ 	self isCollapsed ifFalse: [model modelSleep].
+ 
+ 	self submorphsDo: [:each | each lock].
+ 
+ 	self lookUnfocused.!
- 	"Lose my drop shadlow and reconfigure my focus according to preferences."
- 	self
- 		 hasDropShadow: false ;
- 		 configureFocus ;
- 		 lookUnfocused.
- 	ActiveHand removeKeyboardListener: self.
- 	model modelSleep!

Item was added:
+ ----- Method: SystemWindow>>passivateIfNeeded (in category 'focus') -----
+ passivateIfNeeded
+ 
+ 	self class windowsActiveOnlyOnTop
+ 		ifTrue: [self passivate]
+ 		ifFalse: [self lockWindowDecorations; lookUnfocused].!

Item was removed:
- ----- Method: SystemWindow>>positionSubmorphs (in category 'open/close') -----
- positionSubmorphs
- 	"Feels like overkill, but effect needed"
- 	super positionSubmorphs.
- 	self submorphsDo:
- 		[:aMorph | aMorph positionSubmorphs]!

Item was changed:
+ ----- Method: SystemWindow>>raisedColor (in category 'colors') -----
- ----- Method: SystemWindow>>raisedColor (in category 'colors handling') -----
  raisedColor
  	^self paneColor raisedColor!

Item was changed:
+ ----- Method: SystemWindow>>refreshWindowColor (in category 'colors') -----
- ----- Method: SystemWindow>>refreshWindowColor (in category 'colors handling') -----
  refreshWindowColor
  	"For changing the underlying model's default window color"
  	self setProperty: #paneColor toValue: nil.
  	self setWindowColor: self paneColor.
  
  	"Reset colors if we are not active."
+ 	self isKeyWindow ifFalse: [
- 	self isActive ifFalse: [
  		self paneColorToUseWhenNotActive in: [:c |
  			self
  				setStripeColorsFrom: c;
  				adoptPaneColor: c]].!

Item was changed:
  ----- Method: SystemWindow>>replaceBoxes (in category 'initialization') -----
  replaceBoxes
  	"Rebuild the various boxes."
  	self setLabelWidgetAllowance.
  	label ifNotNil: [label delete].
  	labelArea ifNotNil: [labelArea delete].
  	self initializeLabelArea.
  	self setFramesForLabelArea.
  	self setWindowColor: self paneColor.
+ 	self isActive
+ 		ifTrue: [self passivate; activate]
+ 		ifFalse: [self activate; passivate].!
- 	self isActive ifFalse: [self passivate].!

Item was changed:
+ ----- Method: SystemWindow>>restoreDefaultPaneColor (in category 'colors') -----
- ----- Method: SystemWindow>>restoreDefaultPaneColor (in category 'colors handling') -----
  restoreDefaultPaneColor
  	"Useful when changing from monochrome to color display"
  
  	self setStripeColorsFrom: self paneColor.!

Item was changed:
  ----- Method: SystemWindow>>sendToBack (in category 'menu') -----
  sendToBack
  	| aWorld nextWindow |
  	aWorld := self world.
  	nextWindow := aWorld submorphs 
  				detect: [:m | (m isSystemWindow) and: [m ~~ self]]
  				ifNone: [^self].
+ 	nextWindow beKeyWindow.
- 	nextWindow activate.
  	aWorld addMorphNearBack: self!

Item was changed:
  ----- Method: SystemWindow>>setDefaultParameters (in category 'initialization') -----
  setDefaultParameters
  
  	Preferences menuAppearance3d ifTrue: [
+ 		self hasDropShadow: self isKeyWindow.
- 		self hasDropShadow: self isActive.
  		
  		self useSoftDropShadow
  			ifTrue: [	
  				self
  					shadowColor: (TranslucentColor r: 0.0 g: 0.0 b: 0.0 alpha: 0.01);
  					shadowOffset: (10 at 8 corner: 10 at 12)]
  			ifFalse: [
  				self
  					shadowColor: (TranslucentColor r: 0.0 g: 0.0 b: 0.0 alpha: 0.333);
  					shadowOffset: 1 at 1] ].
  	self changed.!

Item was changed:
+ ----- Method: SystemWindow>>setStripeColorsFrom: (in category 'colors') -----
- ----- Method: SystemWindow>>setStripeColorsFrom: (in category 'colors handling') -----
  setStripeColorsFrom: paneColor 
  	"Set the stripe color based on the given paneColor"
  
  	labelArea ifNotNil: [labelArea color: Color transparent].
  	self updateBoxesColor: paneColor.
  	stripes ifNil: [^self].
  
  	self borderColor: (paneColor adjustBrightness: -0.3).
  
  	self class gradientWindow
  		ifTrue: [self fillStyle: (self gradientWithColor: paneColor)]
  		ifFalse: [self color: paneColor].!

Item was changed:
+ ----- Method: SystemWindow>>setWindowColor: (in category 'colors') -----
- ----- Method: SystemWindow>>setWindowColor: (in category 'colors handling') -----
  setWindowColor: incomingColor
  	| existingColor aColor |
  	incomingColor ifNil: [^ self].  "it happens"
  	aColor := incomingColor.
  	(aColor = ColorPickerMorph perniciousBorderColor 
  		or: [aColor = Color black]) ifTrue: [^ self].
  	existingColor := self paneColorToUse.
  	existingColor ifNil: [^ Beeper beep].
  	self paneColor: aColor.
  	self setStripeColorsFrom: aColor.
  	self changed.!

Item was added:
+ ----- Method: SystemWindow>>unlockWindowDecorations (in category 'focus') -----
+ unlockWindowDecorations
+ 	"Unlock all window decrations, that is grips, splitters, and title bar."
+ 	
+ 	self submorphsDo: [:m |
+ 		(self paneMorphs includes: m)
+ 			ifFalse: [m unlock]].
+ 		
+ 	
+ 	"Migrate old window instances."
+ 	labelArea ifNotNil: [:m | m submorphsDo: [:sm | sm unlock]].!

Item was added:
+ ----- Method: SystemWindow>>updateFocusLookAtHand (in category 'focus') -----
+ updateFocusLookAtHand
+ 	"If there is more than one active window, look for the mouse cursor and update the window focus look accordingly. This method is not on the class-side because we need our world and some active hand."
+ 	
+ 	self class windowsActiveOnlyOnTop ifTrue: [^ self].
+ 	
+ 	((self class windowsIn: self world)
+ 		do: [:window | window lookUnfocused];
+ 		select: [:window | window bounds containsPoint: self activeHand position])
+ 			ifNotEmpty: [:windowsPointed | windowsPointed first lookFocused "only to foremost window"].
+ 	
+ 	self class keyWindow lookFocused.!

Item was changed:
+ ----- Method: SystemWindow>>updatePaneColors (in category 'colors') -----
- ----- Method: SystemWindow>>updatePaneColors (in category 'colors handling') -----
  updatePaneColors
  	"Useful when changing from monochrome to color display"
  
  	self setStripeColorsFrom: self paneColorToUse.!

Item was changed:
  ----- Method: SystemWindowButton>>mouseEnter: (in category 'visual properties') -----
+ mouseEnter: evt
+ 
+ 	self highlight.
+ !
- mouseEnter: evt 
- 	| classicSqueakBehavior |
- 	classicSqueakBehavior := SystemWindow allWindowsAcceptInput not.
- 	classicSqueakBehavior
- 		ifTrue: [ self highlight ]
- 		ifFalse:
- 			[ self owningWindow ifNotNil:
- 				[ : window | (window isActive or: [ Model windowActiveOnFirstClick ]) ifTrue: [ self highlight ] ] ]!

Item was changed:
  ----- Method: TextMorphForEditView>>mouseUp: (in category 'event handling') -----
  mouseUp: evt
  	super mouseUp: evt.
  	self stopSteppingSelector: #autoScrollView:.
+ 	editView scrollSelectionIntoView: evt.
+ 
- 	SystemWindow allWindowsAcceptInput ifFalse: [editView scrollSelectionIntoView: evt].
  	self setCompositionWindow.
  !

Item was changed:
  ----- Method: TheWorldMainDockingBar>>listWindowsOn: (in category 'submenu - windows') -----
  listWindowsOn: menu
  
  	| windows |
  	windows := SortedCollection sortBlock: [:winA :winB |
  		winA model name = winB model name
  			ifTrue: [winA label < winB label]
  			ifFalse: [winA model name < winB model name]].
  	windows addAll: self allVisibleWindows.
  	windows ifEmpty: [ 
  		menu addItem: [ :item | 
  			item
  				contents: 'No Windows' translated;
  				isEnabled: false ] ].
  	windows do: [ :each |
  		menu addItem: [ :item |
  			item 
  				contents: (self windowMenuItemLabelFor: each);
  				icon: (self colorIcon: each model defaultBackgroundColor);
  				target: each;
  				selector: #comeToFront;
  				subMenuUpdater: self
  				selector: #windowMenuFor:on:
  				arguments: { each };
+ 				action: [ each beKeyWindow; expand ] ] ].
- 				action: [ each activateAndForceLabelToShow; expand ] ] ].
  	menu
  		addLine;
  		add: 'Close all windows' target: self selector: #closeAllWindowsUnsafe;
  		addItem: [:item | item
  			contents: 'Close all windows without changes';
  			target: self;
  			icon: MenuIcons smallBroomIcon;
  			selector: #closeAllWindows];
  		add: 'Close all windows but workspaces' target: self selector: #closeAllWindowsButWorkspaces.!

Item was changed:
+ (PackageInfo named: 'Morphic') postscript: 'SystemWindow reconfigureWindowsForFocus.'!
- (PackageInfo named: 'Morphic') postscript: 'SimpleBorder allSubInstancesDo: [ :each |
- 	(each instVarNamed: #width) ifNil: [ each instVarNamed: #width put: 0 ].
- 	(each instVarNamed: #color) ifNil: [ each instVarNamed: #color put: Color transparent ].
- 	(each instVarNamed: #baseColor) ifNil: [ each instVarNamed: #baseColor put: Color transparent ] ].'!



More information about the Squeak-dev mailing list