[squeak-dev] The Trunk: Monticello-ul.335.mcz

commits at source.squeak.org commits at source.squeak.org
Sat Dec 12 14:22:46 UTC 2009


Levente Uzonyi uploaded a new version of Monticello to project The Trunk:
http://source.squeak.org/trunk/Monticello-ul.335.mcz

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

Name: Monticello-ul.335
Author: ul
Time: 12 December 2009, 2:27:47 am
UUID: 91b9e16f-57c7-d449-8b7e-52a7b2f3c925
Ancestors: Monticello-ar.334

- replace sends of #ifNotNilDo: to #ifNotNil:, #ifNil:ifNotNilDo: to #ifNil:ifNotNil:, #ifNotNilDo:ifNil: to #ifNotNil:ifNil:

=============== Diff against Monticello-ar.334 ===============

Item was changed:
  ----- Method: MCWorkingCopyBrowser>>saveVersion (in category 'actions') -----
  saveVersion
  	| repo |
  	self canSave ifFalse: [^self].
  	repo := self repository.
+ 	workingCopy newVersion ifNotNil:
- 	workingCopy newVersion ifNotNilDo:
  		[: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]]]]]!

Item was changed:
  ----- Method: MCWorkingCopyBrowser>>addRepositoryToWorkingCopy (in category 'actions') -----
  addRepositoryToWorkingCopy
+ 	workingCopy ifNotNil:
- 	workingCopy ifNotNilDo:
  		[:wc |
  			workingCopy repositoryGroup addRepository: self repository.
  			self
  				changed: #workingCopySelection;
  				changed: #repositoryList;
  				changed: #repositorySelection.
  			self changedButtons]!

Item was changed:
  ----- Method: MCMcdReader>>loadPatch (in category 'as yet unclassified') -----
  loadPatch
  	| old new |
+ 	(self zip memberNamed: 'patch.bin') ifNotNil:
- 	(self zip memberNamed: 'patch.bin') ifNotNilDo:
  		[:m | [^ patch := (DataStream on: m contentStream) next ]
  			on: Error do: [:fallThrough ]].
  	definitions := OrderedCollection new.
  	(self zip membersMatching: 'old/*')
  		do: [:m | self extractDefinitionsFrom: m].
  	old := definitions asArray.
  	definitions := OrderedCollection new.
  	(self zip membersMatching: 'new/*')
  		do: [:m | self extractDefinitionsFrom: m].
  	new := definitions asArray.
  	^ patch := self buildPatchFrom: old to: new.
  	!

Item was changed:
  ----- Method: MCSnapshotBrowser>>methodListMenu: (in category 'menus') -----
  methodListMenu: aMenu 
  	super methodListMenu: aMenu.
  	self selectedMessageName
