[Pkg] Monticello Public: Monticello.impl-mtf.558.mcz

squeaksource-noreply at iam.unibe.ch squeaksource-noreply at iam.unibe.ch
Tue Jul 22 02:02:57 UTC 2008


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

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

Name: Monticello.impl-mtf.558
Author: mtf
Time: 21 July 2008, 7:02:09 pm
UUID: 34bc08f3-6600-4d72-bf99-561eeccb95a1
Ancestors: Monticello.impl-mtf.557

Merged in changes from Pharo, as follows:

sd.309: No change; we already have MCWorkingCopy>>printOn:

sd.310: No change; we already changed _ to :=

sd.313: Removed MCCodeTool>>printOutMessage and its menu item

sd.314: Removed MVC support from MCCodeTool>>browseFullProtocol

stephane.ducasse.315: Innapropriate; Author is Pharo-specific

stephane.ducasse.316: No change; we already made a better HTTP creation template

AlexandreBergel.320:
- Added MCRepositoryGroup>>useCache and senders
- Sort dirty packages to the top of the MC Browser
- Opaque change to MCTool>>buttonRow:

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

Item was added:
+ ----- Method: MCRepositoryGroup>>useCache (in category 'as yet unclassified') -----
+ useCache
+ 	^ useCache ifNil: [
+ 		useCache := true
+ 	]!

Item was changed:
  ----- Method: MCWorkingCopyBrowser>>workingCopies (in category 'morphic ui') -----
  workingCopies
+ "List the working copies with the changed packages at the top"
+ 
+ 	| c |
+ 	c := MCWorkingCopy allManagers asSortedCollection:
+ 		[ :a :b | a package name <= b package name ].
+ 	^ (c select: [:mc| mc needsSaving]) asOrderedCollection, (c reject: [:mc| mc needsSaving]) asOrderedCollection.
+ !
- 	^ MCWorkingCopy allManagers asSortedCollection:
- 		[ :a :b | a package name <= b package name ]!

Item was changed:
  ----- Method: MCRepositoryGroup>>repositories (in category 'as yet unclassified') -----
  repositories
+ 	^ (self useCache 
+ 		ifTrue: [Array with: MCCacheRepository default] 
+ 		ifFalse: [Array new]) , repositories select: [ :ea | ea isValid ]
+ !
- 	^ ((Array with: MCCacheRepository default), repositories) select: [ :ea | ea isValid ]!

Item was changed:
  Object subclass: #MCRepositoryGroup
+ 	instanceVariableNames: 'repositories useCache'
- 	instanceVariableNames: 'repositories'
  	classVariableNames: ''
  	poolDictionaries: ''
  	category: 'Monticello-Versioning'!
  MCRepositoryGroup class
  	instanceVariableNames: 'default'!
  
  !MCRepositoryGroup commentStamp: '<historical>' prior: 0!
  A singleton class, holds the list of repositories. Can look for a requested VersionInfo among its repositories.!

Item was added:
+ ----- Method: MCRepositoryGroup>>disableCache (in category 'as yet unclassified') -----
+ disableCache
+ 	useCache := false!

Item was changed:
  ----- Method: MCCodeTool>>methodListMenu: (in category 'menus') -----
  methodListMenu: aMenu
  	"Build the menu for the selected method, if any."
  	
  	self selectedMessageName ifNotNil: [
  	aMenu addList:#(
  			('browse full (b)' 						browseMethodFull)
  			('browse hierarchy (h)'					classHierarchy)
  			('browse method (O)'					openSingleMessageBrowser)
  			('browse protocol (p)'					browseFullProtocol)
  			-
  			('fileOut (o)'							fileOutMessage)
- 			('printOut'								printOutMessage)
- 			('copy class and selector'				copyClassAndSelector)
  			('copy selector (c)'						copySelector)).
  		aMenu addList: #(
  			-
  			('browse senders (n)'						browseSendersOfMessages)
  			('browse implementors (m)'					browseMessages)
  			('inheritance (i)'						methodHierarchy)
  			('versions (v)'							browseVersions)
  		('change sets with this method'			findMethodInChangeSets)
  "		('x revert to previous version'				revertToPreviousVersion)"
  		('remove from current change set'		removeFromCurrentChanges)
  "		('x revert & remove from changes'		revertAndForget)"
  		('add to current change set'				adoptMessageInCurrentChangeset)
  "		('x copy up or copy down...'				copyUpOrCopyDown)"
  "		('x remove method (x)'					removeMessage)"
  		"-"
  		).
  	].
  "	aMenu addList: #(
  			('x inst var refs...'						browseInstVarRefs)
  			('x inst var defs...'						browseInstVarDefs)
  			('x class var refs...'						browseClassVarRefs)
  			('x class variables'						browseClassVariables)
  			('x class refs (N)'							browseClassRefs)
  	).
  "
  	^ aMenu
  !

Item was changed:
  ----- Method: MCCodeTool>>browseFullProtocol (in category 'menus') -----
  browseFullProtocol
+ 	"Open up a protocol-category browser on the value of the
+ 	receiver's current selection."
+ 	
+ 	^ self spawnFullProtocol!
- 	"Open up a protocol-category browser on the value of the receiver's current selection.    If in mvc, an old-style protocol browser is opened instead.  Someone who still uses mvc might wish to make the protocol-category-browser work there too, thanks."
- 
- 	| aClass |
- 
- 	(Smalltalk isMorphic and: [Smalltalk includesKey: #Lexicon]) ifFalse: [^ self spawnFullProtocol].
- 	(aClass := self selectedClassOrMetaClass) ifNotNil:
- 		[(Smalltalk at: #Lexicon) new openOnClass: aClass inWorld: ActiveWorld showingSelector: self selectedMessageName]!

Item was changed:
  ----- Method: MCTool>>buttonRow: (in category 'morphic ui') -----
  buttonRow: specArray
  	| aRow aButton state |
  	aRow := AlignmentMorph newRow.
  	aRow 
  		color: (Display depth <= 8 ifTrue: [Color transparent] ifFalse: [Color gray alpha: 0.2]);
  		borderWidth: 0.
  
  	aRow hResizing: #spaceFill; vResizing: #spaceFill; rubberBandCells: true.
  	aRow clipSubmorphs: true.
+ 	aRow layoutInset: 2 at 2; cellInset: 1; color: Color white.
- 	aRow layoutInset:2 at 2; cellInset: 1; color: Color white.
  	aRow wrapCentering: #center; cellPositioning: #leftCenter.
  	specArray do:
  		[:triplet |
+ 			state := triplet at: 5 ifAbsent: [#buttonState].
- 			state := triplet at: 4 ifAbsent: [#buttonState].
  			aButton := PluggableButtonMorph
  				on: self
  				getState: state
  				action: #performButtonAction:enabled:.
  			aButton
  				hResizing: #spaceFill;
  				vResizing: #spaceFill;
  				label: triplet first asString;
+ 				arguments: (Array with: triplet second with: (triplet at: 4 ifAbsent: [#buttonEnabled])); 
- 				arguments: (Array with: triplet second with: state); 
  				onColor: Color white offColor: Color white.
  			aRow addMorphBack: aButton.
  			aButton setBalloonText: triplet third].
- 
  	^ aRow!

Item was removed:
- ----- Method: MCCodeTool>>printOutMessage (in category 'menus') -----
- printOutMessage
- 	"Write a file with the text of the selected message, for printing by a web browser"
- 
- 	self selectedMessageName ifNotNil: [
- 		self selectedClassOrMetaClass fileOutMethod: self selectedMessageName
- 							asHtml: true]!



More information about the Packages mailing list