[Pkg] The Trunk: Monticello-cmm.608.mcz

commits at source.squeak.org commits at source.squeak.org
Sat Apr 4 21:39:49 UTC 2015


Chris Muller uploaded a new version of Monticello to project The Trunk:
http://source.squeak.org/trunk/Monticello-cmm.608.mcz

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

Name: Monticello-cmm.608
Author: cmm
Time: 4 April 2015, 4:39:33.607 pm
UUID: fe662a05-cd5a-4264-95aa-4ff408797ae1
Ancestors: Monticello-bf.607, Monticello-cmm.601

Updates to the Save Dialog:
	- Honors Reuse Windows.
	- Upon opening, selects the first change automatically.  This will help folks avoid entering version notes into the code pane.
	- Includes the important change annotation pane unconditionally, regardless of the annotationPanes preference.  IMO, we should get rid of defaultAnnotationPaneHeight.
	- Added refresh (R) the changes list.
	- ignore (I) and refresh (R) moved to the bottom of the menu to restore the easier keyboard access to 'install' and 'revert'.
- #flushCachedVersions to no longer rely on Smalltalk garbageCollect to calculate the bytes saved.  Still not sure if its working though.

=============== Diff against Monticello-bf.607 ===============

Item was changed:
  ----- Method: MCChangeSelector>>widgetSpecs (in category 'as yet unclassified') -----
  widgetSpecs
  	Preferences annotationPanes ifFalse: [ ^#(
  		((buttonRow) (0 0 1 0) (0 0 0 30))
  		((multiListMorph:selection:listSelection:menu: list selection listSelectionAt: methodListMenu:) (0 0 1 0.4) (0 30 0 0))
  		((innerButtonRow) (0 0.4 1 0.4) (0 0 0 30))
  		((textMorph: text) (0 0.4 1 1) (0 30 0 0))
  		)].
  
  	^ #(
  		((buttonRow) (0 0 1 0) (0 0 0 30))
  		((multiListMorph:selection:listSelection:menu: list selection listSelectionAt: methodListMenu:) (0 0 1 0.4) (0 30 0 0))
  		((innerButtonRow) (0 0.4 1 0.4) (0 0 0 30))
+ 		((textMorph: annotations) (0 0.4 1 0.4) (0 30 0 88))
+ 		((textMorph: text) (0 0.4 1 1) (0 88 0 0))
- 		((textMorph: annotations) (0 0.4 1 0.4) (0 30 0 60))
- 		((textMorph: text) (0 0.4 1 1) (0 60 0 0))
  		)!

Item was changed:
  ----- Method: MCOperationsBrowser>>selection: (in category 'selecting') -----
+ selection: aNumber 
+ 	selection := self items
+ 		at: aNumber
+ 		ifAbsent: [  ].
+ 	self
+ 		 changed: #selection ;
+ 		 changed: #text ;
+ 		 changed: #annotations!
- selection: aNumber
- 	selection := aNumber = 0 ifFalse: [self items at: aNumber].
- 	self changed: #selection; changed: #text; changed: #annotations!

Item was added:
+ ----- Method: MCPatchBrowser>>representsSameBrowseeAs: (in category 'ui') -----
+ representsSameBrowseeAs: anotherModel 
+ 	^ self class = anotherModel class
+ 	and: [ items = anotherModel items ]!

