[squeak-dev] The Trunk: Monticello-eem.783.mcz

commits at source.squeak.org commits at source.squeak.org
Thu Jan 12 18:27:45 UTC 2023


Eliot Miranda uploaded a new version of Monticello to project The Trunk:
http://source.squeak.org/trunk/Monticello-eem.783.mcz

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

Name: Monticello-eem.783
Author: eem
Time: 12 January 2023, 10:27:42.868759 am
UUID: ca62da1a-e6bb-42ac-9f59-9b7d3541ffc6
Ancestors: Monticello-mt.782

Do a better job at filing ou definitions from an MCCodeTool, especially an MCPatchBrowser.  Add fileOutDefinition that files out the incoming versions, not the versions in this system.  Clarify the menus.

=============== Diff against Monticello-mt.782 ===============

Item was added:
+ ----- Method: MCCodeTool>>fileOutDefinition (in category 'menus') -----
+ fileOutDefinition
+ 	"Put a description of the selected definition(s) on a file.
+ 	 Output the version(s) corresponding to the incoming definition(s), not the versions in this system."
+ 
+ 	| index fileName itemsToFileOut |
+ 	itemsToFileOut := (index := self selection) ~= 0
+ 							ifTrue: [{items at: index}]
+ 							ifFalse: [items].
+ 	items isEmpty ifTrue:
+ 		[^self].
+ 	fileName := UIManager default
+ 					saveFilenameRequest: 'File out on which file?'
+ 					initialAnswer: (index ~= 0
+ 										ifTrue: [itemsToFileOut first summary]
+ 										ifFalse: ['definitions']).
+ 	fileName isEmptyOrNil ifTrue: [^self].
+ 	Cursor write showWhile:
+ 		[| definitionStream |
+ 		definitionStream := WriteStream on: (String new: 1000).
+ 		definitionStream header; timeStamp.
+ 		itemsToFileOut do:
+ 			[:patchOp| 
+ 			patchOp definition fileOutOn: definitionStream].
+ 		FileStream writeSourceCodeFrom: definitionStream baseName: fileName isSt: true useHtml: false]!

Item was changed:
  ----- Method: MCCodeTool>>fileOutMessage (in category 'menus') -----
  fileOutMessage
+ 	"Put a description of the selected definition(s) on a file.
+ 	 Output the version(s) corresponding to this system, not the incoming definition."
- 	"Put a description of the selected message on a file"
  
+ 	| index fileName itemsToFileOut |
+ 	itemsToFileOut := (index := self selection) ~= 0
+ 							ifTrue: [{items at: index}]
+ 							ifFalse: [items].
- 	| fileName |
- 	self selectedMessageName ifNotNil:
- 		[Cursor write showWhile:
- 			[self selectedClassOrMetaClass fileOutMethod: self selectedMessageName].
- 		 ^self].
  	items isEmpty ifTrue:
  		[^self].
