[Pkg] The Trunk: Tools-mt.613.mcz

commits at source.squeak.org commits at source.squeak.org
Fri May 1 12:32:42 UTC 2015


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

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

Name: Tools-mt.613
Author: mt
Time: 1 May 2015, 2:32:16.632 pm
UUID: e0697d0b-8eb9-5647-81bd-922a24eb997f
Ancestors: Tools-mt.612

Deprecations updated.

=============== Diff against Tools-mt.612 ===============

Item was changed:
  ----- Method: Browser>>arrowKey:from: (in category 'multi-window support') -----
  arrowKey: aChar from: view
  	"Intercept Apple-Digit to select panes"
  	| index |
  	(aChar isDigit
+ 	 and: [self multiWindowState notNil]) ifTrue:
- 	 and: [multiWindowState notNil]) ifTrue:
  	 	[index := aChar asciiValue - $0 asciiValue.
  		index = 0 ifTrue: [index := 10].
+ 		^index <= self multiWindowState models size
+ 			ifTrue: [self multiWindowState selectWindowIndex: index]
- 		^index <= multiWindowState models size
- 			ifTrue: [multiWindowState selectWindowIndex: index]
  			ifFalse: [self changed: #flash]].
  	^super arrowKey: aChar from: view
  !

Item was removed:
- ----- Method: Browser>>classComment:notifying: (in category 'class comment pane') -----
- classComment: aText notifying: aPluggableTextMorph 
- 	"The user has just entered aText.
- 	It may be all red (a side-effect of replacing the default comment), so remove the color if it is."
- 
- 	| theClass cleanedText redRange |
- 	theClass := self selectedClassOrMetaClass.
- 	theClass
- 		ifNotNil: [cleanedText := aText asText.
- 			redRange := cleanedText rangeOf: TextColor red startingAt: 1.
- 			redRange size = cleanedText size
- 				ifTrue: [cleanedText
- 						removeAttribute: TextColor red
- 						from: 1
- 						to: redRange last ].
- 			theClass comment: aText stamp: Utilities changeStamp].
- 	self changed: #classCommentText.
- 	^ true!

Item was changed:
  ----- Method: Browser>>classHierarchy (in category 'multi-window support') -----
  classHierarchy
  	| behavior newBrowser |
  	(behavior := self selectedClassOrMetaClass) isNil ifTrue:
  		[^self].
  
  	(self isPackage "PackageBrowser pains can't support a hierarchy browser; not sure why."
+ 	 or: [self multiWindowState isNil]) ifTrue:
- 	 or: [multiWindowState isNil]) ifTrue:
  		[^super classHierarchy].
  
  	(newBrowser := HierarchyBrowser new initHierarchyForClass: behavior)
  		selectMessageCategoryNamed: self selectedMessageCategoryName;
  		selectMessageNamed: self selectedMessageName;
  		editSelection: editSelection.
  
+ 	self multiWindowState addWindow: newBrowser
- 	multiWindowState addWindow: newBrowser
  !

Item was removed:
- ----- Method: Browser>>defineMessage:notifying: (in category 'message functions') -----
- defineMessage: aString notifying: aController
- 	self deprecated: 'Use Browser >> #defineMessageFrom:notifying:. This returns a Symbol or nil, not a Boolean.'.
- 	^ (self defineMessageFrom: aString notifying: aController) notNil.!

Item was changed:
  ----- Method: Browser>>findClass (in category 'system category functions') -----
  findClass
  	"Search for a class by name."
  
  	| foundClass |
+ 	(self multiWindowState notNil
- 	(multiWindowState notNil
  	 or: [self okToChange]) ifFalse:
  		[^self classNotFound].
  	foundClass := UIManager default chooseClassOrTrait.
  	foundClass ifNil: [^self classNotFound].
  	(self selectedClass notNil
+ 	 and: [self multiWindowState notNil
- 	 and: [multiWindowState notNil
  	 "Can only support multi-window if original window has all the right panes."
+ 	 and: [self multiWindowState prototype isHierarchy not]]) ifTrue:
- 	 and: [multiWindowState prototype isHierarchy not]]) ifTrue:
  		[(self classList includes: foundClass name)
+ 			ifTrue: [self multiWindowState copyWindow]
+ 			ifFalse: [self multiWindowState addNewWindow]].
- 			ifTrue: [multiWindowState copyWindow]
- 			ifFalse: [multiWindowState addNewWindow]].
   	self selectCategoryForClass: foundClass.
  	self selectClass: foundClass!

Item was changed:
  ----- Method: Browser>>labelString (in category 'initialize-release') -----
  labelString
  	| label |
  	label := self selectedClassName
  				ifNil: [ self defaultBrowserTitle ]
  				ifNotNil: [ self defaultBrowserTitle, ': ', self selectedClassName asString ].
+ 	(self multiWindowState notNil
+ 	 and: [self multiWindowState models size > 1]) ifTrue:
+ 		[label := (self multiWindowState models indexOf: self) printString, '. ', label].
- 	(multiWindowState notNil
- 	 and: [multiWindowState models size > 1]) ifTrue:
- 		[label := (multiWindowState models indexOf: self) printString, '. ', label].
  	^label!

Item was removed:
- ----- Method: Browser>>messageListSingleton (in category 'message list') -----
- messageListSingleton
- 
- 	| name |
- 	name := self selectedMessageName.
- 	^ name ifNil: [Array new]
- 		ifNotNil: [Array with: name]!

