[Pkg] Monticello Public: Monticello.impl-kph.620.mcz

squeak-dev-noreply at lists.squeakfoundation.org squeak-dev-noreply at lists.squeakfoundation.org
Sun Feb 8 04:46:14 UTC 2009


A new version of Monticello.impl was added to project Monticello Public:
http://www.squeaksource.com/mc/Monticello.impl-kph.620.mcz

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

Name: Monticello.impl-kph.620
Author: kph
Time: 8 February 2009, 4:46:03 am
UUID: 84e21120-9270-41aa-b39a-852e04c8a5ac
Ancestors: Monticello.impl-kph.619

LANDMARK - NOW FULLY MIT

=============== Diff against Monticello.impl-kph.619 ===============

Item was changed:
  ----- Method: MCRepositoryVersionsInspector>>versionListMenu: (in category 'morphic ui') -----
  versionListMenu: aMenu
  	 	
  	self hasSnapshot ifTrue: [
  		self fillMenu: aMenu fromSpecs:
  			#(
  			('adopt' #adopt)
  			('diff' #diff)  
  			('change log entry' #openChangeLogEntry)
  			('open dual changes browser' #openDual)
  			
  			).
  		aMenu add:  'copy all' target: self selector: #copyAll.
  		aMenu add:  'copy all (forked)' target: self selector: #copyAllFork.
+ 		aMenu add:  'find authors' target: self selector: #authorsFind.
  		aMenu add:  'print authors' target: self selector: #authors.
  			aMenu addLine.
  		self isVersionDeletable ifTrue: [   
  			aMenu add: 'delete' target: self selector: #delete.
  		].
  		 
  	].
+ 	self hasSnapshot ifFalse: [ 
+ 		aMenu add:  'print all authors (forked)' target: self selector: #authorsAll.
+ 		aMenu add:  'find authors (forked)' target: self selector: #authorsFindAll.
+ 		
+ 	].
- 	self hasSnapshot ifFalse: [ aMenu add:  'print all authors (forked)' target: self selector: #authorsAll ].
  
  	aMenu addLine.
  	
  	self versionListOrderMenu: aMenu.
  
  	(self class = MCRepositoryVersionsInspector) 
  		ifTrue: [
  			aMenu addLine.
  			aMenu add: 'open two column display' target: self selector: #twoColumnOpen.
  			aMenu add: 'always use two column display' target: self selector: #twoColumnAlways.
  		].
  	
  	^ aMenu
  !

Item was changed:
  ----- Method: MCChangeLogEntry>>repository: (in category 'as yet unclassified') -----
  repository: aRepository
  	repository := aRepository!

Item was added:
+ ----- Method: MCSnapshot>>definitionsWithAnyAuthor: (in category 'authorship') -----
+ definitionsWithAnyAuthor: initialsList
+ 	
+ 	^ self definitions select: [ :ea | initialsList anySatisfy: [ :init | init = ea authorInitials ]]
+ !

Item was changed:
  ----- Method: MCChangeLogEntry>>ancestors (in category 'as yet unclassified') -----
  ancestors
  	^ancestors ifNil: [ |  infosOfAncestors |
  		infosOfAncestors := self version info ancestors.
  		ancestors := infosOfAncestors collect: [:each | self versionForName: each name ] ]
  	!

Item was added:
+ ----- Method: MCRepositoryVersionsInspector>>authorsFindAll (in category 'authorship') -----
+ authorsFindAll
+ 
+ 	 [
+ 		self authorsFindIn: versionInfos. 
+ 		self inform: 'search complete'	] fork!

Item was changed:
  ----- Method: MCHttpRepository>>writeStreamForFileNamed:replace:do: (in category 'required') -----
  writeStreamForFileNamed: aString replace: ignoreBoolean do: aBlock
  	| stream response statusLine code |
  	stream := RWBinaryOrTextStream on: String new.
  	aBlock value: stream.
  	response := HTTPSocket
  					httpPut: stream contents
  					to: (self urlForFileNamed: aString)
  					user: self user
  					passwd: self password.
  
  	statusLine := response copyUpTo: Character cr.
+ 	code := statusLine findTokens: ' '. 
+ 	code := code second asInteger.
- 	code := (statusLine findTokens: ' ') second asInteger.
  	(code >= 200 and: [code < 300])
+ 			ifFalse: [self error: response].
+ 			!
- 			ifFalse: [self error: response].!

Item was changed:
  ----- Method: MCChangeLogEntry>>fileNameForVersionName: (in category 'as yet unclassified') -----
  fileNameForVersionName: aVersionName
  	| fileNames |
  	fileNames := [(repository allFileNamesForVersionNamed: aVersionName)]
  		on: Error do: [self error: 'No such version in this repository'].
  	(fileNames size = 0) ifTrue: [self error: 'No file for this version'].
  	(fileNames size = 1) ifFalse: [self error: 'What to do with multiple files?' ].
  	^fileNames first	!

Item was changed:
  ----- Method: MCChangeLogEntry>>changesAccordingTo: (in category 'as yet unclassified') -----
  changesAccordingTo: anAncestor
  	^ anAncestor snapshot patchRelativeToBase: version snapshot!

Item was changed:
+ ----- Method: MCSnapshot>>authorInitials (in category 'authorship') -----
- ----- Method: MCSnapshot>>authorInitials (in category 'accessing') -----
  authorInitials
  
  	| authors |
  	authors := Set new.
  	
  	self definitions do: [ :ea | ea authorInitials ifNotNilDo: [ :a | authors add: a ]].
  		
  	^ authors!

Item was added:
+ ----- Method: MCRepositoryVersionsInspector>>authorsFindIn: (in category 'authorship') -----
+ authorsFindIn: vis
+ 
+ 	| list defns snap string |
+ 	string := FillInTheBlank request: 'Please enter authors'.
+ 	list := string findTokens: ','.
+ 	(string includesSubString: ',,') ifTrue: [ list add: '' ].
+ 	vis do: [ :ea |
+ 		Transcript cr; show: 'inspecting ', ea description.
+ 		version := repository versionWithInfo: ea. 
+ 		defns := version snapshot definitionsWithAnyAuthor: list.
+ 		defns ifNotEmpty: [
+ 			snap := MCSnapshot fromDefinitions: defns.
+ 			  ((MCPatchBrowser forPatch: (snap patchRelativeToBase: (MCSnapshot empty)))
+ 				label: version description;
+ 				yourself) show.
+ 		]
+ 	].
+ 	^ defns!

Item was added:
+ ----- Method: MCRepositoryVersionsInspector>>authorsFind (in category 'authorship') -----
+ authorsFind
+ 
+ 	(self authorsFindIn: (Array with: selectedVersionInfo)) ifEmpty:[ self inform: 'nothing found' ]!



More information about the Packages mailing list