+ 		ifNotNil: [:msgName | aMenu addLine; add: 'load method' translated action: #loadMethodSelection].
- 		ifNotNilDo: [:msgName | aMenu addLine; add: 'load method' translated action: #loadMethodSelection].
  	^ aMenu!

Item was changed:
  ----- Method: MCMergingTest>>handleConflict: (in category 'emulating') -----
  handleConflict: aConflict	
  	|l r|
  	l := #removed.
  	r := #removed.
+ 	aConflict localDefinition ifNotNil: [:d | l := d token].
+ 	aConflict remoteDefinition ifNotNil: [:d | r := d token].	
- 	aConflict localDefinition ifNotNilDo: [:d | l := d token].
- 	aConflict remoteDefinition ifNotNilDo: [:d | r := d token].	
  	conflicts := conflicts copyWith: (Array with: r with: l).
  	(l = #removed or: [r = #removed])
  		ifTrue: [aConflict chooseRemote]
  		ifFalse:
  			[l > r
  				ifTrue: [aConflict chooseLocal]
  				ifFalse: [aConflict chooseRemote]]
  		!

Item was changed:
  ----- Method: MCMethodDefinition>>unload (in category 'installing') -----
  unload
  	| previousVersion |
  	self isOverrideMethod ifTrue: [previousVersion := self scanForPreviousVersion].
  	previousVersion
+ 		ifNil: [self actualClass ifNotNil: [:class | class removeSelector: selector]]
- 		ifNil: [self actualClass ifNotNilDo: [:class | class removeSelector: selector]]
  		ifNotNil: [previousVersion fileIn] !

Item was changed:
  ----- Method: MCMczInstallerTest>>assertDict:matchesInfo: (in category 'as yet unclassified') -----
  assertDict: dict matchesInfo: info
  	#(name id message date time author)
+ 		do: [:sel |  (info perform: sel) ifNotNil: [:i | dict at: sel ifPresent: [:d | self assert: i = d]]].
- 		do: [:sel |  (info perform: sel) ifNotNilDo: [:i | dict at: sel ifPresent: [:d | self assert: i = d]]].
  	info ancestors 
  			with: (dict at: #ancestors) 
  			do: [:i :d | self assertDict: d matchesInfo: i]!

Item was changed:
  ----- Method: MCThreeWayMerger>>addDefinition: (in category 'as yet unclassified') -----
  addDefinition: aDefinition
  	index
  		definitionLike: aDefinition
  		ifPresent: [:other |
  			(self removalForDefinition: aDefinition)
+ 				ifNotNil:
- 				ifNotNilDo:
  					[:op |
  					self addOperation: (MCModification of: other to: aDefinition).
  					self removeOperation: op.
  					^ self].
  			other = aDefinition
  				ifFalse: [self addConflictWithOperation: (MCModification of: other to: aDefinition)]
  				ifTrue: [self redundantAdds add: aDefinition]]
  		ifAbsent: [self addOperation: (MCAddition of: aDefinition)]!

Item was changed:
  ----- Method: MCStReader>>addDefinitionsFromDoit: (in category 'as yet unclassified') -----
  addDefinitionsFromDoit: aString
+ 	(MCDoItParser forDoit: aString) ifNotNil:
- 	(MCDoItParser forDoit: aString) ifNotNilDo:
  		[:parser |
  		parser addDefinitionsTo: definitions]!

Item was changed:
  ----- Method: MCRepositoryGroup>>versionWithInfo:ifNone: (in category 'as yet unclassified') -----
  versionWithInfo: aVersionInfo ifNone: aBlock
+ 	self repositoriesDo: [:ea | (ea versionWithInfo: aVersionInfo) ifNotNil: [:v | ^ v]].
- 	self repositoriesDo: [:ea | (ea versionWithInfo: aVersionInfo) ifNotNilDo: [:v | ^ v]].
  	^aBlock value!

Item was changed:
  ----- Method: MCTraitDefinition>>load (in category 'installing') -----
  load
+ 	 self createClass ifNotNil: [:trait |
- 	 self createClass ifNotNilDo: [:trait |
  		self hasComment ifTrue: [trait classComment: comment stamp: commentStamp]]!

Item was changed:
  ----- Method: MCWorkingCopyBrowser>>revertPackage (in category 'actions') -----
  revertPackage
+ 	self pickAncestorVersionInfo ifNotNil: [:info |
- 	self pickAncestorVersionInfo ifNotNilDo: [:info |
  		(self repositoryGroup versionWithInfo: info
  			ifNone: [^self inform: 'No repository found for ', info name]
  		) load]!

Item was changed:
  ----- Method: MCMczReader>>loadDefinitions (in category 'as yet unclassified') -----
  loadDefinitions
  	definitions := OrderedCollection new.
+ 	(self zip memberNamed: 'snapshot.bin') ifNotNil:
- 	(self zip memberNamed: 'snapshot.bin') ifNotNilDo:
  		[:m | [^ definitions := (DataStream on: m contentStream) next definitions]
  			on: Error do: [:fallThrough ]].
  	"otherwise"
  	(self zip membersMatching: 'snapshot/*')
  		do: [:m | self extractDefinitionsFrom: m].
  !

Item was changed:
  ----- Method: MCConflict>>definition (in category 'as yet unclassified') -----
  definition
+ 	^operation ifNotNil: [ :op | op definition ]!
- 	^operation ifNotNilDo: [ :op | op definition ]!

Item was changed:
  ----- Method: MCVersionInspector>>diff (in category 'as yet unclassified') -----
  diff
  	| ancestorVersion |
+ 	self pickAncestor ifNotNil:
- 	self pickAncestor ifNotNilDo:
  		[:ancestor |
  		ancestorVersion := self version workingCopy repositoryGroup versionWithInfo: ancestor.
  		(self version asDiffAgainst: ancestorVersion) open]!

Item was changed:
  ----- Method: MCWorkingCopyBrowser>>backportChanges (in category 'actions') -----
  backportChanges
  	self canBackport ifFalse: [^self].
  	workingCopy ifNotNil:
  		[workingCopy needsSaving ifTrue: [^ self inform: 'You must save the working copy before backporting.'].
+ 		self pickAncestorVersionInfo ifNotNil:
- 		self pickAncestorVersionInfo ifNotNilDo:
  			[:baseVersionInfo |
  			workingCopy backportChangesTo: baseVersionInfo]]!

Item was changed:
  ----- Method: MCWorkingCopyBrowser>>addRepositoryToPackage (in category 'actions') -----
  addRepositoryToPackage
+ 	self repository ifNotNil:
- 	self repository ifNotNilDo:
  		[:repos |
+ 		(self pickWorkingCopySatisfying: [ :p | (p repositoryGroup includes: repos) not ]) ifNotNil:
- 		(self pickWorkingCopySatisfying: [ :p | (p repositoryGroup includes: repos) not ]) ifNotNilDo:
  			[:wc |
  			workingCopy := wc.
  			workingCopy repositoryGroup addRepository: repos.
  			self repository: repos.	
  			self
  				changed: #workingCopySelection;
  				changed: #repositoryList;
  				changed: #repositorySelection.
  			self changedButtons]]!

Item was changed:
  ----- Method: MCWorkingCopy>>backportChangesTo: (in category 'operations') -----
  backportChangesTo: aVersionInfo
  	| baseVersion fullPatch currentVersionInfo currentVersion newSnapshot newAncestry |
  	currentVersionInfo := self currentVersionInfo.
  	baseVersion := self repositoryGroup versionWithInfo: aVersionInfo.
  	currentVersion := self repositoryGroup versionWithInfo: currentVersionInfo.
  	fullPatch := currentVersion snapshot patchRelativeToBase: baseVersion snapshot.
  	(MCChangeSelectionRequest new
  		patch: fullPatch;
  		label: 'Changes to Backport';
+ 		signal ) ifNotNil:
- 		signal ) ifNotNilDo:
  		[:partialPatch |
  		newSnapshot := MCPatcher apply: partialPatch to: baseVersion snapshot.
  		newAncestry := MCWorkingAncestry new
  							addAncestor: aVersionInfo;
  							addStepChild: currentVersionInfo;
  							yourself.
  		MCPackageLoader updatePackage: package withSnapshot: newSnapshot.
  		ancestry := newAncestry.
  		self modified: false; modified: true]!

Item was changed:
  ----- Method: MCRepository>>closestAncestorVersionFor:ifNone: (in category 'as yet unclassified') -----
  closestAncestorVersionFor: anAncestry ifNone: errorBlock
  	anAncestry breadthFirstAncestorsDo:
  		[:ancestorInfo |
+ 		(self versionWithInfo: ancestorInfo) ifNotNil: [:v | ^ v]].
- 		(self versionWithInfo: ancestorInfo) ifNotNilDo: [:v | ^ v]].
  	^ errorBlock value!

Item was changed:
  ----- Method: MCVersionInspector>>save (in category 'as yet unclassified') -----
  save
+ 	self pickRepository ifNotNil:
- 	self pickRepository ifNotNilDo:
  		[:ea |
  		ea storeVersion: self version]!

Item was changed:
  ----- Method: MCWorkingCopyBrowser>>addRequiredPackage (in category 'actions') -----
  addRequiredPackage
  	| chosen |
+ 	workingCopy ifNotNil:
- 	workingCopy ifNotNilDo:
  		[:wc |
  		chosen := self pickWorkingCopySatisfying: 
  			[:ea | ea ~= wc and: [(wc requiredPackages includes: ea package) not]].
  		chosen ifNotNil:
  			[wc requirePackage: chosen package.
  			self workingCopyListChanged]]!

Item was changed:
  ----- Method: MCAncestryTest>>versionForName:in: (in category 'building') -----
  versionForName: name in: tree
  	(tree name = name) ifTrue: [^ tree].
  	
+ 	tree ancestors do: [:ea | (self versionForName: name in: ea) ifNotNil: [:v | ^ v]].
- 	tree ancestors do: [:ea | (self versionForName: name in: ea) ifNotNilDo: [:v | ^ v]].
  	
  	^ nil!

Item was changed:
  ----- Method: MCWorkingCopyBrowser>>openRepository (in category 'actions') -----
  openRepository
+ 	self repository ifNotNil: [:repos | repos morphicOpen: workingCopy ]!
- 	self repository ifNotNilDo: [:repos | repos morphicOpen: workingCopy ]!

Item was changed:
  ----- Method: MCWorkingCopyBrowser>>removeRepository (in category 'actions') -----
  removeRepository
+ 	self repository ifNotNil:
- 	self repository ifNotNilDo:
  		[:repos |
  		self repositoryGroup removeRepository: repos.
  		self repositorySelection: (1 min: self repositories size)].
  	self changed: #repositoryList.
  	self changedButtons.
  !

Item was changed:
  ----- Method: MCPackageManager>>modified: (in category 'accessing') -----
  modified: aBoolean
       modified = aBoolean ifTrue: [^ self].
  	modified := aBoolean.
  	self changed: #modified.
  	
  	modified ifFalse:
+ 		[(((Smalltalk classNamed: 'SmalltalkImage') ifNotNil: [:si | si current]) ifNil: [Smalltalk])
- 		[(((Smalltalk classNamed: 'SmalltalkImage') ifNotNilDo: [:si | si current]) ifNil: [Smalltalk])
  			logChange: '"', self packageName, '"'].!

Item was changed:
  ----- Method: MCWorkingCopy>>newVersion (in category 'operations') -----
  newVersion
+ 	^ (self requestVersionNameAndMessageWithSuggestion: self uniqueVersionName) ifNotNil:
- 	^ (self requestVersionNameAndMessageWithSuggestion: self uniqueVersionName) ifNotNilDo:
  		[:pair |
  		self newVersionWithName: pair first message: pair last].
  !

Item was changed:
  ----- Method: MCThreeWayMerger>>removeDefinition: (in category 'as yet unclassified') -----
  removeDefinition: aDefinition
  	index
  		definitionLike: aDefinition
  		ifPresent: [:other | other = aDefinition
  								ifTrue:
  									[(self modificationConflictForDefinition: aDefinition)
+ 										ifNotNil:
- 										ifNotNilDo:
  											[:c |
  											self addOperation: c operation.
  											self removeConflict: c.
  											^ self]. 
  									(self redundantAdds includes: aDefinition)
  										ifFalse: [self addOperation: (MCRemoval of: aDefinition)]]
  								ifFalse:
  									[self addConflictWithOperation: (MCRemoval of: other)]]
  		ifAbsent: []!

Item was changed:
  ----- Method: MCClassDefinition>>load (in category 'installing') -----
  load
+ 	 self createClass ifNotNil:
- 	 self createClass ifNotNilDo:
  		[:class |
  		class class instanceVariableNames: self classInstanceVariablesString.
  		self hasComment ifTrue: [class classComment: comment stamp: commentStamp]]!

Item was changed:
  ----- Method: MCCodeTool>>adoptMessageInCurrentChangeset (in category 'menus') -----
  adoptMessageInCurrentChangeset
  	"Add the receiver's method to the current change set if not already there"
  
+ 	self selectedClassOrMetaClass ifNotNil: [ :cl |
+ 		self selectedMessageName ifNotNil: [ :sel |
- 	self selectedClassOrMetaClass ifNotNilDo: [ :cl |
- 		self selectedMessageName ifNotNilDo: [ :sel |
  			ChangeSet current adoptSelector: sel forClass: cl.
  			self changed: #annotations ]]
  !

Item was changed:
  ----- Method: MCWorkingCopyBrowser>>clearRequiredPackages (in category 'actions') -----
  clearRequiredPackages
+ 	workingCopy ifNotNil:
- 	workingCopy ifNotNilDo:
  		[:wc |
  		wc clearRequiredPackages.
  		self workingCopyListChanged]!

Item was changed:
  ----- Method: MCFileBasedRepository>>versionReaderForFileNamed:do: (in category 'as yet unclassified') -----
  versionReaderForFileNamed: aString do: aBlock
  	^ self
  		readStreamForFileNamed: aString
  		do: [:s |
+ 			(MCVersionReader readerClassForFileNamed: aString) ifNotNil:
- 			(MCVersionReader readerClassForFileNamed: aString) ifNotNilDo:
  				[:class | aBlock value: (class on: s fileName: aString)]]
  !

Item was changed:
  ----- Method: MCHttpRepository>>versionReaderForFileNamed:do: (in category 'as yet unclassified') -----
  versionReaderForFileNamed: aString do: aBlock
+ 	^ (self versionReaderForFileNamed: aString) ifNotNil: aBlock!
- 	^ (self versionReaderForFileNamed: aString) ifNotNilDo: aBlock!

Item was changed:
  ----- Method: MCMczReader>>extractDefinitionsFrom: (in category 'as yet unclassified') -----
  extractDefinitionsFrom: member
  	| reader |
  	(MCSnapshotReader readerClassForFileNamed: member fileName)
+ 		ifNotNil: [:rc | reader := rc on: member contentStream text.
- 		ifNotNilDo: [:rc | reader := rc on: member contentStream text.
  					definitions addAll: reader definitions]
  !

Item was changed:
  ----- Method: MCWorkingCopyBrowser>>addRepository (in category 'actions') -----
  addRepository
+ 	self newRepository ifNotNil:
- 	self newRepository ifNotNilDo:
  		[:repos | self addRepository: repos ].
  !

Item was changed:
  ----- Method: MCDoItParser class>>forDoit: (in category 'as yet unclassified') -----
  forDoit: aString
+ 	^ (self subclassForDoit: aString) ifNotNil: [:c | c new source: aString]!
- 	^ (self subclassForDoit: aString) ifNotNilDo: [:c | c new source: aString]!

Item was changed:
  ----- Method: MCConflict>>annotations (in category 'as yet unclassified') -----
  annotations
+ 	^operation ifNotNil: [ :op | op annotations ]!
- 	^operation ifNotNilDo: [ :op | op annotations ]!

Item was changed:
  ----- Method: MCDirectoryRepository class>>morphicConfigure (in category 'instance creation') -----
  morphicConfigure
+ 	^ FileList2 modalFolderSelector ifNotNil:
- 	^ FileList2 modalFolderSelector ifNotNilDo:
  		[:directory |
  		self new directory: directory]!

Item was removed:
- ----- Method: MethodReference>>category (in category '*monticello') -----
- category
- 	^ self actualClass organization categoryOfElement: methodSymbol!




More information about the Squeak-dev mailing list