[squeak-dev] The Trunk: Morphic-kb.352.mcz

commits at source.squeak.org commits at source.squeak.org
Wed Feb 24 15:08:21 UTC 2010


Andreas Raab uploaded a new version of Morphic to project The Trunk:
http://source.squeak.org/trunk/Morphic-kb.352.mcz

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

Name: Morphic-kb.352
Author: kb
Time: 24 February 2010, 2:19:18.532 pm
UUID: 65cd154f-d443-49ed-9dc9-b9025591e736
Ancestors: Morphic-ar.348, Morphic-kb.350, Morphic-kb.351, Morphic-kb.349

 - merge of latest trunk, docking bar keyboard navigation and set style bugfix.

=============== Diff against Morphic-ar.348 ===============

Item was changed:
  ----- Method: DockingBarMorph>>deleteIfPopUp: (in category 'control') -----
  deleteIfPopUp: evt 
+ 	
+ 	evt ifNotNil: [
+ 		evt hand releaseMouseFocus: self ]!
- 	evt
- 		ifNotNil: [evt hand releaseMouseFocus: self]!

Item was changed:
  ----- Method: DockingBarMorph>>initialize (in category 'initialization') -----
  initialize
  	"initialize the receiver"
  	super initialize.
  	""
  	selectedItem := nil.
  	activeSubMenu := nil.
  	fillsOwner := true.
  	avoidVisibleBordersAtEdge := true.
  	autoGradient := Preferences gradientMenu.
  	""
  	self setDefaultParameters.
  	""
  	self beFloating; beSticky.
  	""
  	self layoutInset: 0.
+ 	Project current world activeHand addKeyboardListener: self!
- 	!

Item was added:
+ DockingBarMenuMorph subclass: #DockingBarUpdatingMenuMorph
+ 	instanceVariableNames: 'arguments updater updateSelector menuUpdater'
+ 	classVariableNames: ''
+ 	poolDictionaries: ''
+ 	category: 'Morphic-Menus-DockingBar'!

Item was changed:
  ----- Method: DockingBarMorph>>activeSubmenu: (in category 'control') -----
  activeSubmenu: aSubmenu 
  	activeSubMenu isNil
  		ifFalse: [activeSubMenu delete].
  	activeSubMenu := aSubmenu.
  	aSubmenu isNil
  		ifTrue: [^ self].
  	activeSubMenu updateMenu.
  	activeSubMenu selectItem: nil event: nil.
  	MenuIcons decorateMenu: activeSubMenu.
+ 	activeSubMenu 
+ 		activatedFromDockingBar: self;
+ 		borderColor: self borderColor;
+ 		beSticky;
+ 		resistsRemoval: true;
+ 		removeMatchString!
- 	activeSubMenu activatedFromDockingBar: self.
- 	activeSubMenu borderColor: self borderColor.
- 	activeSubMenu beSticky.
- 	activeSubMenu resistsRemoval: true.
- activeSubMenu removeMatchString.!

Item was added:
+ ----- Method: MenuMorph>>deactivate: (in category 'events') -----
+ deactivate: evt
+ 
+ 	"If a stand-alone menu, just delete it"
+ 	popUpOwner ifNil: [ 
+ 		self delete.
+ 		^true ].
+ 	"If a sub-menu, then deselect, and return focus to outer menu"
+ 	self selectItem: nil event: evt.
+ 	evt hand newMouseFocus: popUpOwner owner.
+ 	evt hand newKeyboardFocus: popUpOwner owner!

Item was added:
+ ----- Method: MenuMorph>>showKeyboardHelp (in category 'keystroke helpers') -----
+ showKeyboardHelp
+ 
+ 	| help |
+ 	help := BalloonMorph 
+ 		string: 'Enter text to\narrow selection down\to matching items ' withCRs 
+ 		for: self 
+ 		corner: #topLeft.
+ 	help popUpForHand: self activeHand!

Item was changed:
  ----- Method: UpdatingMenuMorph>>activate: (in category 'as yet unclassified') -----
  activate: evt
  	"Receiver should be activated; e.g., so that control passes correctly."
  	
  	self updateMenu.
+ 	super activate: evt!
- 	evt hand newMouseFocus: self.!

Item was changed:
  ----- Method: MenuMorph>>activeSubmenu: (in category 'control') -----
  activeSubmenu: aSubmenu 
  	activeSubMenu ifNotNil: [
  		activeSubMenu delete ].
  	activeSubMenu := aSubmenu.
  	activeSubMenu ifNotNil: [
+ 		activeSubMenu updateMenu ]!
- 		activeSubMenu updateMenu.
- 		activeSubMenu activatedFromDockingBar: nil. ]!

Item was added:
+ ----- Method: MenuMorph>>handleUpStorke: (in category 'keystroke helpers') -----
+ handleUpStorke: evt
+ 
+ 	evt keyValue = 30 ifFalse: [ ^false ].
+ 	self moveSelectionDown: -1 event: evt.
+ 	^true!

Item was added:
+ ----- Method: MenuMorph>>handleDownStroke: (in category 'keystroke helpers') -----
+ handleDownStroke: evt
+ 
+ 	evt keyValue = 31 ifFalse: [ ^false ].
+ 	self moveSelectionDown: 1 event: evt.
+ 	^true!