Item was changed:
  ----- Method: Browser>>okToClose (in category 'multi-window support') -----
  okToClose
  	^super okToClose
+ 	  and: [self multiWindowState isNil or: [self multiWindowState okToClose]]!
- 	  and: [multiWindowState isNil or: [multiWindowState okToClose]]!

Item was removed:
- ----- Method: Browser>>optionalAnnotationHeight (in category 'initialize-release') -----
- optionalAnnotationHeight
- 
- 	^ 10!

Item was removed:
- ----- Method: Browser>>optionalButtonHeight (in category 'initialize-release') -----
- optionalButtonHeight
- 
- 	^ 10!

Item was removed:
- ----- Method: Browser>>potentialClassNames (in category 'system category functions') -----
- potentialClassNames
- 	"Answer the names of all the classes that could be viewed in this browser.  This hook is provided so that HierarchyBrowsers can indicate their restricted subset.  For generic Browsers, the entire list of classes known to Smalltalk is provided, though of course that really only is accurate in the case of full system browsers."
- 
- 	^ Smalltalk classNames!

Item was removed:
- ----- Method: CodeHolder>>abbreviatedWordingFor: (in category 'commands') -----
- abbreviatedWordingFor: aButtonSelector
- 	"Answer the abbreviated form of wording, from a static table.  Answer nil if there is no entry -- in which case the long form will be used on the corresponding browser button."
- 
- 	#(
- 	(browseMethodFull				'browse')
- 	(browseSendersOfMessages	   	'senders')
- 	(browseMessages				'impl')
- 	(browseVersions					'vers')
- 	(methodHierarchy				'inher')
- 	(classHierarchy					'hier')
- 	(browseVariableReferences				'refs')
- 	(offerMenu						'menu')) do:
- 
- 		[:pair | pair first == aButtonSelector ifTrue: [^ pair second]].
- 	^ nil!

Item was changed:
  ----- Method: CodeHolder>>buildCodeProvenanceButtonWith: (in category 'toolbuilder') -----
  buildCodeProvenanceButtonWith: builder
  	| buttonSpec |
  	buttonSpec := builder pluggableActionButtonSpec new.
+ 	buttonSpec
+ 		model: self;
+ 		label: #codePaneProvenanceString;
+ 		changeLabelWhen: #contents;
+ 		style: #menuButton;
+ 		action: #offerWhatToShowMenu;
+ 		help: 'Governs what view is shown in the code pane.  Click here to change the view';
+ 		margin: (5 at 0 corner: 0 at 0).
- 	buttonSpec model: self.
- 	buttonSpec label: #codePaneProvenanceString.
- 	buttonSpec changeLabelWhen: #contents.
- 	buttonSpec style: #menuButton.
- 	buttonSpec action: #offerWhatToShowMenu.
- 	buttonSpec help: 'Governs what view is shown in the code pane.  Click here to change the view'.
  	^buttonSpec!

Item was changed:
  ----- Method: CodeHolder>>restoreTextualCodingPane (in category 'diffs') -----
  restoreTextualCodingPane
  	"If the receiver is showing tiles, restore the textual coding pane"
  
+ 	contentsSymbol == #tiles ifTrue:
- 	self showingTiles ifTrue:
  		[contentsSymbol := #source.
  		self installTextualCodingPane]!

Item was removed:
- ----- Method: CodeHolder>>showingDiffsString (in category 'diffs') -----
- showingDiffsString
- 	"Answer a string representing whether I'm showing diffs.  Not sent any more but retained so that prexisting buttons that sent this will not raise errors."
- 
- 	^ (self showingRegularDiffs
- 		ifTrue:
- 			['<yes>']
- 		ifFalse:
- 			['<no>']), 'showDiffs'!

Item was removed:
- ----- Method: CodeHolder>>showingTiles (in category 'diffs') -----
- showingTiles
- 	"Answer whether the receiver is currently showing tiles"
- 
- 	^ contentsSymbol == #tiles
- !

Item was removed:
- ----- Method: CodeHolder>>toggleDiff (in category 'diffs') -----
- toggleDiff
- 	"Retained for backward compatibility with existing buttons in existing images"
- 
- 	self toggleDiffing!

Item was removed:
- ----- Method: HierarchyBrowser>>potentialClassNames (in category 'initialization') -----
- potentialClassNames
- 	"Answer the names of all the classes that could be viewed in this browser"
- 	^ self classList collect:
- 		[:aName | aName copyWithout: $ ]!

Item was changed:
  ----- Method: PackagePaneBrowser>>labelString (in category 'initialize-release') -----
  labelString
  	^self package
  		ifNil: [super labelString]
  		ifNotNil:
  			[:pkg| | label |
  			label := self defaultBrowserTitle, ': ', pkg, (self selectedClass
  														ifNil: ['']
  														ifNotNil: [' ', self selectedClass printString]).
+ 			(self multiWindowState notNil
+ 			 and: [self multiWindowState models size > 1]) ifTrue:
+ 				[label := (self multiWindowState models indexOf: self) printString, '. ', label].
- 			(multiWindowState notNil
- 			 and: [multiWindowState models size > 1]) ifTrue:
- 				[label := (multiWindowState models indexOf: self) printString, '. ', label].
  			label]!



More information about the Packages mailing list