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

squeak-dev-noreply at lists.squeakfoundation.org squeak-dev-noreply at lists.squeakfoundation.org
Sat Feb 7 21:35:34 UTC 2009


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

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

Name: Monticello.impl-kph.617
Author: kph
Time: 7 February 2009, 9:35:17 pm
UUID: 24faebcc-475b-4c74-adfb-7d8751b1f282
Ancestors: Monticello.impl-mtf.616

+ scanning of package/packages/whole repository for authors

=============== Diff against Monticello.impl-mtf.616 ===============

Item was changed:
  ----- Method: MCVersionInfo>>authorFromName (in category 'pillaging') -----
  authorFromName
   	
+  	| authorTokens out |
- 	| authorTokens out |
  	
  	authorTokens := OrderedCollection new.
  	
  	self nameAfterLastDashAsTokens do: [ : token |
  
  		token first isDigit ifFalse: [ authorTokens add: token ].
  	
  	].
  
  	out := String streamContents: [:str | 
  	   authorTokens do: [ :ea | str nextPutAll: ea ; nextPut: $. ]
  	].
  
  	^ out allButLast 
  !

Item was changed:
+ ----- Method: MCRepositoryVersionsInspector>>copyAllFork (in category 'actions') -----
- ----- Method: MCRepositoryVersionsInspector>>copyAllFork (in category 'morphic ui') -----
  copyAllFork
  		| versionsToCopy   aVersion gotAlready |
   
  	self pickRepository ifNotNilDo: [:aRepository |.
  	
  	gotAlready := aRepository heldVersionInfos collect: [ :v | v versionName ].
  
  	versionsToCopy := versionInfos removeAllSuchThat: [ :v | gotAlready includes: v versionName ].
  
  		Transcript cr; show: 'versions: ', versionsToCopy asArray printString.
  	[   [
  		versionsToCopy do: [:each |
  		
  				 [ aVersion := repository versionWithInfo: each. 
  				Transcript cr; show: '',aRepository description,' storeVersion: ', aVersion printString.
  				aRepository storeVersion: aVersion ] ifError: [ Transcript cr; show: each description, ' not readable'. ]
  			
  			]
  		] on: Notification do: [ :ex | ex resume ].
  	] forkAt: Processor userBackgroundPriority.
  ]
  	!

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:  'print authors' target: self selector: #authors.
+ 			aMenu addLine.
- 		aMenu addLine.
  		self isVersionDeletable ifTrue: [   
  			aMenu add: 'delete' target: self selector: #delete.
  		].
  		 
  	].