Item was changed:
+ ----- Method: MCSaveVersionDialog>>accept (in category 'actions') -----
- ----- Method: MCSaveVersionDialog>>accept (in category 'as yet unclassified') -----
  accept
  	self updateItems.
  	self answer:
  		(Array
  			with: (self findTextMorph: #versionName) text asString
  			with: (self findTextMorph: #logMessage) text asString
  			with: ignore)
  !

Item was changed:
+ ----- Method: MCSaveVersionDialog>>cancel (in category 'actions') -----
- ----- Method: MCSaveVersionDialog>>cancel (in category 'as yet unclassified') -----
  cancel
  	self answer: nil!

Item was changed:
+ ----- Method: MCSaveVersionDialog>>ignore (in category 'actions') -----
- ----- Method: MCSaveVersionDialog>>ignore (in category 'as yet unclassified') -----
  ignore
  	^ ignore ifNil: [ignore := Set new]!

Item was changed:
+ ----- Method: MCSaveVersionDialog>>ignoreSelection (in category 'actions') -----
- ----- Method: MCSaveVersionDialog>>ignoreSelection (in category 'as yet unclassified') -----
  ignoreSelection
  	selection
  		ifNil: [ignore size = items size
  			ifFalse: [ignore addAll: items]
  			ifTrue: [ignore removeAll]]
  		ifNotNil: [
  			ignore remove: selection ifAbsent: [
  				ignore add: selection].
  			self selection < items size
  				ifTrue: [self selection: self selection + 1]].
  	self changed: #list
  !

Item was changed:
+ ----- Method: MCSaveVersionDialog>>installSelection (in category 'actions') -----
- ----- Method: MCSaveVersionDialog>>installSelection (in category 'as yet unclassified') -----
  installSelection
  	super installSelection.
  	selection ifNotNil: [
  		ignore remove: selection ifAbsent: [].
  		self changed: #list].
  
  !

Item was changed:
  ----- Method: MCSaveVersionDialog>>methodListKey:from: (in category 'menus') -----
  methodListKey: aKeystroke from: aListMorph 
  	aKeystroke caseOf: {
  		[$I] -> [self ignoreSelection].
+ 		[$R] -> [self refresh].
  	} otherwise: [super methodListKey: aKeystroke from: aListMorph ]!

Item was changed:
+ ----- Method: MCSaveVersionDialog>>methodListMenu: (in category 'menus') -----
- ----- Method: MCSaveVersionDialog>>methodListMenu: (in category 'accessing') -----
  methodListMenu: aMenu
- 	aMenu addList:#(
- 		('ignore (I)'	ignoreSelection 'Do not include this change when saving')
- 		-).
  	super methodListMenu: aMenu.
+ 	aMenu addList:#(-
+ 		('ignore (I)'	ignoreSelection 'Toggle inclusion of this change when saving.')
+ 		('refresh (R)'	refresh 'Refresh the list of changes to this package.')).
  	^aMenu!

Item was added:
+ ----- Method: MCSaveVersionDialog>>refresh (in category 'actions') -----
+ refresh
+ 	self
+ 		 updateItems ;
+ 		 changed: #list!

Item was changed:
+ ----- Method: MCSaveVersionDialog>>revertSelection (in category 'actions') -----
- ----- Method: MCSaveVersionDialog>>revertSelection (in category 'as yet unclassified') -----
  revertSelection
  	super revertSelection.
  	selection ifNotNil: [
  		ignore add: selection.
  		self changed: #list].
  !

Item was changed:
  ----- Method: MCSaveVersionDialog>>widgetSpecs (in category 'ui') -----
  widgetSpecs
  	^ #(	
+ 		((listMorph:selection:menu:keystroke: list selection methodListMenu: methodListKey:from:) (0 0 0.5 0.6) (0 0 0 -47) )
- 		((listMorph:selection:menu:keystroke: list selection methodListMenu: methodListKey:from:) (0 0 0.5 0.6) )
  		((textMorph: versionName) (0.5 0 1 0) (0 0 0 30))
+ 		((textMorph: logMessage) (0.5 0 1 0.6) (0 30 0 -47))
+ 		((buttonRow) (0.5 0.6 1 0.6) (0 -47 0 0))
+ 		((textMorph: annotations) (0 0.6 0.5 0.6) (0 -47 0 0))
- 		((textMorph: logMessage) (0.5 0 1 0.6) (0 30 0 -30))
- 		((buttonRow) (0.5 0.6 1 0.6) (0 -30 0 0))
  		((textMorph: text) (0 0.6 1 1) (0 0 0 0))
  		)!

Item was changed:
  ----- Method: MCVersionNameAndMessageRequest>>defaultAction (in category 'handling') -----
  defaultAction
  	^ MCSaveVersionDialog new
  		versionName: suggestion;
  		logMessage: initialMessage;
  		patchBlock: patchBlock;
+ 		selection: 1;
  		showModally!

Item was changed:
  ----- Method: MCWorkingCopyBrowser>>flushCachedVersions (in category 'actions') -----
  flushCachedVersions
  	| beforeBytes afterBytes beforeVersions afterVersions |
  	Cursor wait showWhile: [
+ 		Smalltalk garbageCollect.
+ 		beforeBytes := Smalltalk bytesLeft: true.
- 		beforeBytes := Smalltalk garbageCollect.
  		beforeVersions := MCVersion allSubInstances size.
  		MCFileBasedRepository flushAllCaches.
+ 		afterBytes := Smalltalk bytesLeft: true.
- 		afterBytes := Smalltalk garbageCollect.
  		afterVersions := MCVersion allSubInstances size.
  	].
  	^self inform: (beforeVersions - afterVersions) asString, ' versions flushed', String cr,
+  		(beforeBytes - afterBytes) asBytesDescription, ' bytes reclaimed'!
-  		(afterBytes - beforeBytes) asStringWithCommas, ' bytes reclaimed'!



More information about the Packages mailing list