+ 	fileName := UIManager default
+ 					saveFilenameRequest: 'File out on which file?'
+ 					initialAnswer: (index ~= 0
+ 										ifTrue: [itemsToFileOut first summary]
+ 										ifFalse: ['definitions']).
- 	fileName := UIManager default saveFilenameRequest: 'File out on which file?' initialAnswer: 'methods'.
  	fileName isEmptyOrNil ifTrue: [^self].
  	Cursor write showWhile:
  		[| definitionStream removalInitStream |
  		definitionStream := WriteStream on: (String new: 1000).
  		removalInitStream := WriteStream on: (String new: 100).
  		definitionStream header; timeStamp.
+ 		itemsToFileOut do:
- 		items do:
  			[:patchOp| | def |
  			def := patchOp definition.
  			def isMethodDefinition ifTrue:
  				[(def actualClass notNil
  				  and: [def actualClass includesSelector: def selector])
  					ifTrue:
  						[def actualClass
  							printMethodChunk: def selector
  							withPreamble: true
  							on: definitionStream
  							moveSource: false
  							toFile: nil.
  						(def selector == #initialize and: [def classIsMeta]) ifTrue:
  							[removalInitStream nextChunkPut: def className, ' initialize'; cr]]
  					ifFalse:
  						[removalInitStream nextChunkPut: def className, (def classIsMeta ifTrue: [' class'] ifFalse: ['']), ' removeSelector: ', def selector printString; cr]].
  			def isClassDefinition ifTrue:
  				[def actualClass
  					ifNotNil:
  						[definitionStream nextChunkPut: def actualClass definition.
  						 def comment ifNotNil:
  							[def actualClass organization
  								putCommentOnFile: definitionStream
  								numbered: 1
  								moveSource: false
  								forClass: def actualClass]]
  					ifNil:
  						[removalInitStream nextChunkPut: def className, ' removeFromSystem'; cr]]].
  		definitionStream nextPutAll: removalInitStream contents.
  		FileStream writeSourceCodeFrom: definitionStream baseName: fileName isSt: true useHtml: false]!

Item was changed:
  ----- Method: MCCodeTool>>methodListMenu: (in category 'menus') -----
  methodListMenu: aMenu
  	"Build the menu for the selected method, if any."
  	
  	self selectedMessageName
  	ifNil: [items notEmpty ifTrue:
  		[aMenu addList:#(
+ 			('fileOut ours (o)'						fileOutMessage)
+ 			('fileOut theirs'							fileOutDefinition))]]
- 			('fileOut (o)'								fileOutMessage))]]
  	ifNotNil: [
  	aMenu addList:#(
  			('browse full (b)' 						browseMethodFull)
  			('browse hierarchy (h)'					browseClassHierarchy)
  			('browse protocol (p)'					browseFullProtocol)
  			-
+ 			('fileOut ours (o)'						fileOutMessage)
+ 			('fileOut theirs'							fileOutDefinition)
- 			('fileOut (o)'								fileOutMessage)
  			('printOut'								printOutMessage)
  			('copy selector (c)'						copySelector)
  			('copy reference (C)'					copyReference)).
  		aMenu addList: #(
  			-
  			('browse senders (n)'						browseSendersOfMessages)
  			('browse implementors (m)'					browseMessages)
  			('inheritance (i)'						methodHierarchy)
  			('versions (v)'							browseVersions)
  		('change sets with this method'			findMethodInChangeSets)
  "		('x revert to previous version'				revertToPreviousVersion)"
  		('remove from current change set'		removeFromCurrentChanges)
  "		('x revert & remove from changes'		revertAndForget)"
  		('add to current change set'				adoptMessageInCurrentChangeset)
  "		('x copy up or copy down...'				copyUpOrCopyDown)"
  "		('x remove method (x)'					removeMessage)"
  		"-"
  		).
  	].
  "	aMenu addList: #(
  			('x inst var refs...'						browseInstVarRefs)
  			('x inst var defs...'						browseInstVarDefs)
  			('x class var refs...'						browseClassVarRefs)
  			('x class variables'						browseClassVariables)
  			('x class refs (N)'							browseClassRefs)
  	).
  "
  	^ aMenu
  !

Item was added:
+ ----- Method: MCDefinition>>fileOutOn: (in category 'printing') -----
+ fileOutOn: aStream
+ 	"File out the receiver's definition in chunk format.
+ 	 This is a workable default implementation that serves for some subclasses."
+ 	aStream nextChunkPut: self source!

Item was added:
+ ----- Method: MCMethodDefinition>>fileOutOn: (in category 'printing') -----
+ fileOutOn: aStream
+ 	"File out the receiver's definition in chunk format.
+ 	 Override to add the methodsFor: chunk."
+ 	aStream nextPut: $!!; nextChunkPut: self methodsForString.
+ 	super fileOutOn: aStream!

Item was added:
+ ----- Method: MCMethodDefinition>>methodsForString (in category 'printing') -----
+ methodsForString
+ 	"Answer the string that defines the class, category and timestamp, for file out."
+ 	^String streamContents:
+ 		[:s|
+ 		s nextPutAll: className.
+ 		classIsMeta ifTrue:
+ 			[s nextPutAll: ' class'].
+ 		s nextPutAll: ' methodsFor: '; store: category; nextPutAll: ' stamp: '; print: timeStamp]!



More information about the Squeak-dev mailing list