[Pkg] The Trunk: Tools-pre.884.mcz

commits at source.squeak.org commits at source.squeak.org
Thu Sep 5 08:26:26 UTC 2019


Patrick Rein uploaded a new version of Tools to project The Trunk:
http://source.squeak.org/trunk/Tools-pre.884.mcz

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

Name: Tools-pre.884
Author: pre
Time: 5 September 2019, 10:26:18.328476 am
UUID: 24fb9919-2314-e04e-bbe9-56ac6134b493
Ancestors: Tools-pre.883

Fixes some calls to now deprecated methods in ChangeSorter and FileList (previously missed as they were self class sends).

=============== Diff against Tools-pre.883 ===============

Item was changed:
  ----- Method: ChangeSorter>>fileIntoNewChangeSet (in category 'changeSet menu') -----
  fileIntoNewChangeSet
  	"Obtain a file designation from the user, and file its contents into a  
  	new change set whose name is a function of the filename. Show the  
  	new set and leave the current changeSet unaltered."
  	self okToChange
  		ifFalse: [^ self].
  	ChangeSet promptForDefaultChangeSetDirectoryIfNecessary.
  	
  	(FileChooserDialog openOn: ChangeSet defaultChangeSetDirectory) ifNotNil: 
  		[:fileName | 	
  		FileStream oldFileNamed: fileName do: 
  			[:stream | | localName |
  			localName := FileDirectory localNameFor: fileName.
+ 			(ChangeSet newChangesFromStream: stream named: localName)
- 			(self class newChangesFromStream: stream named: localName)
  				ifNotNil: [:aNewChangeSet | self showChangeSet: aNewChangeSet]]].!

Item was changed:
  ----- Method: ChangeSorter>>fileOutClass (in category 'class list') -----
  fileOutClass
  	"this is a hack!!!! makes a new change set, called the class name, adds author initials to try to make a unique change set name, files it out and removes it. kfr 16 june 2000" 
  	| aSet |
  	"File out the selected class set."
+      aSet := ChangeSet newChangeSet: (self withoutItemAnnotation: currentClassName).
-      aSet := self class newChangeSet: (self withoutItemAnnotation: currentClassName).
  	aSet absorbClass: self selectedClassOrMetaClass name from: myChangeSet.
  	aSet fileOut.
+ 	ChangeSet removeChangeSet: aSet.
- 	self class removeChangeSet: aSet.
  	parent modelWakeUp.	"notice object conversion methods created"
  
  !

Item was changed:
  ----- Method: ChangeSorter>>newSet (in category 'changeSet menu') -----
  newSet
  	"Create a new changeSet and show it., making it the current one.  Reject name if already in use."
  
  	| aSet |
  	self okToChange ifFalse: [^ self].
+ 	aSet := ChangeSet newChangeSet.
- 	aSet := self class newChangeSet.
  	aSet ifNotNil:[
  		self update.
  		self showChangeSet: aSet.
  		self changed: #relabel]!

Item was changed:
  ----- Method: ChangeSorter>>promoteToTopChangeSet (in category 'changeSet menu') -----
  promoteToTopChangeSet
  	"Move the selected change-set to the top of the list"
  
+ 	ChangeSet promoteToTop: myChangeSet.
- 	self class promoteToTop: myChangeSet.
  	(parent ifNil: [self]) modelWakeUp!

Item was changed:
  ----- Method: ChangeSorter>>setRecentUpdatesMarker (in category 'changeSet menu') -----
  setRecentUpdatesMarker
  	"Allow the user to change the recent-updates marker"
  
  	| result |
  	result := UIManager default request: 
  ('Enter the lowest change-set number
  that you wish to consider "recent"?
  (note: highest change-set number
+ in this image at this time is ', ChangeSet highestNumberedChangeSet asString, ')') initialAnswer: ChangesOrganizer recentUpdateMarker recentUpdateMarker asString.
- in this image at this time is ', ChangeSet highestNumberedChangeSet asString, ')') initialAnswer: self class recentUpdateMarker asString.
  	(result notNil and: [result startsWithDigit]) ifTrue:
+ 		[ChangesOrganizer recentUpdateMarker: result asInteger.
- 		[self class recentUpdateMarker: result asInteger.
  		Smalltalk isMorphic ifTrue: [SystemWindow wakeUpTopWindowUponStartup]]!

Item was changed:
  ----- Method: FileList class>>removeObsolete (in category 'class initialization') -----
  removeObsolete
  	"FileList removeObsolete"
+ 	FileServices removeObsolete
+ 	!
- 	self registeredFileReaderClasses copy 
- 		do:[:cls| cls isObsolete ifTrue:[self unregisterFileReader: cls]]!

Item was changed:
  ----- Method: FileList>>itemsForDirectory: (in category 'file list menu') -----
  itemsForDirectory: dir 
  	| services |
  	services := OrderedCollection new.
  	dir ifNotNil: [
  		services
+ 			addAll: (FileServices itemsForDirectory: dir).
- 			addAll: (self class itemsForDirectory: dir).
  		services last useLineAfter: true. ].
  	services add: self serviceAddNewFile.
  	services add: self serviceAddNewDirectory.
  	^ services!

Item was changed:
  ----- Method: FileList>>itemsForFile: (in category 'file list menu') -----
  itemsForFile: fullName
  	"Answer a list of services appropriate for a file of the given full name"
+ 	^ (FileServices itemsForFile: fullName) , (self myServicesForFile: fullName suffix: (FileServices suffixOf: fullName))!
- 	| suffix |
- 	suffix := self class suffixOf: fullName.
- 	^ (self class itemsForFile: fullName) , (self myServicesForFile: fullName suffix: suffix)!

Item was changed:
  ----- Method: FileList>>registeredFileReaderClasses (in category 'private') -----
  registeredFileReaderClasses
  	"return the list of classes that provide file reader services"
  
+ 	^ FileServices registeredFileReaderClasses!
- 	^ self class registeredFileReaderClasses!

Item was changed:
  ----- Method: FileList>>servicesFromSelectorSpecs: (in category 'own services') -----
  servicesFromSelectorSpecs: symbolArray
  	"Answer an array of services represented by the incoming symbols, eliminating any that do not have a currently-registered service.  Pass the symbol #- along unchanged to serve as a separator between services"
  
  	"FileList new servicesFromSelectorSpecs: #(fileIn: fileIntoNewChangeSet: browseChangesFile:)"
  
  	| services col | 
  	col := OrderedCollection new.
+ 	services := FileServices allRegisteredServices, (self myServicesForFile: #dummy suffix: '*').
- 	services := self class allRegisteredServices, (self myServicesForFile: #dummy suffix: '*').
  	symbolArray do: 
  		[:sel | | res | 
  			sel == #-
  				ifTrue:
  					[col add: sel]
  				ifFalse:
  					[res := services
  							detect: [:each | each selector = sel] ifNone: [nil].
  					res notNil
  							ifTrue: [col add: res]]].
  	^ col!

Item was changed:
  ----- Method: FileList>>suffixOfSelectedFile (in category 'file list menu') -----
  suffixOfSelectedFile
  	"Answer the file extension of the receiver's selected file"
+ 	^ FileServices suffixOf: self fullName.!
- 	^ self class suffixOf: self fullName.!



More information about the Packages mailing list