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

squeak-dev-noreply at lists.squeakfoundation.org squeak-dev-noreply at lists.squeakfoundation.org
Fri Dec 5 18:22:33 UTC 2008


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

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

Name: Monticello.impl-kph.596
Author: kph
Time: 5 December 2008, 6:22:23 pm
UUID: 37d462b1-afaa-411a-aff0-56f9ebcaf01d
Ancestors: Monticello.impl-kph.595

+ Recategorized classes for future split into modules
+ Include MonticelloConfigurations as Monticello-Configurations

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

Item was changed:
  Object subclass: #MCPasswordManager
  	instanceVariableNames: 'directory'
  	classVariableNames: 'Default'
  	poolDictionaries: ''
+ 	category: 'Monticello-Base-Repositories'!
- 	category: 'Monticello-Repositories'!
  
  !MCPasswordManager commentStamp: '<historical>' prior: 0!
  Simple password manager to avoid storing passwords in the image.!

Item was changed:
  MCVersionHistoryBrowser subclass: #MCChangeLogBrowser
  	instanceVariableNames: ''
  	classVariableNames: ''
  	poolDictionaries: ''
+ 	category: 'Monticello-UI-Browsers'!
- 	category: 'Monticello-UI'!

Item was added:
+ ----- Method: MCConfiguration>>log: (in category 'accessing') -----
+ log: aStream
+ 	log := aStream.!

Item was added:
+ ----- Method: MCConfigurationBrowser>>checkDependencies (in category 'dependencies') -----
+ checkDependencies
+ 	^self checkModified and: [self checkMissing]!

Item was changed:
  MCDirectoryRepository subclass: #MCCacheRepository
  	instanceVariableNames: 'packageCaches seenFiles'
  	classVariableNames: ''
  	poolDictionaries: ''
+ 	category: 'Monticello-Base-Repositories'!
- 	category: 'Monticello-Repositories'!
  MCCacheRepository class
  	instanceVariableNames: 'default'!

Item was changed:
  MCRepository subclass: #MCWriteOnlyRepository
  	instanceVariableNames: ''
  	classVariableNames: ''
  	poolDictionaries: ''
+ 	category: 'Monticello-Base-Repositories'!
- 	category: 'Monticello-Repositories'!

Item was added:
+ ----- Method: MCConfigurationBrowser>>upgrade (in category 'actions') -----
+ upgrade
+ 	self configuration upgrade.
+ 	self changed: #dependencyList; changed: #description
+ !

Item was changed:
  MCDefinition subclass: #MCScriptDefinition
  	instanceVariableNames: 'script packageName properties'
  	classVariableNames: ''
  	poolDictionaries: ''
+ 	category: 'Monticello-Base-Modeling'!
- 	category: 'Monticello-Modeling'!

Item was added:
+ ----- Method: MCConfiguration>>repositories (in category 'accessing') -----
+ repositories
+ 	^repositories ifNil: [repositories := OrderedCollection new]!

Item was added:
+ ----- Method: MCConfigurationBrowser>>installMenu (in category 'actions') -----
+ installMenu
+ 
+ 	| menu |
+ 	menu := MenuMorph new defaultTarget: self.
+ 	menu add: 'load packages' action: #load.
+ 	menu add: 'merge packages' action: #merge.
+ 	menu add: 'upgrade packages' action: #upgrade.
+ 	menu popUpInWorld.!

Item was added:
+ ----- Method: MCConfiguration>>log (in category 'accessing') -----
+ log
+ 	^log ifNil: [Transcript]!

Item was changed:
  MCMethodDefinition subclass: #MCMethodBeforeCommitUnloadDefinition
  	instanceVariableNames: ''
  	classVariableNames: ''
  	poolDictionaries: ''
+ 	category: 'Monticello-Base-Modeling'!
- 	category: 'Monticello-Modeling'!

Item was changed:
  MCPatchOperation subclass: #MCRemoval
  	instanceVariableNames: 'definition'
  	classVariableNames: ''
  	poolDictionaries: ''
+ 	category: 'Monticello-Base-Patching'!
- 	category: 'Monticello-Patching'!

Item was changed:
  Object subclass: #MCMergeRecord
  	instanceVariableNames: 'version packageSnapshot ancestorInfo ancestor ancestorSnapshot imagePatch mergePatch'
  	classVariableNames: ''
  	poolDictionaries: ''
+ 	category: 'Monticello-Base-Versioning'!
- 	category: 'Monticello-Versioning'!

Item was changed:
  MCVersionInspector subclass: #MCChangeLogEntry
  	instanceVariableNames: 'ancestors repository'
  	classVariableNames: ''
  	poolDictionaries: ''
+ 	category: 'Monticello-UI-Browsers'!
- 	category: 'Monticello-UI'!

Item was changed:
  MCVersionHistoryBrowser subclass: #MCWorkingHistoryBrowser
  	instanceVariableNames: ''
  	classVariableNames: ''
  	poolDictionaries: ''
+ 	category: 'Monticello-UI-Browsers'!
- 	category: 'Monticello-UI'!

Item was changed:
  MCWriter subclass: #MCStWriter
  	instanceVariableNames: 'initStream'
  	classVariableNames: ''
  	poolDictionaries: ''
+ 	category: 'Monticello-Base-Chunk Format'!
- 	category: 'Monticello-Chunk Format'!

Item was changed:
  MCDoItParser subclass: #MCClassTraitParser
  	instanceVariableNames: ''
  	classVariableNames: ''
  	poolDictionaries: ''
+ 	category: 'Monticello-Base-Chunk Format'!
- 	category: 'Monticello-Chunk Format'!

Item was changed:
  MCPatchBrowser subclass: #MCMergeBrowser
  	instanceVariableNames: 'conflicts merger ok'
  	classVariableNames: ''
  	poolDictionaries: ''
+ 	category: 'Monticello-UI-Browsers'!
- 	category: 'Monticello-UI'!

Item was added:
+ ----- Method: MCConfigurationBrowser>>index (in category 'selection') -----
+ index
+ 	^self dependencyIndex max: self repositoryIndex!

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

Item was added:
+ ----- Method: MCConfigurationBrowser>>updateIndex (in category 'selection') -----
+ updateIndex
+ 	self index > 0 ifTrue: [self index: (self index min: self maxIndex)]!

Item was added:
+ ----- Method: MCConfigurationBrowser>>selectedDependency (in category 'dependencies') -----
+ selectedDependency
+ 	^ self dependencies at: self dependencyIndex ifAbsent: []!

Item was added:
+ ----- Method: MCConfigurationBrowser>>dependencyList (in category 'dependencies') -----
+ dependencyList
+ 	^self dependencies collect: [:dep | 
+ 		Text string: dep versionInfo name
+ 			attributes: (Array streamContents: [:attr |
+ 				dep isFulfilledByAncestors
+ 					ifFalse: [attr nextPut: TextEmphasis bold]
+ 					ifTrue: [dep isCurrent ifFalse: [attr nextPut: TextEmphasis italic]].
+ 			])]
+ !

Item was changed:
  MCWriteOnlyRepository subclass: #MCSMReleaseRepository
  	instanceVariableNames: 'packageName user'
  	classVariableNames: ''
  	poolDictionaries: ''
+ 	category: 'Monticello-Base-Repositories'!
- 	category: 'Monticello-Repositories'!

Item was added:
+ ----- Method: MCConfigurationBrowser>>pickName (in category 'morphic ui') -----
+ pickName
+ 	| name |
+ 	name := FillInTheBlank
+ 		request: 'Name (.', self configuration writerClass extension, ' will be appended):'
+ 		initialAnswer: (self configuration name ifNil: ['']).
+ 	^ name isEmpty ifFalse: [name]!

Item was added:
+ ----- Method: MCConfigurationBrowser>>repositoryIndex: (in category 'selection') -----
+ repositoryIndex: anInteger
+ 	repositoryIndex := anInteger.
+ 	repositoryIndex > 0
+ 		ifTrue: [self dependencyIndex: 0].
+ 	self changed: #repositoryIndex; changed: #description.
+ 	self changedButtons.!

Item was changed:
  Object subclass: #MCPatch
  	instanceVariableNames: 'operations'
  	classVariableNames: ''
  	poolDictionaries: ''
+ 	category: 'Monticello-Base-Patching'!
- 	category: 'Monticello-Patching'!

Item was added:
+ ----- Method: MCConfiguration>>mustMerge: (in category 'private') -----
+ mustMerge: aVersion
+ 	"answer true if we have to do a full merge and false if we can simply load instead"
+ 	
+ 	| pkg wc current |
+ 	(pkg := aVersion package) hasWorkingCopy ifFalse: [^false "no wc -> load"].
+ 	(wc := pkg workingCopy) modified ifTrue: [^true "modified -> merge"].
+ 	wc ancestors isEmpty ifTrue: [^true "no ancestor info -> merge"].
+ 	current := wc ancestors first.
+ 	(aVersion info hasAncestor: current) ifTrue: [^false "direct descendant of wc -> load"].
+ 	"new branch -> merge"
+ 	^true!

Item was changed:
  MCTool subclass: #MCVersionHistoryBrowser
  	instanceVariableNames: 'ancestry index repositoryGroup package infos'
  	classVariableNames: ''
  	poolDictionaries: ''
+ 	category: 'Monticello-UI-Browsers'!
- 	category: 'Monticello-UI'!

Item was added:
+ ----- Method: MCConfiguration>>merge (in category 'actions') -----
+ merge
+ 	^self depsSatisfying: [:dep | dep isFulfilledByAncestors not]
+ 		versionDo: [:ver | ver merge]
+ 		displayingProgress: 'merging packages'
+ !

Item was changed:
  Object subclass: #MCPackageLoader1b
  	instanceVariableNames: 'requirements unloadableDefinitions obsoletions additions removals errorDefinitions provisions isUnloading isMultiplePackage'
  	classVariableNames: ''
  	poolDictionaries: ''