Item was added:
+ ----- Method: MenuMorph>>handleFiltering: (in category 'keystroke helpers') -----
+ handleFiltering: evt
+ 
+ 	| matchString |
+ 	matchString := self valueOfProperty: #matchString ifAbsentPut: [ String new ].
+ 	matchString := evt keyValue = 8 " Character backspace asciiValue "
+ 		ifTrue: [
+ 			matchString isEmpty 
+ 				ifTrue: [ matchString ] 
+ 				ifFalse: [ matchString allButLast ] ]
+ 		ifFalse: [
+ 			matchString copyWith: evt keyCharacter ].
+ 	self setProperty: #matchString toValue: matchString.
+ 	self displayFiltered: evt.
+ 	self showKeyboardHelp !

Item was added:
+ ----- Method: MenuMorph>>keyStrokeHandlers (in category 'keystroke helpers') -----
+ keyStrokeHandlers
+ 
+ 	^#(
+ 		handleCommandKeyPress:
+ 		handleCRStroke:
+ 		handleEscStroke:
+ 		handleLeftStroke:
+ 		handleRightStroke:
+ 		handleUpStorke:
+ 		handleDownStroke:
+ 		handlePageUpStroke:
+ 		handlePageDownStroke:)!

Item was added:
+ ----- Method: MenuItemMorph>>createUpdatingSubmenu (in category 'private') -----
+ createUpdatingSubmenu
+ 
+ 	^UpdatingMenuMorph new!

Item was added:
+ Object subclass: #MenuUpdater
+ 	instanceVariableNames: 'updater updateSelector arguments'
+ 	classVariableNames: ''
+ 	poolDictionaries: ''
+ 	category: 'Morphic-Menus'!

Item was added:
+ ----- Method: DockingBarUpdatingMenuMorph>>updater:updateSelector:arguments: (in category 'as yet unclassified') -----
+ updater: anObject updateSelector: aSelector arguments: anArray
+ 
+ 	menuUpdater updater: anObject updateSelector: aSelector arguments: anArray!

Item was changed:
  ----- Method: DockingBarMorph>>selectedItem (in category 'private') -----
  selectedItem
+ 
+ 	(selectedItem notNil and: [ 
+ 		selectedItem isSelected ]) ifTrue: [ 
+ 			^selectedItem ].
+ 	^ nil!
- 	selectedItem isNil
- 		ifTrue: [^ nil].
- 	^ selectedItem isSelected
- 		ifTrue: [ selectedItem]
- 		ifFalse: [ nil]!

Item was changed:
  ----- Method: DockingBarMorph>>activate: (in category 'events') -----
  activate: evt 
  	"Receiver should be activated; e.g., so that control passes  
  	correctly."
+ 	
+ 	oldKeyboardFocus := evt hand keyboardFocus.
+ 	self oldMouseFocus: evt hand mouseFocus.
+ 	evt hand 
+ 		newKeyboardFocus: self;
+ 		newMouseFocus: self.
+ 	self ensureSelectedItem: evt!
- 	evt hand newMouseFocus: self!

Item was changed:
  ----- Method: TheWorldMainDockingBar>>listWindowsOn: (in category 'submenu - windows') -----
  listWindowsOn: menu
  
  	| expanded |
  	expanded := SystemWindow windowsIn: World satisfying: [ :w | w isCollapsed not ].
  	expanded ifEmpty: [ 
  		menu addItem: [ :item | 
  			item
  				contents: 'No open Windows' translated;
  				isEnabled: false ] ].
  	expanded do: [ :each |
  		menu addItem: [ :item |
  			item 
  				contents: (each label contractTo: 50);
  				icon: (self colorIcon: each paneColor);
+ 				target: each;
+ 				selector: #comeToFront;
  				subMenuUpdater: self
  				selector: #windowMenuFor:on:
  				arguments: { each };
  				action: [ each activateAndForceLabelToShow ] ] ].!

Item was added:
+ ----- Method: MenuItemMorph>>createSubmenu (in category 'private') -----
+ createSubmenu
+ 
+ 	^MenuMorph new!

Item was added:
+ ----- Method: DockingBarItemMorph>>createUpdatingSubmenu (in category 'private') -----
+ createUpdatingSubmenu
+ 
+ 	^DockingBarUpdatingMenuMorph new!

Item was added:
+ ----- Method: DockingBarMenuMorph>>veryDeepInner: (in category 'copying') -----
+ veryDeepInner: deepCopier
+ 	"Copy all of my instance variables.  Some need to be not copied at all, but shared.  	Warning!!!!  Every instance variable defined in this class must be handled.  We must also implement veryDeepFixupWith:.  See DeepCopier class comment."
+ 
+ 	super veryDeepInner: deepCopier.
+ 	activatorDockingBar := activatorDockingBar.  "Weakly copied"
+ !

Item was added:
+ ----- Method: MenuMorph>>noteRootMenuHasUsedKeyboard (in category 'keystroke helpers') -----
+ noteRootMenuHasUsedKeyboard
+ 
+ 	(self rootMenu hasProperty: #hasUsedKeyboard) ifFalse: [
+ 		self setProperty: #hasUsedKeyboard toValue: true.
+ 		self changed ].!

