[squeak-dev] The Trunk: Tools-mt.670.mcz

commits at source.squeak.org commits at source.squeak.org
Wed Feb 3 20:07:14 UTC 2016


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

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

Name: Tools-mt.670
Author: mt
Time: 3 February 2016, 9:06:55.449922 pm
UUID: 4c92b664-5e2f-422e-a5a1-35241e64ad52
Ancestors: Tools-mt.669

Stop using the context menu of an inspector in the object explorer. Now the object explorer has its own working callbacks.

This fixes a bug where it was difficult (if not impossible) to invoke menu (of keyboard shortcut) operations on objects in the tree if the enclosing parent was volatile. This also removes the annoying pop-up or debugger, which used to appear in those cases.

=============== Diff against Tools-mt.669 ===============

Item was added:
+ ----- Method: ObjectExplorer>>browseClassRefs (in category 'menus - actions') -----
+ browseClassRefs
+ 
+ 	(self selectedClass notNil and: [self selectedClass isTrait not])
+ 		ifTrue: [self systemNavigation browseAllCallsOnClass: self selectedClass theNonMetaClass].!

Item was added:
+ ----- Method: ObjectExplorer>>browseFull (in category 'menus - actions') -----
+ browseFull
+ 
+ 	^ self selectedClass ifNotNil: [:cls | ToolSet browseClass: cls]!

Item was added:
+ ----- Method: ObjectExplorer>>browseVariableAssignments (in category 'menus - actions') -----
+ browseVariableAssignments
+ 
+ 	(self selectedClass notNil and: [self selectedClass isTrait not])
+ 		ifTrue: [self systemNavigation browseVariableAssignments: self selectedClass].!

Item was added:
+ ----- Method: ObjectExplorer>>browseVariableReferences (in category 'menus - actions') -----
+ browseVariableReferences
+ 
+ 	(self selectedClass notNil and: [self selectedClass isTrait not])
+ 		ifTrue: [self systemNavigation browseVariableReferences: self selectedClass].!

Item was added:
+ ----- Method: ObjectExplorer>>chasePointersForSelection (in category 'menus - actions') -----
+ chasePointersForSelection
+ 	
+ 	self flag: #tooMany. "mt: Note that we might want to ignore references caused by this tool."
+ 	self object chasePointers.!

Item was added:
+ ----- Method: ObjectExplorer>>classHierarchy (in category 'menus - actions') -----
+ classHierarchy
+ 	"Create and schedule a class list browser on the receiver's hierarchy."
+ 
+ 	self systemNavigation
+ 		spawnHierarchyForClass: self selectedClass
+ 		selector: nil
+ !

Item was added:
+ ----- Method: ObjectExplorer>>copyName (in category 'menus - actions') -----
+ copyName
+ 	"Copy the name of the current variable, so the user can paste it into the window below and work with is."
+ 	
+ 	Clipboard clipboardText: self currentSelection key.	!

