[etoys-dev] Etoys: Monticello-bf.400.mcz

commits at source.squeak.org commits at source.squeak.org
Tue Sep 7 15:52:02 EDT 2010


Bert Freudenberg uploaded a new version of Monticello to project Etoys:
http://source.squeak.org/etoys/Monticello-bf.400.mcz

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

Name: Monticello-bf.400
Author: bf
Time: 7 September 2010, 9:51:49 pm
UUID: a7b2b800-bfec-4e1d-a297-b13de5c3bc6c
Ancestors: Monticello-bf.398, Monticello-bf.399

Merge latest from Squeak trunk

=============== Diff against Monticello-bf.398 ===============

Item was changed:
  SystemOrganization addCategory: #'Monticello-Base'!
  SystemOrganization addCategory: #'Monticello-Chunk Format'!
  SystemOrganization addCategory: #'Monticello-Loading'!
  SystemOrganization addCategory: #'Monticello-Merging'!
  SystemOrganization addCategory: #'Monticello-Modeling'!
  SystemOrganization addCategory: #'Monticello-Patching'!
  SystemOrganization addCategory: #'Monticello-Repositories'!
  SystemOrganization addCategory: #'Monticello-Storing'!
  SystemOrganization addCategory: #'Monticello-UI'!
  SystemOrganization addCategory: #'Monticello-Versioning'!
+ SystemOrganization addCategory: #'Monticello-Mocks'!

