[squeak-dev] The Trunk: Monticello-mt.757.mcz

commits at source.squeak.org commits at source.squeak.org
Tue Nov 30 16:16:11 UTC 2021


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

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

Name: Monticello-mt.757
Author: mt
Time: 30 November 2021, 5:16:09.97009 pm
UUID: 256d2e17-90f4-8b43-bce0-2592e8c7235c
Ancestors: Monticello-ct.738, Monticello-ct.739, Monticello-ct.754, Monticello-ct.755, Monticello-ct.756, Monticello-ul.753

Merge. Merge. Merge.

Monticello-ct.738:
	Supports author name in and removes redundant spaces from the annotation string of a method definition.

Monticello-ct.739:
	Tweaks 'add to current change set' command to create a changeset from all (non-ignored) items in an operations browser.

Also hides the 'browse full' command from the menu if not any item is selected since it does not have any function in this case.

Monticello-ct.754:
	Fixes a debugger when pressing <cmd>v in a save version dialog while no method is selected. All other hotkeys there are okay, I have checked this.

Monticello-ct.755:
	On MCRepositoryGroup, implements further selectors for compatibility with MCRepository (#cacheAllFileNamesDuring: and #isValid).

This is required for  https://github.com/hpi-swa/Squot/pull/328.

(Just asking, would it be possible to backport this to 5.3 and 5.2? This would testing much easier on the Squot side.)

Monticello-ct.756:
	Honor the preference #checkForNewerVersionsBeforeSave again, which was previously unused.

=============== Diff against Monticello-ul.753 ===============

Item was changed:
  ----- Method: MCCodeTool>>browseVersions (in category 'menus') -----
  browseVersions
  	"Create and schedule a message set browser on all versions of the currently selected message selector."
  	(ToolSet
  		browseVersionsOf: self selectedClassOrMetaClass
+ 		selector: (self selectedMessageName ifNil: [^ self])) ifNil: [self changed: #flash]!
- 		selector: self selectedMessageName) ifNil: [self changed: #flash]!

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:#(
- 			('browse full (b)' 						browseMethodFull)
  			('fileOut (o)'								fileOutMessage))]]
  	ifNotNil: [
  	aMenu addList:#(
  			('browse full (b)' 						browseMethodFull)
  			('browse hierarchy (h)'					browseClassHierarchy)
  			('browse protocol (p)'					browseFullProtocol)
  			-
  			('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 changed:
  ----- Method: MCMethodDefinition>>printAnnotations:on: (in category 'annotations') -----
  printAnnotations: requests on: aStream
  	"Add a string for an annotation pane, trying to fulfill the annotation requests.
  	These might include anything that
  		Preferences defaultAnnotationRequests 
  	might return. Which includes anything in
  		Preferences annotationInfo
  	To edit these, use:"
  	"Preferences editAnnotations"
  
+ 	| annotationSeparator annotations |
+ 	annotationSeparator := ' · '. "Same as in CodeHolder"
+ 	annotations := requests
+ 		collect: [:request | request
+ 			caseOf: {
+ 				[#timeStamp] -> [self timeStamp].
+ 				[#author] -> [
+ 					| initials |
+ 					initials := self timeStamp ifNotNil: [:timeStamp |
+ 						timeStamp findTokens ifNotEmpty: [:tokens | tokens first]].
+ 					SystemNavigation authorsInverted
+ 						at: initials
+ 						ifPresent: [:fullNames | fullNames anyOne]
+ 						ifAbsent: ['unknown author' translated]].
+ 				[#messageCategory] -> [self category].
+ 				[#requirements] -> [self requirements joinSeparatedBy: Character space] }
+ 			otherwise: []]
+ 		thenSelect: [:annotation | annotation isEmptyOrNil not].
+ 	
+ 	annotations 
+ 		do: [:annotation | aStream nextPutAll: annotation]
+ 		separatedBy: [aStream nextPutAll: annotationSeparator].!
- 	requests do: [ :aRequest |
- 		aRequest == #timeStamp ifTrue: [ aStream nextPutAll: self timeStamp ].
- 		aRequest == #messageCategory ifTrue: [ aStream nextPutAll: self category ].
- 		aRequest == #requirements ifTrue: [
- 			self requirements do: [ :req |
- 				aStream nextPutAll: req ] separatedBy: [ aStream space ]].
- 	] separatedBy: [ aStream space ].!

Item was added:
+ ----- Method: MCOperationsBrowser>>adoptMessageInCurrentChangeset (in category 'menus') -----
+ adoptMessageInCurrentChangeset
+ 
+ 	selection ifNotNil: [^ super adoptMessageInCurrentChangeset].
+ 	
+ 	items select: [:each | each definition isMethodDefinition] thenDo: [:item |
+ 		self forItem: item setClassAndSelectorIn: [:class :selector |
+ 			((item isAddition or: [item isModification]) and: [class includesSelector: selector])
+ 				ifTrue: [ChangeSet current adoptSelector: selector forClass: class].
+ 			item isRemoval
+ 				ifTrue: [ChangeSet current removeSelector: selector class: class priorMethod: nil lastMethodInfo: nil]]].
+ 	self changed: #annotations.!

Item was added:
+ ----- Method: MCOperationsBrowser>>forItem:setClassAndSelectorIn: (in category 'private') -----
+ forItem: item setClassAndSelectorIn: classSelectorBlock
+ 
+ 	item definition isMethodDefinition ifFalse: [self halt].
+ 	^ classSelectorBlock
+ 		value: item definition actualClass
+ 		value: item definition selector!

Item was changed:
  ----- Method: MCOperationsBrowser>>methodListMenu: (in category 'menus') -----
  methodListMenu: aMenu
+ 	selection
+ 		ifNil: [items ifNotEmpty: [
+ 			aMenu addList: #(
+ 				('add all to current change set'			adoptMessageInCurrentChangeset))]]
+ 		ifNotNil: [aMenu addList: #(
- 	selection ifNotNil:
- 		[aMenu addList: #(
  			('install'	 installSelection)
  			('revert (x)'	 revertSelection)
  			('browse origin' browseSelectionOrigin) 
  			-)].
  	self unchangedMethods ifNotEmpty:
  		[aMenu addList: #(
  			('revert unchanged methods...'	revertUnchangedMethods) 
  			('filter out unchanged methods...'	filterOutUnchangedMethods) 
  			-)].
  	super methodListMenu: aMenu.
  	^ aMenu!

Item was added:
+ ----- Method: MCRepositoryGroup>>cacheAllFileNamesDuring: (in category 'private') -----
+ cacheAllFileNamesDuring: aBlock
+ 	^ (repositories
+ 		inject: aBlock
+ 		into: [ :innerBlock :repository |
+ 			[ repository cacheAllFileNamesDuring: innerBlock ]
+ 		]) value!

Item was added:
+ ----- Method: MCRepositoryGroup>>isValid (in category 'testing') -----
+ isValid
+ 
+ 	^ repositories allSatisfy: #isValid!

Item was added:
+ ----- Method: MCSaveVersionDialog>>adoptMessageInCurrentChangeset (in category 'menus') -----
+ adoptMessageInCurrentChangeset
+ 
+ 	selection ifNotNil: [^ super adoptMessageInCurrentChangeset].
+ 	
+ 	(items copyWithoutAll: ignore) select: [:each | each definition isMethodDefinition] thenDo: [:item |
+ 		self forItem: item setClassAndSelectorIn: [:class :selector |
+ 			((item isAddition or: [item isModification]) and: [class includesSelector: selector])
+ 				ifTrue: [ChangeSet current adoptSelector: selector forClass: class].
+ 			item isRemoval
+ 				ifTrue: [ChangeSet current removeSelector: selector class: class priorMethod: nil lastMethodInfo: nil]]].
+ 	self changed: #annotations.!

Item was changed:
  ----- Method: MCWorkingCopyBrowser>>saveVersion (in category 'actions') -----
  saveVersion
  	| repo |
  	self canSave ifFalse: [^self].
+ 	self class checkForNewerVersionsBeforeSave ==> [self checkForNewerVersions] ifFalse: [^self].
- 	self checkForNewerVersions ifFalse: [^self].
  	repo := self repository.
  	(repo == MCRepository trunk and: [SystemVersion current isFeatureFreeze])
  		ifTrue: [self inform: 'FEATURE FREEZE. A new release is being prepared.\Please do only do bugfixes, but no new features.' translated withCRs].
  	(repo == MCRepository trunk and: [SystemVersion current isCodeFreeze])
  		ifTrue: [self inform: 'CODE FREEZE. The new release is almost ready.\Please do only do URGENT fixes, if any.' translated withCRs].
  				
  	(self withRepository: repo do: [workingCopy newVersion]) ifNotNil:
  		[:v |
  		(MCVersionInspector new version: v) show.
  		Cursor wait showWhile: [repo storeVersion: v].
  		MCCacheRepository default cacheAllFileNamesDuring: 
  			[repo cacheAllFileNamesDuring: 
  				[v allAvailableDependenciesDo:
  					[:dep |
  					(repo includesVersionNamed: dep info name)
  						ifFalse: [repo storeVersion: dep]]]]]!



More information about the Squeak-dev mailing list