+ 	self hasSnapshot ifFalse: [ aMenu add:  'print all authors' 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 added:
+ ----- Method: MCRepositoryVersionsInspector>>authorNameFor: (in category 'authorship') -----
+ authorNameFor: init
+ 
+ 	^ ((Smalltalk classNamed: 'Authorship') ifNil: [ ^ '-' ]) nameFor: init!

Item was changed:
+ ----- Method: MCRepositoryVersionsInspector>>buttonSpecs (in category 'actions') -----
- ----- Method: MCRepositoryVersionsInspector>>buttonSpecs (in category 'morphic ui') -----
  buttonSpecs
  	^#(('Refresh' refresh 'refresh the version-list')) , super buttonSpecs!

Item was changed:
  ----- Method: MCVersionInfo>>versionStringFrom: (in category 'pillaging') -----
  versionStringFrom: tokens
  	
+  	"version string includes the author initials and the version numbers" 
- 	"version string includes the author initials and the version numbers" 
  	
  	^ String streamContents: [:stream | tokens
  		do: [:ea | stream nextPutAll: ea]
  		separatedBy: [stream nextPut: $.]]!

Item was added:
+ ----- Method: MCDefinition>>authorInitials (in category 'accessing') -----
+ authorInitials
+ 	
+ 	^ nil!

Item was changed:
  ----- Method: MCVersionInfo>>versionString (in category 'pillaging') -----
  versionString
  	
  	^ self versionStringFrom: self versionTokens
  	 !

Item was changed:
  ----- Method: MCPackageManager class>>methodModified: (in category 'system changes') -----
  methodModified: anEvent
+ 	^ self managersForClass: anEvent itemClass selector: anEvent itemSelector do:[:mgr| mgr modified: true].!
- 	^self managersForClass: anEvent itemClass selector: anEvent itemSelector do:[:mgr| mgr modified: true].!

Item was added:
+ ----- Method: MCRepositoryVersionsInspector>>authorsPrint: (in category 'authorship') -----
+ authorsPrint: authors
+ 
+ 	authors do: [ :init |
+ 		Transcript cr show: (init printString, ' -> ', (self authorNameFor: init) printString), '.'.
+ 	].
+ 	  
+ 	^ authors!

Item was changed:
  ----- Method: MCSnapshotBrowser>>loadMethodSelection (in category 'menus') -----
  loadMethodSelection
  	methodSelection ifNil: [ ^self ].
  	(MCPackageLoader1b new) 
  		addDefinition: methodSelection;
+ 		load !
- 		load!

Item was changed:
  ----- Method: MCVersionInfo>>nextUIDBasedVersion (in category 'pillaging') -----
  nextUIDBasedVersion
  	
  	^ self class new name: (self packageName, '-', Utilities authorInitials, '.' , (self versionStringFrom: self nextUIDBasedVersionTokens)); yourself
  
   !

Item was changed:
+ ----- Method: MCRepositoryVersionsInspector>>browse (in category 'actions') -----
- ----- Method: MCRepositoryVersionsInspector>>browse (in category '') -----
  browse
  
  	self hasVersion ifTrue: [ self versionInfo browseVersionFrom: repository ].
  	 
  	self refresh
  	!

Item was added:
+ ----- Method: MCRepositoryVersionsInspector>>authors (in category 'authorship') -----
+ authors
+ 
+ 	(self authorsPrint: (self authorsForVersionInfo: selectedVersionInfo on: Set new)) explore!

Item was changed:
  ----- Method: MCScriptDefinition>>preloadOver: (in category '') -----
  preloadOver: aDefinition
   
  	super preloadOver: aDefinition.
  	self installScript!

Item was changed:
  ----- Method: MCVersionInfoFilename>>nextUIDBasedVersion (in category 'accessing') -----
  nextUIDBasedVersion
  	
  	^ self class new name: (self packageName, '-', Utilities authorInitials, '.' , (self versionStringFrom: self nextUIDBasedVersionTokens), '.', self ext); yourself
  
   !

Item was added:
+ ----- Method: MCRepositoryVersionsInspector>>authorsForVersionInfo:on: (in category 'authorship') -----
+ authorsForVersionInfo: versionInfo on: aCollection
+  					 
+ 	aCollection addAll: (repository versionWithInfo: versionInfo) snapshot authorInitials.
+ 
+ 	^ aCollection	!

Item was changed:
  ----- Method: MCDefinition>>load (in category 'installing') -----
  load
  
  	self preloadOver: nil.
  	self install.
  	self postinstall.
  	self postloadOver: nil.!

Item was added:
+ ----- Method: MCMethodDefinition>>authorInitials (in category 'accessing') -----
+ authorInitials
+ 
+ 	^ self timeStamp upTo: $ .!

Item was changed:
  ----- Method: MCVersionInfo>>nextUIDBasedVersionTokens (in category 'pillaging') -----
  nextUIDBasedVersionTokens
  	
  	"The Universal ID is not a true GUID but a simpler sortable timestamp based equivalent."
  	
   	| t count tokens |
  	
  	"copyReplaceAll is more backwards compatible than replacing:with: "
  	
  	tokens := self versionTokens.
  	
  	count := tokens last asNumber.
  	
  	t := DateAndTime now.
  	tokens at: (tokens size - 2) put: (t asDate printFormat: #(3 2 1 0 1 1 2)).
  	t := t asTime.
  	tokens at: (tokens size - 1) put: (t print24 reject: [ :ea | ea = $: ]), 
  	(t milliSecond asString padded: #left to: 3	with: $0).
  	tokens at: tokens size put: (count + 1) asString.
  	
  	^ tokens
  	!

Item was added:
+ ----- 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>>authorsAll (in category 'authorship') -----
+ authorsAll
+ 
+ 	 | authors |
+ 
+ 	 authors := Set new.
+ 	self halt.
+ 	 versionInfos do: [ :ea | 
+ 		Transcript cr show: 'inspecting ', ea description.
+ 		self authorsForVersionInfo: ea on: authors ].
+ 	
+ 	self authorsPrint: authors.
+ 	^ authors explore!

Item was changed:
  ----- Method: MCWorkingCopyBrowser>>widgetSpecs (in category 'morphic ui') -----
  widgetSpecs
  	^ #(
+ 		((buttonRow) (0 0 1 0) (0 0 0 29))
- 		((buttonRow) (0 0 1 0) (0 0 0 30))
  		((treeOrListMorph: workingCopy) (0 0 0.5 1) (0 30 0 0))
  		((listMorph: repository) (0.5 0 1 1) (0 30 0 0))
  		)!

Item was changed:
+ ----- Method: MCRepositoryVersionsInspector>>copyAll (in category 'actions') -----
- ----- Method: MCRepositoryVersionsInspector>>copyAll (in category 'morphic ui') -----
  copyAll
  		| versionsToCopy   aVersion gotAlready |
   
  	self pickRepository ifNotNilDo: [:aRepository |.
  	
  	gotAlready := aRepository heldVersionInfos collect: [ :v | v versionName ].
  
  	versionsToCopy := versionInfos removeAllSuchThat: [ :v | gotAlready includes: v versionName ].
  				 
  		Transcript cr; show: 'versions: ', versionsToCopy asArray printString.
  		Cursor wait showWhile: [
  			versionsToCopy do: [:each |
  				[ aVersion := repository versionWithInfo: each.
  				Transcript cr; show: '',aRepository description,' storeVersion: ', aVersion description.
  
   		aVersion info name: aVersion info name withBlanksTrimmed.
  		aVersion info allAncestorsDo: [ :ea | ea name: ea name withBlanksTrimmed ].
   
  				aRepository storeVersion: aVersion ] ifError: [ Transcript cr; show: each description, ' not readable'. ]
  			
  			]
  		]
  	]!

Item was changed:
  ----- Method: MCWorkingCopyBrowser>>defaultExtent (in category 'morphic ui') -----
  defaultExtent
+ 	^ 620 at 400!
- 	^ 600 at 400!

Item was changed:
+ ----- Method: MCRepositoryVersionsInspector>>hasSnapshot (in category 'testing') -----
- ----- Method: MCRepositoryVersionsInspector>>hasSnapshot (in category '') -----
  hasSnapshot
  	 
  	^ selectedVersionInfo notNil and: [ selectedVersionInfo hasSnapshot ]!

Item was changed:
+ ----- Method: MCRepositoryVersionsInspector>>merge (in category 'actions') -----
- ----- Method: MCRepositoryVersionsInspector>>merge (in category '') -----
  merge
   
  	self hasVersion ifTrue: [ self versionInfo mergeVersionFrom: repository ].
  	 
  	self refresh
  	!



More information about the Packages mailing list