+ 	category: 'Monticello-Base-Loading'!
- 	category: 'Monticello-Loading'!
  
  !MCPackageLoader1b commentStamp: 'kph 5/25/2007 04:43' prior: 0!
  MCPackageLoader1b - Attempt to improve loading with a number of tricks
  
  In #basicLoad the loading process starts with a collection of definitions 
  in #additions, and another in #removals. #analyse should have sorted these so that 
  dependencies shouldnt cause errors.
  
  The load sequence sent to each addidion is: #preLoadOver: [ #install #postinstall ] #postloadOver:
  The load sequence sent to each removal is                    [ #unload ]
  
  The brackets above mark the fact that the 'load' itself which is perfromed by #install/#postinstall and #unload are performed in a tight loop and this is our attempt at atomicity.
  
  For methods, #preloadOver:, and #postloadOver: obsoletions are supplied, being the original item being overwritten.
  
  InstVar #defn is the currently loading definition. This allows error handlers to know what was being processed when the error occured.
  
  -----
  Note that to support loading this Monicello over a version which does not support atomic loading, soe things have to remain in place that are otherwise obsolete.
  
  MCDefinition-#loadOver:
  MCPackageLoader instVar's errorDefinitions, addtions, removals cant be renamed.
  !

Item was added:
+ ----- Method: MCConfiguration>>browse (in category 'actions') -----
+ browse
+ 	(MCConfigurationBrowser new configuration: self) show!

Item was changed:
  Object subclass: #MCPackageCache
  	instanceVariableNames: 'sorter fileNames'
  	classVariableNames: ''
  	poolDictionaries: ''
+ 	category: 'Monticello-Base-Repositories'!
- 	category: 'Monticello-Repositories'!

Item was added:
+ ----- Method: MCConfigurationBrowser>>buttonSpecs (in category 'morphic ui') -----
+ buttonSpecs
+ 	^ #(('Add' add 'Add a dependency')
+ 		('Update' updateMenu 'Update dependencies')
+ 		('Install' installMenu 'Load/Merge/Upgrade into image')
+ 		('Up' up 'Move item up in list' canMoveUp)
+ 		('Down' down 'Move item down in list' canMoveDown)
+ 		('Remove' remove 'Remove item' canRemove)
+ 		('Store' store 'store configuration')
+ 		('Post' post 'Post this configuration to an update stream')
+ 		)!

Item was changed:
  MCVersionSorter subclass: #MCFilteredVersionSorter
  	instanceVariableNames: 'target'
  	classVariableNames: ''
  	poolDictionaries: ''
+ 	category: 'Monticello-Base-Versioning'!
- 	category: 'Monticello-Versioning'!

Item was added:
+ ----- Method: MCConfigurationBrowser>>pickRepository (in category 'morphic ui') -----
+ pickRepository
+ 	^self pickRepositorySatisfying: [:ea | true]
+ !

Item was changed:
  Object subclass: #MCMerger
  	instanceVariableNames: 'conflicts'
  	classVariableNames: ''
  	poolDictionaries: ''
+ 	category: 'Monticello-Base-Merging'!
- 	category: 'Monticello-Merging'!

Item was added:
+ ----- Method: MCConfigurationBrowser>>checkRepositories (in category 'repositories') -----
+ checkRepositories
+ 	| bad |
+ 	bad := self repositories reject: [:repo | (repo isKindOf: MCHttpRepository) | (repo isKindOf: MCDirectoryRepository)].
+ 	^bad isEmpty or: [
+ 		self selectRepository: bad first.
+ 		self inform: (String streamContents: [:strm |
+ 			strm nextPutAll: 'Please remove these repositories:'; cr.
+ 			bad do: [:r | strm nextPutAll: r description; cr].
+ 			strm nextPutAll: '(only HTTP or Directory repositories are supported)']).
+ 		false].
+ !

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

Item was added:
+ ----- Method: MCConfigurationBrowser>>repositoryIndex (in category 'selection') -----
+ repositoryIndex
+ 	^repositoryIndex ifNil: [0]!

Item was added:
+ ----- Method: MCConfigurationBrowser>>dependencyIndex: (in category 'selection') -----
+ dependencyIndex: anInteger
+ 	dependencyIndex := anInteger.
+ 	dependencyIndex > 0
+ 		ifTrue: [self repositoryIndex: 0].
+ 	self changed: #dependencyIndex; changed: #description.
+ 	self changedButtons.!

Item was changed:
  Object subclass: #MCRepository
  	instanceVariableNames: 'creationTemplate storeDiffs'
  	classVariableNames: ''
  	poolDictionaries: ''
+ 	category: 'Monticello-Base-Repositories'!
- 	category: 'Monticello-Repositories'!
  MCRepository class
  	instanceVariableNames: 'ui'!
  
  !MCRepository commentStamp: 'kph 5/17/2007 14:31' prior: 0!
  MCRepository subclasses appear in the UI list of avaiable repository types if they return #description.!

Item was changed:
  Object subclass: #MCPatcher
  	instanceVariableNames: 'definitions'
  	classVariableNames: ''
  	poolDictionaries: ''
+ 	category: 'Monticello-Base-Patching'!
- 	category: 'Monticello-Patching'!

Item was changed:
  Exception subclass: #MCNoChangesException
  	instanceVariableNames: ''
  	classVariableNames: ''
  	poolDictionaries: ''
+ 	category: 'Monticello-Base-Versioning'!
- 	category: 'Monticello-Versioning'!

Item was changed:
  Notification subclass: #MCChangeSelectionRequest
  	instanceVariableNames: 'patch label'
  	classVariableNames: ''
  	poolDictionaries: ''
+ 	category: 'Monticello-Base-Versioning'!
- 	category: 'Monticello-Versioning'!

Item was changed:
  MCMczWriter subclass: #MCMcdWriter
  	instanceVariableNames: ''
  	classVariableNames: ''
  	poolDictionaries: ''
+ 	category: 'Monticello-Base-Storing'!
- 	category: 'Monticello-Storing'!

Item was added:
+ ----- Method: MCConfiguration class>>defaultLog: (in category 'accessing') -----
+ defaultLog: aStream
+ 	"Set the default configuration log"
+ 	DefaultLog := aStream.!

Item was changed:
  Object subclass: #MCVersionLoader
  	instanceVariableNames: 'versions'
  	classVariableNames: ''
  	poolDictionaries: ''
+ 	category: 'Monticello-Base-Loading'!
- 	category: 'Monticello-Loading'!

Item was added:
+ ----- Method: MCConfigurationBrowser>>selectDependency: (in category 'selection') -----
+ selectDependency: aDependency
+ 	self dependencyIndex: (self dependencies indexOf: aDependency)!

Item was added:
+ ----- Method: MCConfigurationBrowser>>repositories: (in category 'accessing') -----
+ repositories: aCollection
+ 	^self configuration repositories: aCollection
+ !

Item was changed:
  MCRepository subclass: #MCGOODSRepository
  	instanceVariableNames: 'hostname port connection'
  	classVariableNames: ''
  	poolDictionaries: ''
+ 	category: 'Monticello-Base-Repositories'!
- 	category: 'Monticello-Repositories'!

Item was added:
+ MCMethodDefinition subclass: #MCMethodFileReferenceDefinition
+ 	instanceVariableNames: ''
+ 	classVariableNames: ''
+ 	poolDictionaries: ''
+ 	category: 'Monticello-Files'!

Item was added:
+ ----- Method: MCConfiguration>>summary (in category 'accessing') -----
+ summary
+ 	^String streamContents: [:stream |
+ 		self dependencies
+ 			do: [:ea | stream nextPutAll: ea versionInfo name; cr ]]!

Item was changed:
  MCVersion subclass: #MCVersionVirtual
  	instanceVariableNames: ''
  	classVariableNames: ''
  	poolDictionaries: ''
+ 	category: 'Monticello-Base-Versioning'!
- 	category: 'Monticello-Versioning'!

Item was added:
+ ----- Method: MCConfiguration>>updateFromRepositories (in category 'updating') -----
+ updateFromRepositories
+ 	| oldInfos newNames sortedNames newDeps |
+ 	oldInfos := self dependencies collect: [:dep | dep versionInfo].
+ 	newNames := Dictionary new.
+ 	self repositories
+ 		do: [:repo | 
+ 			ProgressNotification signal: '' extra: 'Checking ', repo description.
+ 			(repo possiblyNewerVersionsOfAnyOf: oldInfos)
+ 				do: [:newName | newNames at: newName put: repo]]
+ 		displayingProgress: 'Searching new versions'.
+ 
+ 	sortedNames := newNames keys asSortedCollection:
+ 		[:a :b | a > b ].
+ 
+ 	newDeps := OrderedCollection new.
+ 	self dependencies do: [:dep |
+ 		| newName |
+ 		newName := sortedNames
+ 			detect: [:each | each packageName = dep versionInfo packageName]
+ 			ifNone: [nil].
+ 		newDeps add: (newName
+ 			ifNil: [dep]
+ 			ifNotNil: [
+ 				| repo ver  |
+ 				repo := newNames at: newName.
+ 				ver := self versionNamed: newName for: dep from: repo.
+ 				ver ifNil: [dep]
+ 					ifNotNil: [MCVersionDependency package: ver package info: ver info]
+ 			])
+ 	] displayingProgress: 'downloading new versions'.
+ 
+ 	self dependencies: newDeps.
+ !

Item was changed:
  MCMerger subclass: #MCThreeWayMerger
  	instanceVariableNames: 'index operations provisions redundantAdds'
  	classVariableNames: ''
  	poolDictionaries: ''
+ 	category: 'Monticello-Base-Merging'!
- 	category: 'Monticello-Merging'!

Item was changed:
  MCReader subclass: #MCSnapshotReader
  	instanceVariableNames: 'definitions'
  	classVariableNames: ''
  	poolDictionaries: ''
+ 	category: 'Monticello-Base-Storing'!
- 	category: 'Monticello-Storing'!

Item was added:
+ ----- Method: MCConfigurationBrowser>>list (in category 'selection') -----
+ list
+ 	self dependencyIndex > 0 ifTrue: [^self dependencies].
+ 	self repositoryIndex > 0 ifTrue: [^self repositories].
+ 	^#()!

Item was added:
+ Object subclass: #MCConfiguration
+ 	instanceVariableNames: 'name dependencies repositories log'
+ 	classVariableNames: 'DefaultLog'
+ 	poolDictionaries: ''
+ 	category: 'Monticello-Configurations'!

Item was added:
+ ----- Method: MCMcmReader>>summary (in category 'accessing') -----
+ summary
+ 
+ 	| s |
+ 	
+ 	s := 'Monticello Configuration: ', fileName, '
+ 
+ ', (self version summary).
+ 
+ 	stream reset.
+ 
+ 	^ s!

Item was changed:
  MCDirectoryRepository subclass: #MCSubDirectoryRepository
  	instanceVariableNames: ''
  	classVariableNames: ''
  	poolDictionaries: ''
+ 	category: 'Monticello-Base-Repositories'!
- 	category: 'Monticello-Repositories'!
  
  !MCSubDirectoryRepository commentStamp: 'nk 6/11/2004 18:56' prior: 0!
  A MCDirectoryRepository that looks in subdirectories too.!

Item was changed:
  Object subclass: #MCPackageManager
  	instanceVariableNames: 'package modified'
  	classVariableNames: ''
  	poolDictionaries: ''
+ 	category: 'Monticello-Base-Versioning'!
- 	category: 'Monticello-Versioning'!
  MCPackageManager class
  	instanceVariableNames: 'registry'!

Item was changed:
  Object subclass: #MCConflict
  	instanceVariableNames: 'operation chooseRemote'
  	classVariableNames: ''
  	poolDictionaries: ''
+ 	category: 'Monticello-Base-Merging'!
- 	category: 'Monticello-Merging'!