Item was added:
+ ----- Method: DockingBarItemMorph>>createSubmenu (in category 'private') -----
+ createSubmenu
+ 
+ 	^DockingBarMenuMorph new!

Item was added:
+ ----- Method: DockingBarMorph>>oldMouseFocus (in category 'events') -----
+ oldMouseFocus
+ 	
+ 	oldMouseFocus = self
+ 		ifTrue: [ ^nil ]
+ 		ifFalse: [ ^oldMouseFocus ]!

Item was changed:
  MenuItemMorph subclass: #DockingBarItemMorph
  	instanceVariableNames: 'selectedIcon'
  	classVariableNames: ''
  	poolDictionaries: ''
+ 	category: 'Morphic-Menus-DockingBar'!
- 	category: 'Morphic-Menus'!

Item was added:
+ ----- Method: DockingBarMenuMorph>>roundedCorners (in category 'rounding') -----
+ roundedCorners
+ 	"Return a list of those corners to round"
+ 	activatorDockingBar isFloating
+ 		ifTrue: [^ #(2 3 )].
+ 	activatorDockingBar isAdheringToTop
+ 		ifTrue: [^ #(2 3 )].
+ 	activatorDockingBar isAdheringToBottom
+ 		ifTrue: [^ #(1 4 )].
+ 	activatorDockingBar isAdheringToLeft
+ 		ifTrue: [^ #(3 4 )].
+ 	activatorDockingBar isAdheringToRight
+ 		ifTrue: [^ #(1 2 )]!

Item was added:
+ ----- Method: MenuMorph>>handleRightStroke: (in category 'keystroke helpers') -----
+ handleRightStroke: evt
+ 
+ 	29 = evt keyValue ifFalse: [ ^false ].
+ 	self stepIntoSubmenu: evt.
+ 	^true!

Item was added:
+ ----- Method: MenuUpdater>>updater:updateSelector:arguments: (in category 'as yet unclassified') -----
+ updater: anObject updateSelector: aSelector arguments: anArray
+ 
+ 	updater := anObject.
+ 	updateSelector := aSelector.
+ 	arguments := anArray!

Item was changed:
  ----- Method: MenuMorph>>activate: (in category 'events') -----
  activate: evt
  	"Receiver should be activated; e.g., so that control passes correctly."
+ 	evt hand 
+ 		newMouseFocus: self;
+ 		newKeyboardFocus: self!
- 	evt hand newMouseFocus: self.!

Item was added:
+ ----- Method: DockingBarMenuMorph>>handleLeftStroke: (in category 'keystroke helpers') -----
+ handleLeftStroke: evt
+ 
+ 	28 = evt keyValue ifFalse: [ ^false ].
+ 	(self stepIntoSubmenu: evt) ifFalse: [ 
+ 		self deactivate: evt.
+ 		activatorDockingBar moveSelectionDown: -1 event: evt ].
+ 	^true!

Item was added:
+ ----- Method: DockingBarMorph>>keyStroke: (in category 'events-processing') -----
+ keyStroke: evt 
+ 
+ 	| asc |
+ 	asc := evt keyCharacter asciiValue.
+ 	asc = 27 ifTrue: [ "escape key" 
+ 		^self deactivate: evt ].
+ 	asc = self selectSubmenuKey ifTrue: [
+ 		self ensureSelectedItem: evt.
+ 		self selectedItem subMenu ifNotNil: [ :subMenu |
+ 			subMenu items ifNotEmpty: [
+ 				subMenu activate: evt.
+ 				^subMenu moveSelectionDown: 1 event: evt ] ] ].
+ 	asc = self previousKey ifTrue: [ ^self moveSelectionDown: -1 event: evt ].
+ 	asc = self nextKey ifTrue: [ ^self moveSelectionDown: 1 event: evt ].!

Item was added:
+ ----- Method: DockingBarMorph>>ensureSelectedItem: (in category 'events') -----
+ ensureSelectedItem: evt
+ 	
+ 	self selectedItem ifNil: [
+ 		self 
+ 			selectItem: (
+ 				self submorphs 
+ 					detect: [ :each | each isKindOf: DockingBarItemMorph ] 
+ 					ifNone: [ ^self ]) 
+ 			event: evt ]!

Item was added:
+ ----- Method: DockingBarMorph>>oldMouseFocus: (in category 'events') -----
+ oldMouseFocus: aMorph
+ 	
+ 	(self submorphs includes: aMorph) 
+ 		ifFalse: [ oldMouseFocus := aMorph ]
+ 		ifTrue: [ oldMouseFocus := nil ]
+ 	!

Item was added:
+ MenuMorph subclass: #DockingBarMenuMorph
+ 	instanceVariableNames: 'activatorDockingBar'
+ 	classVariableNames: ''
+ 	poolDictionaries: ''
+ 	category: 'Morphic-Menus-DockingBar'!

Item was changed:
  ----- Method: MenuItemMorph>>subMenuUpdater:selector: (in category 'accessing') -----
  subMenuUpdater: updater selector: selector
  
+ 	subMenu := self createUpdatingSubmenu.
- 	subMenu := UpdatingMenuMorph new.
  	subMenu updater: updater updateSelector: selector.
  	self changed.
  !

Item was added:
+ ----- Method: MenuMorph>>handleCRStroke: (in category 'keystroke helpers') -----
+ handleCRStroke: evt
+ 
+ 	| selectable |
+ 	evt keyValue = 13 ifFalse: [ ^false ].
+ 	selectedItem ifNotNil: [
+ 		selectedItem hasSubMenu 
+ 			ifTrue: [
+ 				evt hand 
+ 					newMouseFocus: selectedItem subMenu;
+ 					newKeyboardFocus: selectedItem subMenu ]
+ 			ifFalse:  [
+ 				selectedItem invokeWithEvent: evt ].
+ 		^true ].
+ 	(selectable := self items) size = 1 ifTrue: [ 
+ 		selectable first invokeWithEvent: evt ].
+ 	^true!

Item was changed:
  ----- Method: TextEditor>>changeStyle (in category 'attributes') -----
  changeStyle
  	"Let user change styles for the current text pane."
  	| names reply style current menuList |
  
  	current := paragraph textStyle.
+ 	names := TextStyle knownTextStyles.
- 	names := TextStyle availableTextStyleNames.
  	menuList := names collect: [ :styleName |
  		styleName = current name
  			ifTrue: [ '<on>', styleName ]
  			ifFalse: [ '<off>', styleName ]].
  	reply := UIManager default chooseFrom: menuList values: names.
  	reply ifNotNil: [
  		(style := TextStyle named: reply) ifNil: [Beeper beep. ^ true].
  		paragraph textStyle: style.
  		paragraph composeAll.
  		self recomputeSelection].
  	^ true!

Item was changed:
  ----- Method: UpdatingMenuMorph>>updater:updateSelector:arguments: (in category 'initialization') -----
  updater: anObject updateSelector: aSelector arguments: anArray
  
+ 	menuUpdater updater: anObject updateSelector: aSelector arguments: anArray!
- 	updater := anObject.
- 	updateSelector := aSelector.
- 	arguments := anArray!

Item was changed:
  ----- Method: MenuMorph>>keyStroke: (in category 'keyboard control') -----
  keyStroke: evt 
- 	| matchString char asc selectable help |
- 	help := BalloonMorph string: 'Enter text to\narrow selection down\to matching items ' withCRs for: self corner: #topLeft.
- 	help popUpForHand: self activeHand.
- 	(self rootMenu hasProperty: #hasUsedKeyboard) 
- 		ifFalse: 
- 			[self rootMenu setProperty: #hasUsedKeyboard toValue: true.
- 			self changed].
- 	(evt commandKeyPressed and: [self commandKeyHandler notNil]) 
- 		ifTrue: 
- 			[self commandKeyHandler commandKeyTypedIntoMenu: evt.
- 			^self deleteIfPopUp: evt].
- 	char := evt keyCharacter.
- 	asc := char asciiValue.
- 	char = Character cr 
- 		ifTrue: 
- 			[selectedItem ifNotNil: 
- 					[selectedItem hasSubMenu 
- 						ifTrue: 
- 							[evt hand newMouseFocus: selectedItem subMenu.
- 							^evt hand newKeyboardFocus: selectedItem subMenu]
- 						ifFalse: 
- 							["self delete."
- 
- 							^selectedItem invokeWithEvent: evt]].
- 			(selectable := self items) size = 1 
- 				ifTrue: [^selectable first invokeWithEvent: evt].
- 			^self].
- 	asc = 27 
- 		ifTrue: 
- 			["escape key"
- 
- 			self valueOfProperty: #matchString
- 				ifPresentDo: 
- 					[:str | 
- 					str isEmpty 
- 						ifFalse: 
- 							["If filtered, first ESC removes filter"
- 
- 							self setProperty: #matchString toValue: String new.
- 							self selectItem: nil event: evt.
- 							^self displayFiltered: evt]].
- 			"If a stand-alone menu, just delete it"
- 			popUpOwner ifNil: [^self delete].
- 			"If a sub-menu, then deselect, and return focus to outer menu"
- 			self selectItem: nil event: evt.
- 			evt hand newMouseFocus: popUpOwner owner.
- 			^evt hand newKeyboardFocus: popUpOwner owner ].
  	
+ 	self 
+ 		showKeyboardHelp;
+ 		noteRootMenuHasUsedKeyboard.
+ 	self keyStrokeHandlers
+ 		detect: [ :each | self perform: each with: evt ]
+ 		ifNone: [ self handleFiltering: evt ].!
- 	(asc = 28 or: [asc = 29]) 
- 		ifTrue: 
- 			["left or right arrow key"
- 
- 			(selectedItem notNil and: [selectedItem hasSubMenu]) 
- 				ifTrue: 
- 					[evt hand newMouseFocus: selectedItem subMenu.
- 					selectedItem subMenu moveSelectionDown: 1 event: evt.
- 					^evt hand newKeyboardFocus: selectedItem subMenu]
- 				ifFalse: [ ^self ] ].
- 	asc = 30 ifTrue: [^self moveSelectionDown: -1 event: evt].	"up arrow key"
- 	asc = 31 ifTrue: [^self moveSelectionDown: 1 event: evt].	"down arrow key"
- 	asc = 11 ifTrue: [^self moveSelectionDown: -5 event: evt].	"page up key"
- 	asc = 12 ifTrue: [^self moveSelectionDown: 5 event: evt].	"page down key"
- 	matchString := self valueOfProperty: #matchString ifAbsentPut: [String new].
- 	matchString := char = Character backspace 
- 				ifTrue: 
- 					[matchString isEmpty ifTrue: [matchString] ifFalse: [matchString allButLast]]
- 				ifFalse: [matchString copyWith: evt keyCharacter].
- 	self setProperty: #matchString toValue: matchString.
- 	self displayFiltered: evt.
- 	help := BalloonMorph string: 'Enter text to\narrow selection down\to matching items ' withCRs for: self corner: #topLeft.
- 	help popUpForHand: self activeHand.
- !

Item was changed:
  ----- Method: MenuMorph>>popUpAdjacentTo:forHand:from: (in category 'control') -----
  popUpAdjacentTo: rightOrLeftPoint forHand: hand from: sourceItem 
  	"Present this menu at the given point under control of the given  
  	hand."
  	| tryToPlace selectedOffset |
  	hand world startSteppingSubmorphsOf: self.
  	popUpOwner := sourceItem.
  	self fullBounds.
  self updateColor.
  	"ensure layout is current"
  	selectedOffset := (selectedItem
  				ifNil: [self items first]) position - self position.
  	tryToPlace := [:where :mustFit | | delta | 
  			self position: where - selectedOffset.
  			delta := self fullBoundsInWorld amountToTranslateWithin: sourceItem worldBounds.
  			(delta x = 0
  					or: [mustFit])
  				ifTrue: [delta = (0 @ 0)
  						ifFalse: [self position: self position + delta].
  					sourceItem owner owner addMorphFront: self.
  					^ self]].
  	tryToPlace value: rightOrLeftPoint first value: false;
  		 value: rightOrLeftPoint last - (self width @ 0) value: false;
  		 value: rightOrLeftPoint first value: true!

Item was added:
+ ----- Method: MenuMorph>>handlePageDownStroke: (in category 'keystroke helpers') -----
+ handlePageDownStroke: evt
+ 
+ 	evt keyValue = 12 ifFalse: [ ^false ].
+ 	self moveSelectionDown: 5 event: evt.
+ 	^true!

Item was changed:
  AlignmentMorph subclass: #DockingBarMorph
+ 	instanceVariableNames: 'originalColor gradientRamp fillsOwner avoidVisibleBordersAtEdge autoGradient selectedItem activeSubMenu oldKeyboardFocus oldMouseFocus'
- 	instanceVariableNames: 'originalColor gradientRamp fillsOwner avoidVisibleBordersAtEdge autoGradient selectedItem activeSubMenu'
  	classVariableNames: ''
  	poolDictionaries: ''
+ 	category: 'Morphic-Menus-DockingBar'!
- 	category: 'Morphic-Menus'!

Item was added:
+ ----- Method: DockingBarMorph>>selectSubmenuKey (in category 'events-processing') -----
+ selectSubmenuKey
+ 
+ 	self isAdheringToTop ifTrue: [ ^31 ].
+ 	self isAdheringToRight ifTrue: [ ^28 ].
+ 	self isAdheringToLeft ifTrue: [ ^29 ].
+ 	self isAdheringToBottom ifTrue: [ 30 ].
+ 	^31!

Item was added:
+ ----- Method: MenuMorph>>handleRightStorke: (in category 'keystroke helpers') -----
+ handleRightStorke: evt
+ 
+ 	29 = evt keyValue ifFalse: [ ^false ].
+ 	self stepIntoSubmenu: evt.
+ 	^true!

Item was added:
+ ----- Method: MenuMorph>>handlePageUpStroke: (in category 'keystroke helpers') -----
+ handlePageUpStroke: evt
+ 
+ 	evt keyValue = 11 ifFalse: [ ^false ].
+ 	self moveSelectionDown: -5 event: evt.
+ 	^true!

Item was added:
+ ----- Method: DockingBarMorph>>handleListenEvent: (in category 'events-processing') -----
+ handleListenEvent: anEvent
+ 	
+ 	(anEvent controlKeyPressed and: [ anEvent keyValue = 96 " ` " ]) ifTrue: [ 
+ 		self activate: anEvent ]!

Item was added:
+ ----- Method: MenuMorph>>stepIntoSubmenu: (in category 'keystroke helpers') -----
+ stepIntoSubmenu: evt
+ 
+ 	(selectedItem notNil and: [ selectedItem hasSubMenu ]) ifTrue: [
+ 		evt hand newMouseFocus: selectedItem subMenu.
+ 		evt hand newKeyboardFocus: selectedItem subMenu.
+ 		selectedItem subMenu moveSelectionDown: 1 event: evt.
+ 		^true ].
+ 	^false!

Item was added:
+ ----- Method: MenuMorph>>handlePageDownStorke: (in category 'keystroke helpers') -----
+ handlePageDownStorke: evt
+ 
+ 	evt keyValue = 12 ifFalse: [ ^false ].
+ 	self moveSelectionDown: 5 event: evt.
+ 	^true!

Item was changed:
  MenuMorph subclass: #UpdatingMenuMorph
+ 	instanceVariableNames: 'menuUpdater'
- 	instanceVariableNames: 'updater updateSelector arguments'
  	classVariableNames: ''
  	poolDictionaries: ''
  	category: 'Morphic-Menus'!

Item was added:
+ ----- Method: MenuMorph>>handleEscStroke: (in category 'keystroke helpers') -----
+ handleEscStroke: evt
+ 
+ 	evt keyValue = 27 ifFalse: [ ^false ].
+ 	self 
+ 		valueOfProperty: #matchString
+ 		ifPresentDo: [ :str | 
+ 			str isEmpty ifFalse: [ "If filtered, first ESC removes filter"
+ 				self setProperty: #matchString toValue: String new.
+ 				self selectItem: nil event: evt.
+ 				self displayFiltered: evt.
+ 				^true ] ].
+ 	self deactivate: evt.
+ 	^true!

Item was changed:
  ----- Method: DockingBarItemMorph>>mouseDown: (in category 'events') -----
  mouseDown: evt
  	"Handle a mouse down event. Menu items get activated when the mouse is over them."
  
  	evt shiftPressed ifTrue: [ ^super mouseDown: evt ].  "enable label editing" 
  	isSelected
  		ifTrue: [
  			evt hand newMouseFocus: nil.
  			owner selectItem: nil event: evt. ]
  		ifFalse: [
+ 			(self containsPoint: evt position) ifFalse: [ self halt ].
+ 			owner activate: evt. "Redirect to menu for valid transitions"
- 			evt hand newMouseFocus: owner. "Redirect to menu for valid transitions"
  			owner selectItem: self event: evt. ]
  !

Item was changed:
  ----- Method: MenuItemMorph>>addSubMenu: (in category 'accessing') -----
  addSubMenu: aBlock
  
+ 	subMenu := self createSubmenu.
- 	subMenu := MenuMorph new.
  	aBlock value: subMenu.
  	self changed.
  !

Item was changed:
  ----- Method: MenuItemMorph>>subMenuUpdater:selector:arguments: (in category 'accessing') -----
  subMenuUpdater: updater selector: selector arguments: arguments
  
+ 	subMenu := self createUpdatingSubmenu.
- 	subMenu := UpdatingMenuMorph new.
  	subMenu updater: updater updateSelector: selector arguments: arguments.
  	self changed.
  !

Item was added:
+ ----- Method: DockingBarUpdatingMenuMorph>>initialize (in category 'as yet unclassified') -----
+ initialize
+ 
+ 	super initialize.
+ 	menuUpdater := MenuUpdater new!

Item was added:
+ ----- Method: DockingBarUpdatingMenuMorph>>updater:updateSelector: (in category 'as yet unclassified') -----
+ updater: anObject updateSelector: aSelector
+ 
+ 	menuUpdater updater: anObject updateSelector: aSelector!

Item was changed:
  ----- Method: MenuMorph>>veryDeepInner: (in category 'copying') -----
  veryDeepInner: deepCopier
  	"Copy all of my instance variables.  Some need to be not copied at all, but shared.  	Warning!!!!  Every instance variable defined in this class must be handled.  We must also implement veryDeepFixupWith:.  See DeepCopier class comment."
  
+ 	super veryDeepInner: deepCopier.
+ 	"defaultTarget := defaultTarget.		Weakly copied"
+ 	selectedItem := selectedItem veryDeepCopyWith: deepCopier.
+ 	stayUp := stayUp veryDeepCopyWith: deepCopier.
+ 	popUpOwner := popUpOwner.		"Weakly copied"
+ 	activeSubMenu := activeSubMenu. "Weakly copied"
- super veryDeepInner: deepCopier.
- "defaultTarget := defaultTarget.		Weakly copied"
- selectedItem := selectedItem veryDeepCopyWith: deepCopier.
- stayUp := stayUp veryDeepCopyWith: deepCopier.
- popUpOwner := popUpOwner.		"Weakly copied"
- activeSubMenu := activeSubMenu. "Weakly copied"
- activatorDockingBar := activatorDockingBar.  "Weakly copied"
  !

Item was added:
+ ----- Method: MenuUpdater>>update: (in category 'as yet unclassified') -----
+ update: aMenuMorph
+ 	"Reconstitute the menu by first removing the contents and then building it afresh"
+ 
+ 	aMenuMorph removeAllMorphs.
+ 	arguments 
+ 		ifNil: [ updater perform: updateSelector with: aMenuMorph ]
+ 		ifNotNil: [ 
+ 			updater 
+ 				perform: updateSelector 
+ 				withArguments: (arguments copyWith: aMenuMorph) ].
+ 	aMenuMorph changed!

Item was added:
+ ----- Method: DockingBarMorph>>moveSelectionDown:event: (in category 'control') -----
+ moveSelectionDown: direction event: evt
+ 	"Move the current selection up or down by one, presumably under keyboard control.
+ 	direction = +/-1"
+ 
+ 	| index |
+ 	index := (submorphs indexOf: selectedItem ifAbsent: [1-direction]) + direction.
+ 	submorphs do: "Ensure finite"
+ 		[:unused | | m |
+ 		m := submorphs atWrap: index.
+ 		((m isKindOf: DockingBarItemMorph) and: [m isEnabled]) ifTrue:
+ 			[^ self selectItem: m event: evt].
+ 		"Keep looking for an enabled item"
+ 		index := index + direction sign].
+ 	^ self selectItem: nil event: evt!

Item was added:
+ ----- Method: DockingBarUpdatingMenuMorph>>updateMenu (in category 'as yet unclassified') -----
+ updateMenu
+ 
+ 	menuUpdater update: self!

Item was added:
+ ----- Method: MenuMorph>>handleCommandKeyPress: (in category 'keystroke helpers') -----
+ handleCommandKeyPress: evt
+ 
+ 	(evt commandKeyPressed and: [
+ 		self commandKeyHandler notNil ]) ifTrue: [
+ 			self commandKeyHandler commandKeyTypedIntoMenu: evt.
+ 			self deleteIfPopUp: evt.
+ 			^true ].
+ 	^false!

Item was added:
+ ----- Method: MenuMorph>>handleLeftStroke: (in category 'keystroke helpers') -----
+ handleLeftStroke: evt
+ 
+ 	28 = evt keyValue ifFalse: [ ^false ].
+ 	self stepIntoSubmenu: evt.
+ 	^true!

Item was added:
+ ----- Method: DockingBarMorph>>handlesKeyboard: (in category 'events-processing') -----
+ handlesKeyboard: evt
+ 
+ 	^true!

Item was added:
+ ----- Method: MenuUpdater>>updater:updateSelector: (in category 'as yet unclassified') -----
+ updater: anObject updateSelector: aSelector
+ 
+ 	self updater: anObject updateSelector: aSelector arguments: nil!

Item was added:
+ ----- Method: DockingBarMorph>>nextKey (in category 'events-processing') -----
+ nextKey
+ 
+ 	self isHorizontal ifTrue: [ ^29 " right arrow" ].
+ 	self isVertical ifTrue: [ ^31 " down arrow " ]!

Item was added:
+ ----- Method: DockingBarMorph>>previousKey (in category 'events-processing') -----
+ previousKey
+ 
+ 	self isHorizontal ifTrue: [ ^28 "left arrow" ].
+ 	self isVertical ifTrue: [ ^30 "up arrow " ]!

Item was changed:
+ (PackageInfo named: 'Morphic') postscript: 'DockingBarMorph allInstances do: #delete.
+ TheWorldMainDockingBar updateInstances
+ '!
- (PackageInfo named: 'Morphic') postscript: 'nil'!

Item was added:
+ ----- Method: DockingBarMenuMorph>>handleRightStroke: (in category 'keystroke helpers') -----
+ handleRightStroke: evt
+ 
+ 	29 = evt keyValue ifFalse: [ ^false ].
+ 	(self stepIntoSubmenu: evt) ifFalse: [
+ 		self deactivate: evt.
+ 		activatorDockingBar moveSelectionDown: 1 event: evt ].
+ 	^true!

Item was changed:
  AlignmentMorph subclass: #MenuMorph
+ 	instanceVariableNames: 'defaultTarget selectedItem stayUp popUpOwner activeSubMenu'
- 	instanceVariableNames: 'defaultTarget selectedItem stayUp popUpOwner activeSubMenu activatorDockingBar'
  	classVariableNames: 'CloseBoxImage PushPinImage'
  	poolDictionaries: ''
  	category: 'Morphic-Menus'!
  
  !MenuMorph commentStamp: '<historical>' prior: 0!
  Instance variables:
  	defaultTarget 	<Object>				The default target for creating menu items
  	selectedItem		<MenuItemMorph> 	The currently selected item in the receiver
  	stayUp 			<Boolean>			True if the receiver should stay up after clicks
  	popUpOwner 	<MenuItemMorph>	The menu item that automatically invoked the receiver, if any.
  	activeSubMenu 	<MenuMorph>		The currently active submenu.!

Item was changed:
  ----- Method: UpdatingMenuMorph>>updater:updateSelector: (in category 'initialization') -----
  updater: anObject updateSelector: aSelector
- 	"Set the receiver's updater and updateSelector"
  
+ 	menuUpdater updater: anObject updateSelector: aSelector!
- 	updater := anObject.
- 	updateSelector := aSelector!

Item was changed:
  ----- Method: DockingBarMorph>>delete (in category 'submorphs-add/remove') -----
  delete
+ 
+ 	ActiveHand removeKeyboardListener: self.
  	activeSubMenu
  		ifNotNil: [activeSubMenu delete].
  	^ super delete!

Item was added:
+ ----- Method: UpdatingMenuMorph>>initialize (in category 'initialization') -----
+ initialize
+ 
+ 	super initialize.
+ 	menuUpdater := MenuUpdater new!

Item was added:
+ ----- Method: DockingBarMenuMorph>>handleCRStroke: (in category 'keystroke helpers') -----
+ handleCRStroke: evt
+ 
+ 	evt keyValue = 13 ifFalse: [ ^false ].
+ 	selectedItem ifNotNil: [ selectedItem invokeWithEvent: evt ].
+ 	^true!

Item was added:
+ ----- Method: DockingBarMenuMorph>>activatedFromDockingBar: (in category 'as yet unclassified') -----
+ activatedFromDockingBar: aDockingBar 
+ 
+ 	activatorDockingBar := aDockingBar!

Item was changed:
  SystemOrganization addCategory: #'Morphic-Balloon'!
  SystemOrganization addCategory: #'Morphic-Basic'!
  SystemOrganization addCategory: #'Morphic-Basic-NewCurve'!
  SystemOrganization addCategory: #'Morphic-Borders'!
  SystemOrganization addCategory: #'Morphic-Collections-Arrayed'!
  SystemOrganization addCategory: #'Morphic-Demo'!
  SystemOrganization addCategory: #'Morphic-Events'!
  SystemOrganization addCategory: #'Morphic-Explorer'!
  SystemOrganization addCategory: #'Morphic-Kernel'!
  SystemOrganization addCategory: #'Morphic-Layouts'!
  SystemOrganization addCategory: #'Morphic-Menus'!
+ SystemOrganization addCategory: #'Morphic-Menus-DockingBar'!
  SystemOrganization addCategory: #'Morphic-Models'!
  SystemOrganization addCategory: #'Morphic-Pluggable Widgets'!
  SystemOrganization addCategory: #'Morphic-Support'!
  SystemOrganization addCategory: #'Morphic-Text Support'!
  SystemOrganization addCategory: #'Morphic-TrueType'!
  SystemOrganization addCategory: #'Morphic-Widgets'!
  SystemOrganization addCategory: #'Morphic-Windows'!
  SystemOrganization addCategory: #'Morphic-Worlds'!

Item was changed:
  ----- Method: UpdatingMenuMorph>>updateMenu (in category 'update') -----
  updateMenu
- 	"Reconstitute the menu by first removing the contents and then building it afresh"
  
+ 	menuUpdater update: self!
- 	self removeAllMorphs.
- 	arguments 
- 		ifNil: [ updater perform: updateSelector with: self ]
- 		ifNotNil: [ 
- 			updater 
- 				perform: updateSelector 
- 				withArguments: arguments, { self } ]
- 	!

Item was added:
+ ----- Method: DockingBarMorph>>oldKeyboardFocus (in category 'events') -----
+ oldKeyboardFocus
+ 	
+ 	oldKeyboardFocus = self
+ 		ifTrue: [ ^nil ]
+ 		ifFalse: [ ^oldKeyboardFocus ]!

Item was added:
+ ----- Method: DockingBarMorph>>deactivate: (in category 'events') -----
+ deactivate: evt 
+ 
+ 	self selectItem: nil event: evt.
+ 	evt hand
+ 		newKeyboardFocus: self oldKeyboardFocus;
+ 		newMouseFocus: self oldMouseFocus!

Item was removed:
- ----- Method: MenuMorph>>activatedFromDockingBar: (in category 'accessing') -----
- activatedFromDockingBar: aDockingBar 
- 	activatorDockingBar := aDockingBar!

Item was removed:
- ----- Method: MenuMorph>>wasActivatedFromDockingBar (in category 'accessing') -----
- wasActivatedFromDockingBar
- 	"answer true if the receiver was activated from a docking bar"
- 	^ activatorDockingBar notNil!

Item was removed:
- ----- Method: MenuMorph>>moveUp: (in category 'keyboard control') -----
- moveUp: evt 
- 	^self moveSelectionDown: -1 event: evt!

Item was removed:
- ----- Method: MenuMorph>>roundedCorners (in category 'rounding') -----
- roundedCorners
- 	"Return a list of those corners to round"
- 	self wasActivatedFromDockingBar
- 		ifTrue: [""
- 			activatorDockingBar isFloating
- 				ifTrue: [^ #(2 3 )].
- 			activatorDockingBar isAdheringToTop
- 				ifTrue: [^ #(2 3 )].
- 			activatorDockingBar isAdheringToBottom
- 				ifTrue: [^ #(1 4 )].
- 			activatorDockingBar isAdheringToLeft
- 				ifTrue: [^ #(3 4 )].
- 			activatorDockingBar isAdheringToRight
- 				ifTrue: [^ #(1 2 )]].
- 	^ super roundedCorners!

Item was removed:
- ----- Method: MenuMorph>>moveRightOrDown: (in category 'keyboard control') -----
- moveRightOrDown: evt 
- 	selectedItem ifNotNil: 
- 			[selectedItem hasSubMenu 
- 				ifTrue: 
- 					[self selectSubMenu: evt.
- 					selectedItem subMenu moveDown: evt]
- 				ifFalse: [self moveDown: evt]]!

Item was removed:
- ----- Method: MenuMorph>>moveDown: (in category 'keyboard control') -----
- moveDown: evt 
- 	^self moveSelectionDown: 1 event: evt!




More information about the Squeak-dev mailing list