Item was added:
+ Object subclass: #MCMenuSpec
+ 	instanceVariableNames: 'entry target selector'
+ 	classVariableNames: ''
+ 	poolDictionaries: ''
+ 	category: 'Monticello-UI'!
+ 
+ !MCMenuSpec commentStamp: 'tfel 6/12/2010 14:57' prior: 0!
+ A MCMenuSpec holds information to add menu entries to the monticello browser menus from external classes.
+ Required is the entry string (#entry), the call target and the selector be called.
+ An external class may use the MCWorkingCopyBrowser class>>addMenuSpec: method to add it's own menu entry to the monticello browser context menu.
+ 
+ Note that MCMenuSpecs are compared via their menu entry string and if multiple MCMenuSpecs are added to the MCWorkingCopyBrowser, the last one takes precedence.!

Item was added:
+ ----- Method: MCMenuSpec>>= (in category 'comparing') -----
+ = aMCMenuSpec
+ 
+ 	^ self class == aMCMenuSpec class and: [self entry = aMCMenuSpec entry].!

Item was added:
+ ----- Method: MCMenuSpec>>entry (in category 'accessing') -----
+ entry
+ 
+ 	^entry!

Item was added:
+ ----- Method: MCMenuSpec>>entry: (in category 'accessing') -----
+ entry: anObject
+ 
+ 	entry := anObject!

Item was added:
+ ----- Method: MCMenuSpec>>hash (in category 'comparing') -----
+ hash
+ 
+ 	^ self entry hash!

Item was added:
+ ----- Method: MCMenuSpec>>selector (in category 'accessing') -----
+ selector
+ 
+ 	^selector!

Item was added:
+ ----- Method: MCMenuSpec>>selector: (in category 'accessing') -----
+ selector: anObject
+ 
+ 	selector := anObject!

Item was added:
+ ----- Method: MCMenuSpec>>target (in category 'accessing') -----
+ target
+ 
+ 	^target!

Item was added:
+ ----- Method: MCMenuSpec>>target: (in category 'accessing') -----
+ target: anObject
+ 
+ 	target := anObject!

Item was added:
+ Object subclass: #MCPatchMessage
+ 	instanceVariableNames: 'stream'
+ 	classVariableNames: ''
+ 	poolDictionaries: ''
+ 	category: 'Monticello-Versioning'!

Item was added:
+ ----- Method: MCPatchMessage>>addDefinition: (in category 'patch operations') -----
+ addDefinition: aDefinition
+ 	stream nextPutAll: 'A'; tab; nextPutAll: aDefinition summary; cr!

Item was added:
+ ----- Method: MCPatchMessage>>message (in category 'accessing') -----
+ message
+ 	^stream contents
+ !

Item was added:
+ ----- Method: MCPatchMessage>>modifyDefinition:to: (in category 'patch operations') -----
+ modifyDefinition: oldDefinition to: newDefinition
+ 	stream nextPutAll: 'M'; tab; nextPutAll: newDefinition summary; cr!

Item was added:
+ ----- Method: MCPatchMessage>>patch: (in category 'accessing') -----
+ patch: aPatch
+ 	stream ifNil: [stream := WriteStream on: (String new: 100)].
+ 	aPatch operations asSortedCollection
+ 		do: [:op | op applyTo: self]!

Item was added:
+ ----- Method: MCPatchMessage>>removeDefinition: (in category 'patch operations') -----
+ removeDefinition: aDefinition
+ 	stream nextPutAll: 'D'; tab; nextPutAll: aDefinition summary; cr!

Item was changed:
  Notification subclass: #MCVersionNameAndMessageRequest
+ 	instanceVariableNames: 'suggestion initialMessage'
- 	instanceVariableNames: 'suggestion'
  	classVariableNames: ''
  	poolDictionaries: ''
  	category: 'Monticello-Versioning'!

Item was changed:
  ----- Method: MCVersionNameAndMessageRequest>>defaultAction (in category 'as yet unclassified') -----
  defaultAction
  	^ MCSaveVersionDialog new
  		versionName: suggestion;
+ 		logMessage: initialMessage;
  		showModally!

Item was added:
+ ----- Method: MCVersionNameAndMessageRequest>>initialMessage (in category 'as yet unclassified') -----
+ initialMessage
+ 	^ initialMessage!

Item was added:
+ ----- Method: MCVersionNameAndMessageRequest>>initialMessage: (in category 'as yet unclassified') -----
+ initialMessage: aString
+ 	initialMessage := aString!

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

Item was added:
+ ----- Method: MCWorkingCopy>>patchMessageChanges (in category 'operations') -----
+ patchMessageChanges
+ 	| changes parentInfo parentSnapshot |
+ 	parentInfo := self ancestors
+ 		ifEmpty: [nil]
+ 		ifNotEmpty: [self ancestors first].
+ 	parentSnapshot := 	self findSnapshotWithVersionInfo: parentInfo.
+ 	changes := package snapshot patchRelativeToBase: parentSnapshot.
+ 	^ (MCPatchMessage new patch: changes) message!

Item was added:
+ ----- Method: MCWorkingCopy>>patchMessageChangesDelimiter (in category 'operations') -----
+ patchMessageChangesDelimiter
+ 	^'=== text below is ignored ==='!

Item was added:
+ ----- Method: MCWorkingCopy>>patchMessageChangesHeader (in category 'operations') -----
+ patchMessageChangesHeader
+ 	^ancestry summary, String cr,
+ 	'Added, Modified, Deleted',
+ 	(self ancestors ifEmpty: [''] ifNotEmpty: [' vs. ', self ancestors first name]), ':'!

Item was added:
+ ----- Method: MCWorkingCopy>>patchMessageDefault (in category 'operations') -----
+ patchMessageDefault
+ 	^ 'empty log message'!

Item was added:
+ ----- Method: MCWorkingCopy>>patchMessageStripped: (in category 'operations') -----
+ patchMessageStripped: aString
+ 	| pos |
+ 	pos := aString findString: self patchMessageChangesDelimiter.
+ 	^ (pos > 0
+ 		ifTrue: [aString first: pos - 1]
+ 		ifFalse: [aString]) withBlanksTrimmed!

Item was added:
+ ----- Method: MCWorkingCopy>>patchMessageSuggestion (in category 'operations') -----
+ patchMessageSuggestion
+ 	^	self patchMessageDefault, String cr, String cr,
+ 		self patchMessageChangesDelimiter, String cr,
+ 		self patchMessageChangesHeader, String cr,
+ 		self patchMessageChanges!

Item was removed:
- ----- Method: MCWorkingCopy>>requestVersionNameAndMessageWithSuggestion: (in category 'private') -----
- requestVersionNameAndMessageWithSuggestion: aString
- 	^ (MCVersionNameAndMessageRequest new suggestedName: aString) signal!

Item was added:
+ ----- Method: MCWorkingCopy>>requestVersionNameAndMessageWithSuggestion:initialMessage: (in category 'private') -----
+ requestVersionNameAndMessageWithSuggestion: nameString initialMessage: msgString
+ 	^ (MCVersionNameAndMessageRequest new
+ 		suggestedName: nameString;
+ 		initialMessage: msgString
+ 		) signal!

Item was changed:
  MCTool subclass: #MCWorkingCopyBrowser
  	instanceVariableNames: 'workingCopy workingCopyWrapper repository defaults'
+ 	classVariableNames: 'CheckForNewerVersionsBeforeSave ExternalMenuEntries'
- 	classVariableNames: 'CheckForNewerVersionsBeforeSave'
  	poolDictionaries: ''
  	category: 'Monticello-UI'!

Item was added:
+ ----- Method: MCWorkingCopyBrowser class>>addMenuSpec: (in category 'hooks') -----
+ addMenuSpec: aMCMenuSpec
+ 	"Register a context menu entry in the monticello browser from an external package.
+ 	 The MCWorkingCopyBrowser model is passed as argument."
+ 	self externalMenuEntries 
+ 		remove: aMCMenuSpec 
+ 		ifAbsent: ["Remove any previous entry with description string"];
+ 		add: aMCMenuSpec.!

Item was added:
+ ----- Method: MCWorkingCopyBrowser class>>externalMenuEntries (in category 'hooks') -----
+ externalMenuEntries
+ 	
+ 	ExternalMenuEntries ifNil: [ExternalMenuEntries := Set new].
+ 	^ ExternalMenuEntries!

Item was added:
+ ----- Method: MCWorkingCopyBrowser>>insertExternalMenuEntries: (in category 'morphic ui') -----
+ insertExternalMenuEntries: aMenu
+ 	
+ 	self class externalMenuEntries ifNotEmpty: [
+ 		aMenu addLine.
+ 		self class externalMenuEntries do: [:each |
+ 			aMenu 
+ 				add: each entry 
+ 				target: each target
+ 				selector: each selector
+ 				argument: self]].!

Item was changed:
  ----- Method: MCWorkingCopyBrowser>>workingCopyListMenu: (in category 'morphic ui') -----
  workingCopyListMenu: aMenu
  	workingCopy ifNil: [^ aMenu].
  	self fillMenu: aMenu fromSpecs:
  		#(('add required package' #addRequiredPackage)
  			('clear required packages' #clearRequiredPackages)
  			('browse package' #browseWorkingCopy)
  			('view changes' #viewChanges)
  			('view history' #viewHistory)
  			('recompile package' #recompilePackage)
  			('revert package...' #revertPackage)
  			('unload package' #unloadPackage)
  			('delete working copy' #deleteWorkingCopy)).
  	(Smalltalk includesKey: #SARMCPackageDumper) ifTrue: [
  		aMenu add: 'make SAR' target: self selector: #fileOutAsSAR
  	].
+ 	self insertExternalMenuEntries: aMenu.
  	^aMenu!



More information about the etoys-dev mailing list