Item was added:
+ ----- Method: ObjectExplorer>>defsOfSelection (in category 'menus - actions') -----
+ defsOfSelection
+ 	"Open a browser on all defining references to the selected instance variable, if that's what currently selected. "
+ 	
+ 	self selectedParentClass ifNil: [^ self changed: #flash].
+ 	self selectedParentClass isVariable ifTrue: [^ self changed: #flash].
+ 	self selectedInstVarName ifNil: [^ self changed: #flash].
+ 
+ 	self systemNavigation browseAllStoresInto: self selectedInstVarName from: self selectedParentClass.!

Item was added:
+ ----- Method: ObjectExplorer>>explorePointersForSelection (in category 'menus - actions') -----
+ explorePointersForSelection
+ 	
+ 	self flag: #tooMany. "mt: Note that we might want to ignore references caused by this tool."
+ 	self object explorePointers.!

Item was added:
+ ----- Method: ObjectExplorer>>exploreSelection (in category 'menus - actions') -----
+ exploreSelection
+ 
+ 	self object explore.!

Item was changed:
  ----- Method: ObjectExplorer>>explorerKey:from:event: (in category 'menus') -----
  explorerKey: aChar from: view event: event
  
  	event anyModifierKeyPressed ifFalse: [^ false].
  
+ 	self object ifNotNil: [
+ 		aChar == $i ifTrue: [self inspectSelection. ^ true].
+ 		aChar == $I ifTrue: [self exploreSelection. ^ true].
- 	currentSelection ifNotNil: [
- 		self updateInspectorForSelection ifFalse: [^ true].
  
+ 		aChar == $b ifTrue:	[self browseFull. ^ true].
+ 		aChar == $h ifTrue:	[self classHierarchy. ^ true].
+ 		aChar == $c ifTrue: [self copyName. ^ true].
+ 		aChar == $p ifTrue: [self browseFullProtocol. ^ true].
+ 		aChar == $N ifTrue: [self browseClassRefs. ^ true].
+ 		aChar == $v ifTrue: [self viewerForValue. ^ true]].
- 		aChar == $i ifTrue: [self inspector inspectSelection. ^ true].
- 		aChar == $I ifTrue: [self inspector exploreSelection. ^ true].
  
- 		aChar == $b ifTrue:	[self inspector browseMethodFull. ^ true].
- 		aChar == $h ifTrue:	[self inspector classHierarchy. ^ true].
- 		aChar == $c ifTrue: [Clipboard clipboardText: self currentSelection key. ^ true].
- 		aChar == $p ifTrue: [self inspector browseFullProtocol. ^ true].
- 		aChar == $N ifTrue: [self inspector browseClassRefs. ^ true].
- 		aChar == $t ifTrue: [self inspector tearOffTile. ^ true].
- 		aChar == $v ifTrue: [self inspector viewerForValue. ^ true]].
- 
  	^ false!

Item was changed:
  ----- Method: ObjectExplorer>>genericMenu: (in category 'menus') -----
  genericMenu: aMenu 
- 	"Borrow a menu from my inspector"
  
+ 	^ self menu: aMenu for: #(treeListMenu treeListMenuShifted:)!
- 	currentSelection
- 		ifNil: [
- 			aMenu
- 				add: '*nothing selected*'
- 				target: self
- 				selector: #yourself]
- 		ifNotNil: [
- 			self updateInspectorForSelection ifFalse: [^ aMenu].		
- 			aMenu defaultTarget: self inspector.
- 			self inspector fieldListMenu: aMenu.
- 
- 			aMenu addLine;
- 				add: 'monitor changes'
- 				target: self
- 				selector: #monitor:
- 				argument: currentSelection].
- 	monitorList isEmptyOrNil
- 		ifFalse: [aMenu addLine;
- 				add: 'stop monitoring all'
- 				target: self
- 				selector: #stopMonitoring].
- 	^ aMenu!

Item was added:
+ ----- Method: ObjectExplorer>>inspectBasic (in category 'menus - actions') -----
+ inspectBasic
+ 	"Bring up a non-special inspector"
+ 
+ 	self object basicInspect.!

Item was added:
+ ----- Method: ObjectExplorer>>inspectSelection (in category 'menus - actions') -----
+ inspectSelection
+ 
+ 	self object inspect.!

Item was added:
+ ----- Method: ObjectExplorer>>mainTreeListMenu: (in category 'menus') -----
+ mainTreeListMenu: aMenu
+ 	<treeListMenu>
+ 
+ 	aMenu addStayUpItemSpecial.
+ 
+ 	aMenu addList: #(
+ 		('inspect (i)'						inspectSelection)
+ 		('explore (I)'						exploreSelection)
+ 		-
+ 		('method refs to this inst var'		referencesToSelection)
+ 		('methods storing into this inst var'	defsOfSelection)
+ 		('objects pointing to this value'		objectReferencesToSelection)
+ 		('chase pointers'					chasePointersForSelection)
+ 		('explore pointers'				explorePointersForSelection)
+ 		-
+ 		('browse full (b)'					browseFull)
+ 		('browse class'						browseClass)
+ 		('browse hierarchy (h)'					classHierarchy)
+ 		('browse protocol (p)'				browseFullProtocol)
+ 		-
+ 		('references... (r)'					browseVariableReferences)
+ 		('assignments... (a)'					browseVariableAssignments)
+ 		('class refs (N)'						browseClassRefs)
+ 		-
+ 		('copy name (c)'					copyName)		
+ 		('basic inspect'						inspectBasic)).
+ 
+ 	Smalltalk isMorphic ifTrue: [
+ 		aMenu addList: #(
+ 			-
+ 			('viewer for this value (v)'		viewerForValue))].
+ 
+ 	aMenu addList: #(
+ 		-
+ 		('monitor changes'		monitorSelection)).
+ 				
+ 	monitorList isEmptyOrNil ifFalse: [
+ 		aMenu addList: #(
+ 			('stop monitoring all'		stopMonitoring))].
+ 				
+ 	^ aMenu!

Item was added:
+ ----- Method: ObjectExplorer>>monitorSelection (in category 'menus - actions') -----
+ monitorSelection
+ 
+ 	self monitor: self currentSelection.!

Item was added:
+ ----- Method: ObjectExplorer>>objectReferencesToSelection (in category 'menus - actions') -----
+ objectReferencesToSelection
+ 	"Open a list inspector on all the objects that point to the value of the selected instance variable, if any.  "
+ 
+ 	self object ifNil: [^ self changed: #flash].
+ 
+ 	self systemNavigation
+ 		browseAllObjectReferencesTo: self object
+ 		except: {self currentSelection. self currentParent. self parentObject}
+ 		ifNone: [:obj | self changed: #flash].!

Item was added:
+ ----- Method: ObjectExplorer>>referencesToSelection (in category 'menus - actions') -----
+ referencesToSelection
+ 	"Open a browser on all references to the selected instance variable, if that's what currently selected."
+ 	
+ 	self selectedParentClass ifNil: [^ self changed: #flash].
+ 	self selectedParentClass isVariable ifTrue: [^ self changed: #flash].
+ 	self selectedInstVarName ifNil: [^ self changed: #flash].
+ 
+ 	self systemNavigation browseAllAccessesTo: self selectedInstVarName from: self selectedParentClass.!

Item was added:
+ ----- Method: ObjectExplorer>>selectedInstVarName (in category 'accessing - other') -----
+ selectedInstVarName
+ 
+ 	self parentObject ifNil: [^ nil].
+ 	(self parentObject class allInstVarNames includes: self currentSelection key)
+ 		ifTrue: [^ self currentSelection key asSymbol].
+ 	^ nil!

Item was added:
+ ----- Method: ObjectExplorer>>selectedParentClass (in category 'accessing - other') -----
+ selectedParentClass
+ 
+ 	^ self parentObject ifNotNil: [:o | o class]!

Item was removed:
- ----- Method: ObjectExplorer>>selector (in category 'accessing - other') -----
- selector
- 
- 	self isThisEverCalled.
- 	self flag: #deprecated. "mt: Who uses this? And why?"
- 	self parentObject ifNil: [^ nil].
- 	(self parentObject class allInstVarNames includes: self currentSelection key)
- 		ifTrue: [^ self currentSelection key asSymbol].
- 	^ nil!

Item was removed:
- ----- Method: ObjectExplorer>>updateInspectorForSelection (in category 'accessing - other') -----
- updateInspectorForSelection 
- 	"Reuse the inspector for some callbacks."
- 	
- 	self inspector inspect: (self parentObject ifNil: [self object]).
- 
- 	self parentObject
- 		ifNil: [self inspector toggleIndex: 1. "self"]
- 		ifNotNil: [
- 			self inspector toggleIndex: (self inspector fieldList indexOf: self currentSelection key)].
- 		
- 	self inspector selection == self object
- 		ifTrue: [
- 			^ true]
- 		ifFalse: [
- 			self inform: 'Object has changed. Please refresh\before invoking the context menu.' withCRs.
- 			^ false].!

Item was added:
+ ----- Method: ObjectExplorer>>viewerForValue (in category 'menus - actions') -----
+ viewerForValue
+ 
+ 	self object beViewed.!



More information about the Squeak-dev mailing list