Item was added:
+ ----- Method: MCConfigurationBrowser>>index: (in category 'selection') -----
+ index: anInteger
+ 	self dependencyIndex > 0 ifTrue: [^self dependencyIndex: anInteger].
+ 	self repositoryIndex > 0 ifTrue: [^self repositoryIndex: anInteger].
+ 	anInteger > 0 ifTrue: [self error: 'cannot select']!

Item was changed:
  Notification subclass: #MCMergeResolutionRequest
  	instanceVariableNames: 'merger'
  	classVariableNames: ''
  	poolDictionaries: ''
+ 	category: 'Monticello-Base-Versioning'!
- 	category: 'Monticello-Versioning'!

Item was added:
+ ----- Method: MCMcmReader>>mergeVersionFrom: (in category 'accessing') -----
+ mergeVersionFrom: aRepository
+ 
+ 	self version merge!

Item was added:
+ ----- Method: MCConfigurationBrowser>>changedButtons (in category 'selection') -----
+ changedButtons
+ 	self changed: #canMoveDown.
+ 	self changed: #canMoveUp.
+ 	self changed: #canRemove.!

Item was added:
+ ----- Method: MCConfigurationBrowser>>canMoveUp (in category 'testing') -----
+ canMoveUp
+ 	^self index > 1!

Item was changed:
  MCScriptDefinition subclass: #MCRemovalPreambleDefinition
  	instanceVariableNames: ''
  	classVariableNames: ''
  	poolDictionaries: ''
+ 	category: 'Monticello-Base-Modeling'!
- 	category: 'Monticello-Modeling'!

Item was changed:
  Object subclass: #MCPackageLoader
  	instanceVariableNames: 'requirements unloadableDefinitions obsoletions additions removals errorDefinitions provisions isMultiplePackage methodAdditions'
  	classVariableNames: ''
  	poolDictionaries: ''
+ 	category: 'Monticello-Base-Loading'!
- 	category: 'Monticello-Loading'!
  
  !MCPackageLoader commentStamp: 'kph 5/26/2007 04:22' prior: 0!
  This loader is the old MC1 code essentially untouched, thoug this class is now obsolete.
  
  This is kept here so that when loading this new version of mc into a system with an older version of mc it is running this code and so we do not wish to disturb it. 
  
  In loading this version, the class #new method is updated to switch future instanciations to the new package loader, this old one being obsolete.
  
  This loader remains potentially usable but does not know about the orphanage. #installOrphanage is implemented here as a unused noop, just in case someone wants to revert to using this loader.
  
  
  
  !

Item was added:
+ MCWriter subclass: #MCMcmWriter
+ 	instanceVariableNames: ''
+ 	classVariableNames: ''
+ 	poolDictionaries: ''
+ 	category: 'Monticello-Configurations'!

Item was changed:
  SystemOrganization addCategory: #'Monticello-Base'!
+ SystemOrganization addCategory: #'Monticello-Base-Chunk Format'!
+ SystemOrganization addCategory: #'Monticello-Base-Loading'!
+ SystemOrganization addCategory: #'Monticello-Base-Merging'!
+ SystemOrganization addCategory: #'Monticello-Base-Modeling'!
- SystemOrganization addCategory: #'Monticello-Chunk Format'!
- SystemOrganization addCategory: #'Monticello-Loading'!
- SystemOrganization addCategory: #'Monticello-Merging'!
- SystemOrganization addCategory: #'Monticello-Modeling'!
  SystemOrganization addCategory: #'Monticello-Orphanage'!
+ SystemOrganization addCategory: #'Monticello-Base-Patching'!
+ SystemOrganization addCategory: #'Monticello-Base-Repositories'!
+ SystemOrganization addCategory: #'Monticello-Base-Storing'!
+ SystemOrganization addCategory: #'Monticello-UI-Repository'!
+ SystemOrganization addCategory: #'Monticello-Base-Versioning'!
+ SystemOrganization addCategory: #'Monticello-Files'!
+ SystemOrganization addCategory: #'Monticello-Configurations'!
+ SystemOrganization addCategory: #'Monticello-UI-Browsers'!
- SystemOrganization addCategory: #'Monticello-Patching'!
- SystemOrganization addCategory: #'Monticello-Repositories'!
- SystemOrganization addCategory: #'Monticello-Storing'!
  SystemOrganization addCategory: #'Monticello-UI'!
- SystemOrganization addCategory: #'Monticello-Versioning'!

Item was changed:
  MCReader subclass: #MCVersionReader
  	instanceVariableNames: 'package info definitions dependencies stepChildren'
  	classVariableNames: ''
  	poolDictionaries: ''
+ 	category: 'Monticello-Base-Storing'!
- 	category: 'Monticello-Storing'!

Item was added:
+ ----- Method: MCConfigurationBrowser>>updateFromImage (in category 'updating') -----
+ updateFromImage
+ 	self configuration updateFromImage.
+ 	self changed: #dependencyList; changed: #description
+ !

Item was added:
+ ----- Method: MCConfiguration>>load (in category 'actions') -----
+ load
+ 	^self depsSatisfying: [:dep | dep isCurrent not]
+ 		versionDo: [:ver | ver load]
+ 		displayingProgress: 'loading packages'
+ !

Item was added:
+ MCTool subclass: #MCConfigurationBrowser
+ 	instanceVariableNames: 'configuration dependencyIndex repositoryIndex'
+ 	classVariableNames: ''
+ 	poolDictionaries: ''
+ 	category: 'Monticello-Configurations'!

Item was changed:
  MCStReader subclass: #MCCsReader
  	instanceVariableNames: ''
  	classVariableNames: ''
  	poolDictionaries: ''
+ 	category: 'Monticello-Base-Chunk Format'!
- 	category: 'Monticello-Chunk Format'!
  
  !MCCsReader commentStamp: 'abc 7/4/2007 01:25' prior: 0!
  In order to designate a changeset for loading with Monticello use the extension .mcs 
  Monticello does not execute preambles or postscripts.!

Item was changed:
  MCRepository subclass: #MCFileBasedRepository
  	instanceVariableNames: 'cache allFileNames heldVersionInfos'
  	classVariableNames: ''
  	poolDictionaries: ''
+ 	category: 'Monticello-Base-Repositories'!
- 	category: 'Monticello-Repositories'!
  
  !MCFileBasedRepository commentStamp: 'kph 5/17/2007 04:42' prior: 0!
  For the FileBased repository we use versionInfo's as before, 
  but they are based on only what info we can obtain from the file system and fileName.
   
  We are using instances of MCVersionInfo to represent fileNames in order that the UI
  doesnt see anything special about a file based repository. 
  This saves us special UI implementations for File based repositories."
  	!

Item was added:
+ ----- Method: MCConfigurationBrowser>>post (in category 'actions') -----
+ post
+ 	"Take the current configuration and post an update"
+ 	| name update managers names choice |
+ 	(self checkRepositories and: [self checkDependencies]) ifFalse: [^self].
+ 	name := FillInTheBlank
+ 		request: 'Update name (.cs) will be appended):'
+ 		initialAnswer: (self configuration name ifNil: ['']).
+ 	name isEmpty ifTrue:[^self].
+ 	self configuration name: name.
+ 	update := MCPseudoFileStream on: (String new: 100).
+ 	update localName: name, '.cs'.
+ 	update nextPutAll: '"Change Set:		', name.
+ 	update cr; nextPutAll: 'Date:			', Date today printString.
+ 	update cr; nextPutAll: 'Author:			Posted by Monticello'.
+ 	update cr; cr; nextPutAll: 'This is a configuration map created by Monticello."'.
+ 
+ 	update cr; cr; nextPutAll: '(MCConfiguration fromArray: #'.
+ 	self configuration fileOutOn: update.
+ 	update nextPutAll: ') upgrade.'.
+ 	update position: 0.
+ 
+ 	managers := Smalltalk at: #UpdateManager ifPresent:[:mgr| mgr allRegisteredManagers].
+ 	managers ifNil:[managers := #()].
+ 	managers size > 0 ifTrue:[
+ 		| servers index |
+ 		servers := ServerDirectory groupNames asSortedArray.
+ 		names := (managers collect:[:each| each packageVersion]), servers.
+ 		index := UIManager default chooseFrom: names lines: {managers size}.
+ 		index = 0 ifTrue:[^self].
+ 		index <= managers size ifTrue:[
+ 			| mgr |
+ 			mgr := managers at: index.
+ 			^mgr publishUpdate: update.
+ 		].
+ 		choice := names at: index.
+ 	] ifFalse:[
+ 		names := ServerDirectory groupNames asSortedArray.
+ 		choice := (SelectionMenu labelList: names selections: names) startUp.
+ 		choice == nil ifTrue: [^ self].
+ 	].
+ 	(ServerDirectory serverInGroupNamed: choice) putUpdate: update.!

Item was added:
+ ----- Method: MCMcmWriter class>>fileOut:on: (in category 'writing') -----
+ fileOut: aConfiguration on: aStream
+ 	| inst |
+ 	inst := self on: aStream.
+ 	inst writeConfiguration: aConfiguration.
+ 	inst close.
+ 	
+ !

Item was added:
+ ----- Method: MCConfiguration>>name: (in category 'accessing') -----
+ name: aString
+ 
+ 	(aString endsWith: self writerClass extension) 
+ 		ifTrue: [ ^ name := aString allButLast: self writerClass extension size + 1 ].
+ 	name := aString!

Item was changed:
  Object subclass: #MCDependencySorter
  	instanceVariableNames: 'required provided orderedItems'
  	classVariableNames: ''
  	poolDictionaries: ''
+ 	category: 'Monticello-Base-Loading'!
- 	category: 'Monticello-Loading'!
  
  !MCDependencySorter commentStamp: 'kph 5/3/2007 18:46' prior: 0!
  MCDependencySorter
  
     * #orderedItems     has an OrderedCollection of the item Definitions that have
                     all of their requirements when added.
     * #required         A dictionary of Sets, keyed on the 'required' item, the Set
                     containing the items which require that item
     * #provided         A set of provided items, i.e. those which might be required.
  
  As each item is added using #add, or #addAll, it obtains the items requirements, subtracting those items which it already has listed as #provided. Items with all of their requirements are added to the #orderedItems. In doing so each of those items is added to the #provided set. When adding to the provided set, a check is made in the #required items to see if the newly provided item is required. If so, it is cleared out of the required list and those items that were waiting for that requirement are then added via #add:/#addAll:
  
  Finally you have:
  
     * #orderedItems                         - the collection of items which should load.
     * #itemsWithMissingRequirements     - the collection of items that will not yet load.
     * #externalRequirements             - the list of requirements still needed after
                                           all the internal provisions are accounted for.
  
  
  Typical use (e.g. MCPackageLoader-#analyse) is to instantiate via #items, which adds all of the items and sorts them as they are added. Then calling #addExternalProvisions: with the set of class keys avalable in the image. This gives the ready to load result.
  
  The #sortItems: instanciation method sorts the items as above, it assumes that all of the #externalProvisions are available so as to get the complete sorted order. This is used when writing the definitions.
  !

Item was added:
+ ----- Method: MCConfigurationBrowser>>pickRepositorySatisfying: (in category 'morphic ui') -----
+ pickRepositorySatisfying: aBlock
+ 	| index list |
+ 	list := MCRepositoryGroup default repositories select: aBlock.
+ 	index := (PopUpMenu labelArray: (list collect: [:ea | ea description]))
+ 		startUpWithCaption: 'Repository:'.
+ 	^ index = 0 ifFalse: [list at: index]!

Item was added:
+ ----- Method: MCConfigurationBrowser>>addDependency (in category 'dependencies') -----
+ addDependency
+ 	(self pickWorkingCopiesSatisfying: [:each | (self includesPackage: each package) not])
+ 		do: [:wc |
+ 			wc ancestors isEmpty
+ 				ifTrue: [self inform: 'You must save ', wc packageName, ' first!!
+ Skipping this package']
+ 				ifFalse: [
+ 					self dependencies add: (MCVersionDependency
+ 						package: wc package
+ 						info: wc ancestors first)]].
+ 	self changed: #dependencyList; changed: #description!

Item was changed:
  MCFileBasedRepository subclass: #MCFtpRepository
  	instanceVariableNames: 'host directory user connection'
  	classVariableNames: ''
  	poolDictionaries: ''
+ 	category: 'Monticello-Base-Repositories'!
- 	category: 'Monticello-Repositories'!

Item was changed:
  MCFileBasedRepository subclass: #MCDirectoryRepository
  	instanceVariableNames: 'directory'
  	classVariableNames: ''
  	poolDictionaries: ''
+ 	category: 'Monticello-Base-Repositories'!
- 	category: 'Monticello-Repositories'!

Item was changed:
  MCScriptDefinition subclass: #MCRemovalPostscriptDefinition
  	instanceVariableNames: ''
  	classVariableNames: ''
  	poolDictionaries: ''
+ 	category: 'Monticello-Base-Modeling'!
- 	category: 'Monticello-Modeling'!

Item was changed:
  Object subclass: #MCFrontier
  	instanceVariableNames: 'frontier bag'
  	classVariableNames: ''
  	poolDictionaries: ''
+ 	category: 'Monticello-Base-Versioning'!
- 	category: 'Monticello-Versioning'!

Item was changed:
  MCVersionInfo subclass: #MCSystemChangeSetVersionInfo
  	instanceVariableNames: 'csName'
  	classVariableNames: ''
  	poolDictionaries: ''
+ 	category: 'Monticello-Base-Versioning'!
- 	category: 'Monticello-Versioning'!

Item was changed:
  MCDefinition subclass: #MCClassTraitDefinition
  	instanceVariableNames: 'baseTrait classTraitComposition properties'
  	classVariableNames: ''
  	poolDictionaries: ''
+ 	category: 'Monticello-Base-Modeling'!
- 	category: 'Monticello-Modeling'!

Item was added:
+ ----- Method: MCConfigurationBrowser>>pickWorkingCopiesSatisfying: (in category 'morphic ui') -----
+ pickWorkingCopiesSatisfying: aBlock
+ 	| copies item |
+ 	copies := (MCWorkingCopy allManagers select: aBlock)
+ 		asSortedCollection: [:a :b | a packageName <= b packageName].
+ 	item := (PopUpMenu labelArray: #('match ...'),(copies collect: [:ea | ea packageName]) lines: #(1))
+ 				startUpWithCaption: 'Package:'.
+ 	item = 1 ifTrue: [
+ 		| pattern |
+ 		pattern := FillInTheBlank request: 'Packages matching:' initialAnswer: '*'.
+ 		^pattern isEmptyOrNil
+ 			ifTrue: [#()]
+ 			ifFalse: [
+ 				(pattern includes: $*) ifFalse: [pattern := '*', pattern, '*'].
+ 				copies select: [:ea | pattern match: ea packageName]]
+ 	].
+ 	^ item = 0
+ 		ifTrue: [#()]
+ 		ifFalse: [{copies at: item - 1}]!

Item was added:
+ ----- Method: MCConfiguration class>>fromArray: (in category 'instance creation') -----
+ fromArray: anArray
+ 	| configuration |
+ 	configuration := self new.
+ 	anArray pairsDo: [:key :value |
+ 		key = #repository
+ 			ifTrue: [configuration repositories add: (self repositoryFromArray: value)].
+ 		key = #dependency
+ 			ifTrue: [configuration dependencies add: (self dependencyFromArray: value)].
+ 	].
+ 	^configuration!

Item was added:
+ ----- Method: MCConfiguration class>>seeIfRelativeDirectory: (in category 'converting') -----
+ seeIfRelativeDirectory: aPath 
+ 	| possiblePath |
+ 	possiblePath := FileDirectory
+ 				on: (FileDirectory default fullNameFor: aPath).
+ 	^ possiblePath exists
+ 		ifTrue: [MCDirectoryRepository new directory: possiblePath]
+ 		ifFalse: [ nil ]!

Item was added:
+ ----- Method: MCConfiguration>>upgrade (in category 'actions') -----
+ upgrade
+ 	^self depsSatisfying: [:dep | dep isFulfilledByAncestors not]
+ 		versionDo: [:ver | 
+ 			(Preferences upgradeIsMerge and: [self mustMerge: ver])
+ 				ifFalse: [ver load]
+ 				ifTrue: [[ver merge]
+ 					on: MCMergeResolutionRequest do: [:request |
+ 						request merger conflicts isEmpty
+ 							ifTrue: [request resume: true]
+ 							ifFalse: [request pass]]]]
+ 		displayingProgress: 'upgrading packages'
+ !

Item was added:
+ ----- Method: MCConfigurationBrowser>>store (in category 'actions') -----
+ store
+ 	(self checkRepositories and: [self checkDependencies]) ifFalse: [^self].
+ 	self pickName ifNotNilDo: [:name |
+ 		self configuration name: name.
+ 		self pickRepository ifNotNilDo: [:repo |
+ 			repo storeVersion: self configuration]].!

Item was changed:
  MCAncestry subclass: #MCVersionInfo
  	instanceVariableNames: 'id name message date time author version dotPos'
  	classVariableNames: ''
  	poolDictionaries: ''
+ 	category: 'Monticello-Base-Versioning'!
- 	category: 'Monticello-Versioning'!
  
  !MCVersionInfo commentStamp: 'kph 6/2/2008 14:11' prior: 0!
  I am used as a handle for the UI to reference persisted versions and to obtain the relationships between versions.
  
  Some repositories only supply a filename as an initial handle, and so to realise the
  full data from the repository, use #realizeFrom: aRepository
  
  Adds to the record of ancestry, other identifying details.
  
  Names:
  
  The defining point in the name is the 'firstDot' after the first $- (i.e. in some cases it may not actually be the first dot overall), all parts in the name are parsed relative to this. My-Package-kph.234.mcz is split into 'My-Package-kph' and '234.mcz' first. 
  The #namePreFirstDot is split on the last $- to obtain the packgeName/author.
   
  The version is obtained upTo the last $( or $. in the second #postFirstDot portion,  this may be a uuid or, it may even contain $. as in traditional version numbering schemes. 
    
  VersionInfo does not have any notion of a file extn, whereas VersionInfoFilename does, and this is taken to be everything after the last $. 
  
  PackageName - any characters including $- .
  Author - any characters except $- or $.
  Version - any characters including $- or $.
  
  Any older packages which have $- in the author/version suffix must be renamed
  
  UUID's are valid versionnumbers if $- is replcaed by $.!

Item was changed:
  Object subclass: #MCDoItParser
  	instanceVariableNames: 'source'
  	classVariableNames: ''
  	poolDictionaries: ''
+ 	category: 'Monticello-Base-Chunk Format'!
- 	category: 'Monticello-Chunk Format'!

Item was changed:
  MCDoItParser subclass: #MCTraitParser
  	instanceVariableNames: ''
  	classVariableNames: ''
  	poolDictionaries: ''
+ 	category: 'Monticello-Base-Chunk Format'!
- 	category: 'Monticello-Chunk Format'!

Item was added:
+ ----- Method: MCConfigurationBrowser>>checkModified (in category 'dependencies') -----
+ checkModified
+ 	| modified |
+ 	modified := self dependencies select: [:dep |
+ 		dep isFulfilled and: [dep package workingCopy modified]].
+ 	
+ 	^modified isEmpty or: [
+ 		self selectDependency: modified anyOne.
+ 		self confirm: (String streamContents: [:strm |
+ 			strm nextPutAll: 'These packages are modified:'; cr.
+ 			modified do: [:dep | strm nextPutAll: dep package name; cr].
+ 			strm nextPutAll: 'Do you still want to store?'])]
+ 	!

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

Item was changed:
  MCVersionVirtual subclass: #MCSystemChangeSetVersion
  	instanceVariableNames: ''
  	classVariableNames: ''
  	poolDictionaries: ''
+ 	category: 'Monticello-Base-Versioning'!
- 	category: 'Monticello-Versioning'!

Item was changed:
  MCVariableDefinition subclass: #MCPoolImportDefinition
  	instanceVariableNames: ''
  	classVariableNames: ''
  	poolDictionaries: ''
+ 	category: 'Monticello-Base-Modeling'!
- 	category: 'Monticello-Modeling'!

Item was added:
+ ----- Method: MCConfigurationBrowser>>add (in category 'actions') -----
+ add
+ 	(self pickWorkingCopiesSatisfying: [:each | (self includesPackage: each package) not])
+ 		do: [:wc |
+ 			wc ancestors isEmpty
+ 				ifTrue: [self inform: 'You must save ', wc packageName, ' first!!
+ Skipping this package']
+ 				ifFalse: [
+ 					self dependencies add: (MCVersionDependency
+ 						package: wc package
+ 						info: wc ancestors first)]].
+ 	self changed: #dependencyList; changed: #description!

Item was added:
+ ----- Method: MCConfigurationBrowser class>>open (in category 'opening') -----
+ open
+ 	^self new show!

Item was changed:
  Object subclass: #MCVersionDependency
  	instanceVariableNames: 'package versionInfo'
  	classVariableNames: ''
  	poolDictionaries: ''
+ 	category: 'Monticello-Base-Versioning'!
- 	category: 'Monticello-Versioning'!

Item was changed:
  MCFileBasedRepository subclass: #MCSMCacheRepository
  	instanceVariableNames: 'smCache'
  	classVariableNames: ''
  	poolDictionaries: ''
+ 	category: 'Monticello-Base-Repositories'!
- 	category: 'Monticello-Repositories'!
  
  !MCSMCacheRepository commentStamp: 'nk 1/23/2004 09:57' prior: 0!
  I am a Monticello repository that reflects the caching of SqueakMap v2.
  
  I refer write attempts to the default MCCacheRepository.!

Item was changed:
  MCWriter subclass: #MCVersionInfoWriter
  	instanceVariableNames: 'written'
  	classVariableNames: ''
  	poolDictionaries: ''
+ 	category: 'Monticello-Base-Storing'!
- 	category: 'Monticello-Storing'!

Item was changed:
  MCDictionaryRepository subclass: #MCSystemChangeSetsRepository
  	instanceVariableNames: ''
  	classVariableNames: ''
  	poolDictionaries: ''
+ 	category: 'Monticello-Base-Repositories'!
- 	category: 'Monticello-Repositories'!

Item was changed:
  MCVersionInspector subclass: #MCRepositoryVersionsInspector
  	instanceVariableNames: 'loaded loadedNames inheritedNames newer inherited latest repository versionInfos selectedVersionInfo order'
  	classVariableNames: 'Order'
  	poolDictionaries: ''
+ 	category: 'Monticello-UI-Repository'!
- 	category: 'Monticello-UI'!
  MCRepositoryVersionsInspector class
  	instanceVariableNames: 'loaded'!
  
  !MCRepositoryVersionsInspector commentStamp: 'kph 5/16/2007 23:22' prior: 0!
  Customize the MCVersionInspector to show a list of versions from a repository.!

Item was added:
+ ----- Method: MCConfigurationBrowser>>dependencies: (in category 'accessing') -----
+ dependencies: aCollection
+ 	self configuration dependencies: aCollection.
+ 	self changed: #dependencyList; changed: #description
+ !

Item was added:
+ ----- Method: MCConfigurationBrowser>>loadMenu (in category 'actions') -----
+ loadMenu
+ 
+ 	| menu |
+ 	menu := MenuMorph new defaultTarget: self.
+ 	menu add: 'update from image' action: #updateFromImage.
+ 	menu add: 'update from repositories' action: #updateFromRepositories.
+ 	menu popUpInWorld.
+ !

Item was added:
+ ----- Method: MCConfiguration>>logWarning: (in category 'private') -----
+ logWarning: aString
+ 	self log
+ 		cr; nextPutAll: 'WARNING: ';
+ 		nextPutAll: aString; cr;
+ 		flush.
+ !

Item was added:
+ ----- Method: MCConfiguration class>>defaultLog (in category 'accessing') -----
+ defaultLog
+ 	"Answer the default configuration log"
+ 	^DefaultLog!

Item was added:
+ ----- Method: MCMcmWriter class>>readerClass (in category 'accessing') -----
+ readerClass
+ 	^ MCMcmReader!

Item was added:
+ ----- Method: MCMcmReader>>loadVersionFrom: (in category 'accessing') -----
+ loadVersionFrom: aRepository
+ 
+ 	self version load!

Item was changed:
  MCMethodDefinition subclass: #MCMethodBeforeCommitLoadDefinition
  	instanceVariableNames: ''
  	classVariableNames: ''
  	poolDictionaries: ''
+ 	category: 'Monticello-Base-Modeling'!
- 	category: 'Monticello-Modeling'!
  
  !MCMethodBeforeCommitLoadDefinition commentStamp: 'kph 5/30/2007 16:20' prior: 0!
  MCMethodSpecialActionDefinition
  
   !

Item was changed:
  Object subclass: #MCWriter
  	instanceVariableNames: 'stream'
  	classVariableNames: ''
  	poolDictionaries: ''
+ 	category: 'Monticello-Base-Storing'!
- 	category: 'Monticello-Storing'!

Item was added:
+ ----- Method: MCConfiguration>>repositories: (in category 'accessing') -----
+ repositories: aCollection
+ 	repositories := aCollection!

Item was changed:
  MCPatchOperation subclass: #MCAddition
  	instanceVariableNames: 'definition'
  	classVariableNames: ''
  	poolDictionaries: ''
+ 	category: 'Monticello-Base-Patching'!
- 	category: 'Monticello-Patching'!

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

Item was added:
+ ----- Method: MCConfiguration class>>repositoryToArray: (in category 'converting') -----
+ repositoryToArray: aRepository
+ 	^ {aRepository description}!

Item was changed:
  MCFileBasedRepository subclass: #MCHttpRepository
  	instanceVariableNames: 'location user readerCache'
  	classVariableNames: ''
  	poolDictionaries: ''
+ 	category: 'Monticello-Base-Repositories'!
- 	category: 'Monticello-Repositories'!

Item was added:
+ ----- Method: MCConfigurationBrowser class>>initialize (in category 'class initialization') -----
+ initialize
+ 	TheWorldMenu registerOpenCommand: { 'Monticello Configurations' . { self . #open }. 'Monticello Configuration Browser' }.!

Item was changed:
  MCDefinition subclass: #MCOrganizationDefinition
  	instanceVariableNames: 'categories properties'
  	classVariableNames: ''
  	poolDictionaries: ''
+ 	category: 'Monticello-Base-Modeling'!
- 	category: 'Monticello-Modeling'!

Item was changed:
  MCMethodDefinition subclass: #MCMethodUnloaderDefinition
  	instanceVariableNames: ''
  	classVariableNames: ''
  	poolDictionaries: ''
+ 	category: 'Monticello-Base-Modeling'!
- 	category: 'Monticello-Modeling'!

Item was changed:
  MCRepositoryVersionsInspector subclass: #MCDictionaryRepositoryInspector
  	instanceVariableNames: 'repositories'
  	classVariableNames: ''
  	poolDictionaries: ''
+ 	category: 'Monticello-UI-Repository'!
- 	category: 'Monticello-UI'!

Item was changed:
  MCSnapshotReader subclass: #MCStReader
  	instanceVariableNames: ''
  	classVariableNames: ''
  	poolDictionaries: ''
+ 	category: 'Monticello-Base-Chunk Format'!
- 	category: 'Monticello-Chunk Format'!

Item was added:
+ ----- Method: MCConfigurationBrowser>>maxIndex (in category 'selection') -----
+ maxIndex
+ 	^ self list size!

Item was added:
+ ----- Method: MCMcmReader>>fileName: (in category 'accessing') -----
+ fileName: aString
+ 	fileName := aString!

Item was changed:
  MCVersionVirtual subclass: #MCCSVersion
  	instanceVariableNames: ''
  	classVariableNames: ''
  	poolDictionaries: ''
+ 	category: 'Monticello-Base-Versioning'!
- 	category: 'Monticello-Versioning'!

Item was added:
+ ----- Method: MCConfiguration class>>repositoryFromArray: (in category 'converting') -----
+ repositoryFromArray: anArray 
+ 	^ MCRepositoryGroup default repositories
+ 		detect: [:repo | repo description = anArray first]
+ 		ifNone: [(self seeIfRelativeDirectory: anArray first)
+ 				ifNil: [MCHttpRepository
+ 						location: anArray first
+ 						user: ''
+ 						password: '']]!

Item was added:
+ ----- Method: MCConfigurationBrowser>>selectedPackage (in category 'dependencies') -----
+ selectedPackage
+ 	^ self selectedDependency ifNotNilDo: [:dep | dep package]!

Item was changed:
  Object subclass: #MCScanner
  	instanceVariableNames: 'stream'
  	classVariableNames: ''
  	poolDictionaries: ''
+ 	category: 'Monticello-Base-Chunk Format'!
- 	category: 'Monticello-Chunk Format'!

Item was changed:
  ----- Method: MCUnlinkedClassDefinition>>category (in category 'as yet unclassified') -----
  category
  
+ 	^( self actualClass ifNil: [ ^ '' ])category ifNil: [ '' ]!
- 	^ self actualClass category ifNil: [ '' ]!

Item was changed:
  MCMethodDefinition subclass: #MCMethodAfterRemovalActionDefinition
  	instanceVariableNames: ''
  	classVariableNames: ''
  	poolDictionaries: ''
+ 	category: 'Monticello-Base-Modeling'!
- 	category: 'Monticello-Modeling'!

Item was changed:
  MCMethodDefinition subclass: #MCMethodExternalFieldDefinition
  	instanceVariableNames: ''
  	classVariableNames: ''
  	poolDictionaries: ''
+ 	category: 'Monticello-Base-Modeling'!
- 	category: 'Monticello-Modeling'!

Item was changed:
  MCClassDefinition subclass: #MCTraitDefinition
  	instanceVariableNames: ''
  	classVariableNames: ''
  	poolDictionaries: ''
+ 	category: 'Monticello-Base-Modeling'!
- 	category: 'Monticello-Modeling'!

Item was changed:
  Object subclass: #MCVersionNotification
  	instanceVariableNames: 'version ancestor repository changes'
  	classVariableNames: ''
  	poolDictionaries: ''
+ 	category: 'Monticello-Base-Repositories'!
- 	category: 'Monticello-Repositories'!

Item was added:
+ ----- Method: MCConfigurationBrowser>>dependencies (in category 'accessing') -----
+ dependencies
+ 	^self configuration dependencies
+ !

Item was added:
+ ----- Method: MCConfiguration>>logUpdate:with: (in category 'private') -----
+ logUpdate: aPackage with: aVersion
+ 	self log
+ 		cr; nextPutAll: '========== ', aVersion info name, ' =========='; cr;
+ 		cr; nextPutAll: aVersion info message asString; cr;
+ 		flush.
+ 
+ 	aPackage hasWorkingCopy ifFalse: [^self].
+ 
+ 	aPackage workingCopy ancestors do: [:each |
+ 		(aVersion info hasAncestor: each)
+ 			ifTrue: [(aVersion info allAncestorsOnPathTo: each)
+ 				do: [:ver | self log cr; nextPutAll: '>>> ', ver name, ' <<<'; cr;
+ 							nextPutAll: ver message; cr; flush]]]!

Item was changed:
  MCRepositoryVersionsInspector subclass: #MCRepositoryDualVersionsInspector
  	instanceVariableNames: 'repository2 versionInfos2 selectedVersionInfo2 order2 centerPanelModel thePatch'
  	classVariableNames: ''
  	poolDictionaries: ''
+ 	category: 'Monticello-UI-Repository'!
- 	category: 'Monticello-UI'!
  
  !MCRepositoryDualVersionsInspector commentStamp: 'kph 6/4/2008 14:42' prior: 0!
  Known Issues
  
  Some crosstalk between the two versions list... very mystifying!

Item was changed:
  MCScriptDefinition subclass: #MCPreambleDefinition
  	instanceVariableNames: ''
  	classVariableNames: ''
  	poolDictionaries: ''
+ 	category: 'Monticello-Base-Modeling'!
- 	category: 'Monticello-Modeling'!

Item was added:
+ ----- Method: MCConfiguration>>updateFromImage (in category 'updating') -----
+ updateFromImage
+ 	self dependencies: (self dependencies collect: [:dep |
+ 		dep package hasWorkingCopy
+ 			ifTrue: [
+ 				dep package workingCopy in: [:wc |
+ 					MCVersionDependency package: wc package info: wc ancestors first]]
+ 			ifFalse: [dep]]).
+ !

Item was added:
+ ----- Method: MCConfiguration>>isCacheable (in category 'testing') -----
+ isCacheable
+ 	^false!

Item was added:
+ ----- Method: MCConfiguration class>>dependencyToArray: (in category 'converting') -----
+ dependencyToArray: aDependency
+ 	^ {
+ 		aDependency package name . 
+ 		aDependency versionInfo name . 
+ 		aDependency versionInfo id asString }!

Item was added:
+ ----- Method: MCMcmReader>>configurationName (in category 'accessing') -----
+ configurationName
+ 	^fileName ifNotNil: [(fileName findTokens: '/\:') last copyUpToLast: $.]!

Item was changed:
  MCDefinitionIndex subclass: #MCImageBackedDefinitionIndex
  	instanceVariableNames: ''
  	classVariableNames: ''
  	poolDictionaries: ''
+ 	category: 'Monticello-Base-Patching'!
- 	category: 'Monticello-Patching'!
  
  !MCImageBackedDefinitionIndex commentStamp: '<historical>' prior: 0!
  When using definitionLike: ... I go to the image before giving up!

Item was changed:
  Object subclass: #MCVersion
  	instanceVariableNames: 'package info snapshot dependencies'
  	classVariableNames: ''
  	poolDictionaries: ''
+ 	category: 'Monticello-Base-Versioning'!
- 	category: 'Monticello-Versioning'!

Item was added:
+ ----- Method: MCConfigurationBrowser>>dependencyMenu: (in category 'morphic ui') -----
+ dependencyMenu: aMenu
+ 	self fillMenu: aMenu fromSpecs: #(('add dependency...' addDependency)).
+ 	self selectedDependency ifNotNil: [
+ 		self fillMenu: aMenu fromSpecs: #(('remove dependency...' remove))].
+ 	^aMenu
+ !

Item was changed:
  MCWriteOnlyRepository subclass: #MCSmtpRepository
  	instanceVariableNames: 'email'
  	classVariableNames: ''
  	poolDictionaries: ''
+ 	category: 'Monticello-Base-Repositories'!
- 	category: 'Monticello-Repositories'!

Item was changed:
  MCMczReader subclass: #MCMcdReader
  	instanceVariableNames: 'baseInfo patch'
  	classVariableNames: ''
  	poolDictionaries: ''
+ 	category: 'Monticello-Base-Storing'!
- 	category: 'Monticello-Storing'!

Item was changed:
  Object subclass: #MCPatchOperation
  	instanceVariableNames: ''
  	classVariableNames: ''
  	poolDictionaries: ''
+ 	category: 'Monticello-Base-Patching'!
- 	category: 'Monticello-Patching'!

Item was changed:
  MCVersion subclass: #MCDiffyVersion
  	instanceVariableNames: 'base patch'
  	classVariableNames: ''
  	poolDictionaries: ''
+ 	category: 'Monticello-Base-Versioning'!
- 	category: 'Monticello-Versioning'!

Item was added:
+ ----- Method: MCPseudoFileStream>>localName: (in category 'accessing') -----
+ localName: aString
+ 	localName := aString!

Item was changed:
  MCVariableDefinition subclass: #MCClassVariableDefinition
  	instanceVariableNames: ''
  	classVariableNames: ''
  	poolDictionaries: ''
+ 	category: 'Monticello-Base-Modeling'!
- 	category: 'Monticello-Modeling'!

Item was added:
+ ----- Method: MCConfigurationBrowser>>selectedRepository (in category 'repositories') -----
+ selectedRepository
+ 	^ self repositories at: self repositoryIndex ifAbsent: []!

Item was changed:
  MCVariableDefinition subclass: #MCInstanceVariableDefinition
  	instanceVariableNames: ''
  	classVariableNames: ''
  	poolDictionaries: ''
+ 	category: 'Monticello-Base-Modeling'!
- 	category: 'Monticello-Modeling'!

Item was added:
+ ----- Method: MCMcmWriter>>writeConfiguration: (in category 'writing') -----
+ writeConfiguration: aConfiguration
+ 
+ 	stream nextPut: $(.
+ 
+ 	aConfiguration repositories do: [:ea | 
+ 		stream cr.
+ 		stream nextPutAll: 'repository '.
+ 		(MCConfiguration repositoryToArray: ea) printElementsOn: stream].
+ 
+ 	aConfiguration dependencies do: [:ea | 
+ 		stream cr.
+ 		stream nextPutAll: 'dependency '.
+ 		(MCConfiguration dependencyToArray: ea) printElementsOn: stream].
+ 
+ 	stream cr.
+ 	stream nextPut: $).
+ 	stream cr.!

Item was changed:
  MCCodeTool subclass: #MCSnapshotBrowser
  	instanceVariableNames: 'categorySelection classSelection protocolSelection methodSelection switch'
  	classVariableNames: ''
  	poolDictionaries: ''
+ 	category: 'Monticello-UI-Browsers'!
- 	category: 'Monticello-UI'!

Item was changed:
  Object subclass: #MCRepositoryGroup
  	instanceVariableNames: 'repositories useCache'
  	classVariableNames: ''
  	poolDictionaries: ''
+ 	category: 'Monticello-Base-Versioning'!
- 	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 changed:
  Object subclass: #MCPackageLoader2
  	instanceVariableNames: 'editor requirements unloadableDefinitions obsoletions additions removals errorDefinitions provisions isUnloading isMultiplePackage'
  	classVariableNames: ''
  	poolDictionaries: ''
+ 	category: 'Monticello-Base-Loading'!
- 	category: 'Monticello-Loading'!
  
  !MCPackageLoader2 commentStamp: 'kph 5/26/2007 09:32' prior: 0!
  MCPackageLoader2
  
  ProgressBar has great improvements.
  
  #setProgressBar: is used for clients to control how progress is displayed.
  
  If no one indicates a preference we display our own progress bar.
  Otherwise we use the one passed to us.
  
  To not have any progress bar displayed give us an empty block.
  #setProgressBar: [:v |  ] !

Item was changed:
  MCVariableDefinition subclass: #MCClassInstanceVariableDefinition
  	instanceVariableNames: ''
  	classVariableNames: ''
  	poolDictionaries: ''
+ 	category: 'Monticello-Base-Modeling'!
- 	category: 'Monticello-Modeling'!

Item was added:
+ ----- Method: MCConfiguration class>>dependencyFromArray: (in category 'converting') -----
+ dependencyFromArray: anArray
+ 	^MCVersionDependency
+ 		package: (MCPackage named: anArray first)
+ 		info: (
+ 			MCVersionInfo
+ 			name: anArray second
+ 			id: (UUID fromString: anArray third)
+ 			message: nil
+ 			date: nil
+ 			time: nil
+ 			author: nil
+ 			ancestors: nil)!

Item was added:
+ ----- Method: MCConfigurationBrowser>>updateMenu (in category 'actions') -----
+ updateMenu
+ 
+ 	| menu |
+ 	menu := MenuMorph new defaultTarget: self.
+ 	menu add: 'update from image' action: #updateFromImage.
+ 	menu add: 'update from repositories' action: #updateFromRepositories.
+ 	menu popUpInWorld.!

Item was changed:
  MCDefinition subclass: #MCMethodDefinition
  	instanceVariableNames: 'classIsMeta source category selector className timeStamp properties dummy1 dummy2 methodAndNode requestor compiledMethod priorMethodOrNil compiledSelector isInstalled priorMethodCategory theClass defnToInstall'
  	classVariableNames: 'Definitions'
  	poolDictionaries: ''
+ 	category: 'Monticello-Base-Modeling'!
- 	category: 'Monticello-Modeling'!

Item was added:
+ ----- Method: MCConfiguration>>fileName (in category 'accessing') -----
+ fileName
+ 	^ self name, '.', self writerClass extension
+ !

Item was added:
+ ----- Method: MCConfigurationBrowser>>repositories (in category 'accessing') -----
+ repositories
+ 	^ self configuration repositories!

Item was added:
+ ----- Method: MCConfigurationBrowser>>description: (in category 'description') -----
+ description: aText
+ 
+ 	self selectedRepository ifNotNilDo: [:repo | 
+ 		| new | 
+ 		new := MCRepository readFrom: aText asString.
+ 		(new class = repo class 
+ 			and: [new description = repo description])
+ 				ifTrue: [
+ 					repo creationTemplate: aText asString.
+ 					self changed: #description]
+ 				ifFalse: [
+ 					self inform: 'This does not match the previous definition!!'
+ 				]
+ 	].
+ 
+ !

Item was added:
+ ----- Method: MCMcmReader>>versionFromFile: (in category 'MonticelloConfigurations') -----
+ versionFromFile: fileName
+ 	^ self file: fileName streamDo: [:aStream | (self on: aStream fileName: fileName) version ]!

Item was changed:
  MCCodeTool subclass: #MCPatchBrowser
  	instanceVariableNames: 'selection'
  	classVariableNames: ''
  	poolDictionaries: ''
+ 	category: 'Monticello-UI-Browsers'!
- 	category: 'Monticello-UI'!

Item was changed:
  Object subclass: #MCDefinitionIndex
  	instanceVariableNames: 'definitions'
  	classVariableNames: ''
  	poolDictionaries: ''
+ 	category: 'Monticello-Base-Patching'!
- 	category: 'Monticello-Patching'!

Item was added:
+ ----- Method: MCConfiguration>>initialize (in category 'initialize') -----
+ initialize
+ 	super initialize.
+ 	log := DefaultLog.!

Item was changed:
  MCDefinition subclass: #MCClassDefinition
  	instanceVariableNames: 'name superclassName variables category type comment commentStamp traitComposition classTraitComposition properties oldInstVars'
  	classVariableNames: ''
  	poolDictionaries: ''
+ 	category: 'Monticello-Base-Modeling'!
- 	category: 'Monticello-Modeling'!
  
  !MCClassDefinition commentStamp: 'kph 5/15/2007 19:25' prior: 0!
  The strategy for loading is to preload a class definiton is to merge the variables 
  wanted by both the new and the old classes, and load this 'union' class definition.
  
  This should allow old code to continue running, and new code to be compiled.
  
  Since variable order is significant, the original order is preserved for the #preload, and changed on the #install.
  
  In the atomic #install phase, the new traitComposition and comment is switched in.
  
  In the atomic #postinstall phase the #initialize methods are run (note they have access to both the old and new class variables etc. 
  
  In the postload phase the new class definition is loaded, eliminating the now redundant parts.
  
  !

Item was changed:
  MCPatchOperation subclass: #MCModification
  	instanceVariableNames: 'obsoletion modification'
  	classVariableNames: ''
  	poolDictionaries: ''
+ 	category: 'Monticello-Base-Patching'!
- 	category: 'Monticello-Patching'!

Item was changed:
  Error subclass: #MCNoVersionInfoAvailable
  	instanceVariableNames: ''
  	classVariableNames: ''
  	poolDictionaries: ''
+ 	category: 'Monticello-Base-Versioning'!
- 	category: 'Monticello-Versioning'!

Item was added:
+ MCVersionReader subclass: #MCMcmReader
+ 	instanceVariableNames: 'fileName'
+ 	classVariableNames: ''
+ 	poolDictionaries: ''
+ 	category: 'Monticello-Configurations'!

Item was changed:
  MCWriter subclass: #MCMczWriter
  	instanceVariableNames: 'zip infoWriter'
  	classVariableNames: ''
  	poolDictionaries: ''
+ 	category: 'Monticello-Base-Storing'!
- 	category: 'Monticello-Storing'!

Item was changed:
  Notification subclass: #MCAbortNotification
  	instanceVariableNames: ''
  	classVariableNames: ''
  	poolDictionaries: ''
+ 	category: 'Monticello-Base-Loading'!
- 	category: 'Monticello-Loading'!

Item was changed:
  MCAncestry subclass: #MCWorkingAncestry
  	instanceVariableNames: ''
  	classVariableNames: ''
  	poolDictionaries: ''
+ 	category: 'Monticello-Base-Versioning'!
- 	category: 'Monticello-Versioning'!
  
  !MCWorkingAncestry commentStamp: '<historical>' prior: 0!
  The interim record of ancestry for a working copy, gets merged version added to the ancestry, and is used to create the VersionInfo when the working copy becomes a version. !

Item was added:
+ ----- Method: MCConfiguration>>info (in category 'faking') -----
+ info
+ 	^MCVersionInfo new!

Item was changed:
  Object subclass: #MCAncestry
  	instanceVariableNames: 'ancestors stepChildren'
  	classVariableNames: ''
  	poolDictionaries: ''
+ 	category: 'Monticello-Base-Versioning'!
- 	category: 'Monticello-Versioning'!
  
  !MCAncestry commentStamp: '<historical>' prior: 0!
  Abstract superclass of records of ancestry.!

Item was changed:
  Object subclass: #MCVersionMerger
  	instanceVariableNames: 'records merger'
  	classVariableNames: ''
  	poolDictionaries: ''
+ 	category: 'Monticello-Base-Versioning'!
- 	category: 'Monticello-Versioning'!

Item was changed:
  MCScriptDefinition subclass: #MCPostscriptDefinition
  	instanceVariableNames: ''
  	classVariableNames: ''
  	poolDictionaries: ''
+ 	category: 'Monticello-Base-Modeling'!
- 	category: 'Monticello-Modeling'!

Item was added:
+ ----- Method: MCConfiguration>>versionNamed:for:from: (in category 'private') -----
+ versionNamed: verInfo for: aDependency from: repo
+  
+ 	|  fileName ver depVersionInfo |
+ 	(repo filterFileNames: repo cachedFileNames forVersionNamed: verInfo name) ifNotEmptyDo: [:cachedNames |
+ 		fileName := cachedNames anyOne.
+ 		ProgressNotification signal: '' extra: 'Using cached ', fileName.
+ 		ver := repo versionFromFileNamed: fileName].
+ 	ver ifNil: [
+ 	 
+ 		depVersionInfo := self diffVersionInfoFor: aDependency.
+ 		(depVersionInfo notNil and: [depVersionInfo versionName ~= verInfo versionName and: [repo includesVersionNamed: depVersionInfo versionName]]) ifTrue: [
+ 			fileName := (MCDiffyVersion nameForVer: verInfo versionName  base: depVersionInfo versionName ), '.mcd'.
+ 			(repo includesVersionNamed: fileName)  
+ 			ifTrue:[ 
+ 				ProgressNotification signal: '' extra: 'Downloading ', fileName.
+ 				ver := repo versionFromFileNamed: fileName
+ 			]
+ 	]].
+ 	ver ifNil: [
+ 	 
+ 		ProgressNotification signal: '' extra: 'Downloading ', verInfo name.
+ 		ver := repo versionWithInfo: verInfo].
+ 	^ver!

Item was added:
+ ----- Method: MCConfiguration>>writerClass (in category 'accessing') -----
+ writerClass
+ 	^ MCMcmWriter !

Item was added:
+ ----- Method: MCConfiguration>>logError: (in category 'private') -----
+ logError: aString
+ 	self log
+ 		cr; nextPutAll: 'ERROR: ';
+ 		nextPutAll: aString; cr;
+ 		flush.
+ !

Item was added:
+ ----- Method: MCConfigurationBrowser>>merge (in category 'actions') -----
+ merge
+ 	self configuration merge.
+ 	self changed: #dependencyList; changed: #description
+ !

Item was added:
+ ----- Method: MCConfiguration>>depsSatisfying:versionDo:displayingProgress: (in category 'private') -----
+ depsSatisfying: selectBlock versionDo: verBlock displayingProgress: progressString
+ 	| repoMap count |
+ 	repoMap := Dictionary new.
+  
+ 	self repositories do: [:repo |
+ 		MCRepositoryGroup default addRepository: repo.
+ 		repo allVersionNames
+ 			ifEmpty: [self logWarning: 'cannot read from ', repo description]
+ 			ifNotEmptyDo: [:all | all do: [:ver | repoMap at: ver put: repo]]].
+ 
+ 	count := 0.
+ 	self dependencies do: [:dep |
+ 		| ver repo |
+ 		ver := dep versionInfo.
+ 		repo := repoMap at: ver versionName ifAbsent: [
+ 			self logError: 'Version ', ver name, ' not found in any repository'.
+ 			self logError: 'Aborting'.
+ 			^count].
+ 		(selectBlock value: dep) ifTrue: [
+ 			| new |
+ 			new := self versionNamed: ver for: dep from: repo.
+ 			new ifNil: [
+ 					self logError: 'Could not download version ', ver name, ' from ', repo description.
+ 					self logError: 'Aborting'.
+ 					^count]
+ 				ifNotNil: [
+ 					self logUpdate: dep package with: new.
+ 					ProgressNotification signal: '' extra: 'Installing ', ver name.
+ 					verBlock value: new.
+ 					count := count + 1.
+ 				]
+ 		].
+ 		dep package workingCopy repositoryGroup addRepository: repo.
+ 	] displayingProgress: progressString.
+ 
+ 	^count!

Item was added:
+ ----- Method: MCMcmReader class>>extension (in category 'accessing') -----
+ extension
+ 	^ 'mcm'!

Item was added:
+ ----- Method: MCMcmReader>>info (in category 'accessing') -----
+ info
+ 
+ 	^ self  !

Item was added:
+ ----- Method: MCMcmReader class>>loadVersionFile: (in category 'instance creation') -----
+ loadVersionFile: fileName
+  
+ 	(self versionFromFile: fileName) load
+ !

Item was added:
+ ----- Method: MCConfigurationBrowser>>down (in category 'actions') -----
+ down
+ 	self canMoveDown ifTrue: [
+ 		self list swap: self index with: self index + 1.
+ 		self index: self index + 1.
+ 		self changedList.
+ 	].
+ !

Item was added:
+ ----- Method: MCConfigurationBrowser>>dependencyIndex (in category 'selection') -----
+ dependencyIndex
+ 	^dependencyIndex ifNil: [0]!

Item was changed:
  MCDoItParser subclass: #MCSystemCategoryParser
  	instanceVariableNames: ''
  	classVariableNames: ''
  	poolDictionaries: ''
+ 	category: 'Monticello-Base-Chunk Format'!
- 	category: 'Monticello-Chunk Format'!

Item was changed:
  MCSnapshot subclass: #MCImageBackedSnapshot
  	instanceVariableNames: ''
  	classVariableNames: ''
  	poolDictionaries: ''
+ 	category: 'Monticello-Base-Patching'!
- 	category: 'Monticello-Patching'!

Item was added:
+ ----- Method: MCConfiguration>>dependencies: (in category 'accessing') -----
+ dependencies: aCollection
+ 	dependencies := aCollection!

Item was changed:
  MCPackageLoader2 subclass: #MCMultiPackageLoader
  	instanceVariableNames: ''
  	classVariableNames: ''
  	poolDictionaries: ''
+ 	category: 'Monticello-Base-Loading'!
- 	category: 'Monticello-Loading'!
  
  !MCMultiPackageLoader commentStamp: '<historical>' prior: 0!
  A PackageLoader doing some additional cross-package checks!

Item was changed:
  MCTool subclass: #MCVersionInspector
  	instanceVariableNames: 'version'
  	classVariableNames: ''
  	poolDictionaries: ''
+ 	category: 'Monticello-UI-Browsers'!
- 	category: 'Monticello-UI'!

Item was added:
+ ----- Method: MCConfigurationBrowser>>changedList (in category 'selection') -----
+ changedList
+ 	self dependencyIndex > 0 ifTrue: [^self changed: #dependencyList].
+ 	self repositoryIndex > 0 ifTrue: [^self changed: #repositoryList].
+ 	self error: 'nothing selected'!

Item was added:
+ ----- Method: MCConfigurationBrowser>>configuration: (in category 'accessing') -----
+ configuration: aConfiguration
+ 	configuration := aConfiguration!

Item was added:
+ ----- Method: MCConfigurationBrowser>>canRemove (in category 'testing') -----
+ canRemove
+ 	^self index > 0!

Item was added:
+ ----- Method: MCMcmReader class>>versionFromFile: (in category 'instance creation') -----
+ versionFromFile: fileName
+ 	^ self file: fileName streamDo: [:aStream | (self on: aStream fileName: fileName) version ]!

Item was added:
+ ----- Method: MCConfigurationBrowser>>checkMissing (in category 'dependencies') -----
+ checkMissing
+ 	| missing |
+ 	missing := (self dependencies collect: [:ea | ea versionInfo name]) asSet.
+ 
+ 	self repositories
+ 		do: [:repo |
+ 			repo allVersionNames
+ 				do: [:found | missing remove: found ifAbsent: []]]
+ 		displayingProgress: 'searching versions'.
+ 
+ 	^missing isEmpty or: [
+ 		self selectDependency: missing anyOne.
+ 		self confirm: (String streamContents: [:strm |
+ 			strm nextPutAll: 'No repository found for'; cr.
+ 			missing do: [:r | strm nextPutAll: r; cr].
+ 			strm nextPutAll: 'Do you still want to store?'])]
+ 	!

Item was added:
+ ----- Method: MCConfigurationBrowser>>updateFromRepositories (in category 'updating') -----
+ updateFromRepositories
+ 	self configuration updateFromRepositories.
+ 	self changed: #dependencyList; changed: #description
+ !

Item was added:
+ ----- Method: MCConfiguration class>>initialize (in category 'class initialization') -----
+ initialize
+ 	"MCConfiguration initialize"
+ 
+ 	Preferences addPreference: #upgradeIsMerge
+ 		categories: #('updates') default: false 
+ 		balloonHelp: 'When upgrading packages, use merge instead of load'.!

Item was added:
+ ----- Method: MCConfigurationBrowser>>widgetSpecs (in category 'morphic ui') -----
+ widgetSpecs
+ 	^ #(
+ 		((buttonRow) (0 0 1 0) (0 0 0 30))
+ 		((listMorph:selection:menu: dependencyList dependencyIndex dependencyMenu:) (0 0 1 1) (0 30 0 -180))
+ 		((listMorph:selection:menu: repositoryList repositoryIndex repositoryMenu:) (0 1 1 1) (0 -180 0 -120))
+ 		((textMorph: description) (0 1 1 1) (0 -120 0 0))
+ 	 	)!

Item was changed:
  MCVersionReader subclass: #MCMczReader
  	instanceVariableNames: 'zip infoCache'
  	classVariableNames: ''
  	poolDictionaries: ''
+ 	category: 'Monticello-Base-Storing'!
- 	category: 'Monticello-Storing'!

Item was changed:
  MCPackageManager subclass: #MCWorkingCopy
  	instanceVariableNames: 'ancestry counter repositoryGroup requiredPackages'
  	classVariableNames: ''
  	poolDictionaries: ''
+ 	category: 'Monticello-Base-Versioning'!
- 	category: 'Monticello-Versioning'!

Item was added:
+ ----- Method: MCMcmReader>>version (in category 'accessing') -----
+ version
+ 	| configuration |
+ 	stream reset.
+ 	configuration := MCConfiguration fromArray: (MCScanner scan: stream).
+ 	configuration name: self configurationName.
+ 	^configuration!

Item was added:
+ ----- Method: MCMcmReader>>browseVersionFrom: (in category 'accessing') -----
+ browseVersionFrom: aRepository
+ 
+ 	self version browse!

Item was added:
+ ----- Method: MCConfigurationBrowser>>up (in category 'actions') -----
+ up
+ 	self canMoveUp ifTrue: [
+ 		self list swap: self index with: self index - 1.
+ 		self index: self index - 1.
+ 		self changedList.
+ 	].!

Item was added:
+ ----- Method: MCConfiguration>>fileOutOn: (in category 'actions') -----
+ fileOutOn: aStream
+ 	self writerClass fileOut: self on: aStream!

Item was added:
+ ----- Method: MCConfigurationBrowser>>defaultExtent (in category 'morphic ui') -----
+ defaultExtent
+ 	^ 350 at 500!

Item was added:
+ ----- Method: MCConfigurationBrowser>>addRepository (in category 'repositories') -----
+ addRepository
+ 	(self pickRepositorySatisfying: [:ea | (self repositories includes: ea) not])
+ 		ifNotNilDo: [:repo |
+ 			((repo isKindOf: MCHttpRepository) | (repo isKindOf: MCDirectoryRepository))
+ 				ifFalse: [^self inform: 'Only HTTP or Directory repositories are supported'].
+ 			self repositories add: repo.
+ 			self changed: #repositoryList.
+ 		]!

Item was changed:
  MCPatchBrowser subclass: #MCChangeSelector
  	instanceVariableNames: 'kept'
  	classVariableNames: ''
  	poolDictionaries: ''
+ 	category: 'Monticello-UI-Browsers'!
- 	category: 'Monticello-UI'!

Item was changed:
  MCRepository subclass: #MCDictionaryRepository
  	instanceVariableNames: 'description dictionary'
  	classVariableNames: ''
  	poolDictionaries: ''
+ 	category: 'Monticello-Base-Repositories'!
- 	category: 'Monticello-Repositories'!

Item was changed:
  Object subclass: #MCVersionSorter
  	instanceVariableNames: 'layers depthIndex depths stepparents roots'
  	classVariableNames: ''
  	poolDictionaries: ''
+ 	category: 'Monticello-Base-Versioning'!
- 	category: 'Monticello-Versioning'!
  
  !MCVersionSorter commentStamp: 'kph 5/16/2007 19:47' prior: 0!
  For sorting versions.
  
  MCFileRepositories use their own scheme for sorting versions.!

Item was added:
+ ----- Method: MCConfiguration>>dependencies (in category 'accessing') -----
+ dependencies
+ 	^dependencies ifNil: [dependencies := OrderedCollection new]!

Item was changed:
  MCTool subclass: #MCSaveVersionDialog
  	instanceVariableNames: 'name message'
  	classVariableNames: 'LastComments'
  	poolDictionaries: ''
+ 	category: 'Monticello-UI-Browsers'!
- 	category: 'Monticello-UI'!

Item was changed:
  MCVersionInfo subclass: #MCVersionInfoFilename
  	instanceVariableNames: 'isFilename versionName'
  	classVariableNames: ''
  	poolDictionaries: ''
+ 	category: 'Monticello-Base-Versioning'!
- 	category: 'Monticello-Versioning'!
  
  !MCVersionInfoFilename commentStamp: 'kph 6/28/2007 23:55' prior: 0!
  For filenames
  
  Project-Subcategory-author.123.mcz
  
  Everything after the first $. is the version string, this allows for more variation, and is more flexible in the case of different file types and conventions, e.g. .mcm!

Item was added:
+ ----- Method: MCConfigurationBrowser>>configuration (in category 'accessing') -----
+ configuration
+ 	^configuration ifNil: [configuration := MCConfiguration new]!

Item was added:
+ ----- Method: MCConfigurationBrowser>>canMoveDown (in category 'testing') -----
+ canMoveDown
+ 	^self index between: 1 and: self maxIndex - 1 !

Item was added:
+ ----- Method: MCConfigurationBrowser>>load (in category 'actions') -----
+ load
+ 	self configuration load.
+ 	self changed: #dependencyList; changed: #description
+ !

Item was added:
+ ----- Method: MCMcmWriter>>close (in category 'writing') -----
+ close
+ 	stream close!

Item was changed:
  Object subclass: #MCVariableDefinition
  	instanceVariableNames: 'name'
  	classVariableNames: ''
  	poolDictionaries: ''
+ 	category: 'Monticello-Base-Modeling'!
- 	category: 'Monticello-Modeling'!

Item was added:
+ ----- Method: MCConfigurationBrowser>>repositoryMenu: (in category 'morphic ui') -----
+ repositoryMenu: aMenu
+ 	^self fillMenu: aMenu fromSpecs: #(
+ 		('add repository...' addRepository)
+ 	)!

Item was added:
+ ----- Method: MCConfigurationBrowser>>repositoryList (in category 'repositories') -----
+ repositoryList
+ 	^self repositories collect: [:ea | ea description]
+ !

Item was changed:
  MCRepositoryVersionsInspector subclass: #MCRepositoryPackagesVersionsInspector
  	instanceVariableNames: 'selectedPackageName packageNames'
  	classVariableNames: ''
  	poolDictionaries: ''
+ 	category: 'Monticello-UI-Repository'!
- 	category: 'Monticello-UI'!

Item was changed:
  MCMethodDefinition subclass: #MCMethodInitializerDefinition
  	instanceVariableNames: ''
  	classVariableNames: ''
  	poolDictionaries: ''
+ 	category: 'Monticello-Base-Modeling'!
- 	category: 'Monticello-Modeling'!
  
  !MCMethodInitializerDefinition commentStamp: 'kph 1/16/2008 09:39' prior: 0!
  MCMethodInitializerDefinition 
  
  	is loaded as a normal method.
  	at #postloadOver:, it runs itself.
  	!

Item was added:
+ ----- Method: MCConfigurationBrowser>>remove (in category 'actions') -----
+ remove
+ 	self canRemove ifTrue: [
+ 		self list removeAt: self index.
+ 		self changedList.
+ 		self updateIndex.
+ 	].
+ !

Item was changed:
  ClassBuilder subclass: #MCClassBuilder
  	instanceVariableNames: ''
  	classVariableNames: ''
  	poolDictionaries: ''
+ 	category: 'Monticello-Base-Loading'!
- 	category: 'Monticello-Loading'!

Item was added:
+ ----- Method: MCConfigurationBrowser>>includesPackage: (in category 'testing') -----
+ includesPackage: aPackage
+ 	^self dependencies anySatisfy: [:each | each package = aPackage]!

Item was changed:
  Object subclass: #MCReader
  	instanceVariableNames: 'stream'
  	classVariableNames: ''
  	poolDictionaries: ''
+ 	category: 'Monticello-Base-Storing'!
- 	category: 'Monticello-Storing'!

Item was added:
+ RWBinaryOrTextStream subclass: #MCPseudoFileStream
+ 	instanceVariableNames: 'localName'
+ 	classVariableNames: ''
+ 	poolDictionaries: ''
+ 	category: 'Monticello-Configurations'!
+ 
+ !MCPseudoFileStream commentStamp: '<historical>' prior: 0!
+ A pseudo file stream which can be used for updates.!

Item was added:
+ ----- Method: MCConfigurationBrowser>>selectRepository: (in category 'selection') -----
+ selectRepository: aRepository
+ 	self repositoryIndex: (self repositories indexOf: aRepository)!

Item was added:
+ ----- Method: MCConfigurationBrowser>>description (in category 'description') -----
+ description
+ 	self selectedDependency ifNotNilDo: [:dep | ^ ('Package: ', dep package name, String cr,
+ 		dep versionInfo summary) asText].
+ 	self selectedRepository ifNotNilDo: [:repo | ^repo creationTemplate
+ 		ifNotNil: [repo creationTemplate asText]
+ 		ifNil: [repo asCreationTemplate asText addAttribute: TextColor red]].
+ 	^ ''
+ !

Item was added:
+ ----- Method: MCConfiguration>>diffVersionInfoFor: (in category 'private') -----
+ diffVersionInfoFor: aDependency
+ 	| wc |
+ 	aDependency package hasWorkingCopy  ifFalse: [^nil].
+ 	wc := aDependency package workingCopy.
+ 	wc ancestors ifEmpty: [^nil].
+ 	^wc ancestors first  !

Item was added:
+ ----- Method: MCMcmReader class>>on:fileName: (in category 'instance creation') -----
+ on: aStream fileName: aFileName
+ 	| reader |
+ 	reader := self on: aStream.
+ 	reader fileName: aFileName.
+ 	^reader!

Item was added:
+ ----- Method: MCConfiguration>>changes (in category 'faking') -----
+ changes
+ 	^MCPatch operations: #()!

Item was added:
+ ----- Method: MCConfigurationBrowser>>checkRepositoryTemplates (in category 'repositories') -----
+ checkRepositoryTemplates
+ 	"unused for now - we only do HTTP"
+ 	| bad |
+ 	bad := self repositories select: [:repo | repo creationTemplate isNil].
+ 	^bad isEmpty or: [
+ 		self selectRepository: bad first.
+ 		self inform: (String streamContents: [:strm |
+ 			strm nextPutAll: 'Creation template missing for'; cr.
+ 			bad do: [:r | strm nextPutAll: r description; cr].
+ 			strm nextPutAll: 'Please fill in the details first!!']).
+ 		false].
+ !



More information about the Packages mailing list