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

squeak-dev-noreply at lists.squeakfoundation.org squeak-dev-noreply at lists.squeakfoundation.org
Sun Dec 7 02:33:33 UTC 2008


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

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

Name: Monticello.impl-kph.600
Author: kph
Time: 7 December 2008, 2:33:15 am
UUID: d9b6f52e-c8c3-454c-8556-53b43a56820b
Ancestors: Monticello.impl-kph.599

removed implementation of PackageLoader

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

Item was added:
+ ----- Method: MCPackageLoader class>>newCurrent (in category 'as yet unclassified') -----
+ newCurrent
+ 
+ 	^ (self theChosenLoaderClass basicNew) initialize; yourself!

Item was changed:
  ----- Method: MCSnapshot>>install (in category 'loading') -----
  install
+ 	(MCPackageLoader newCurrent)
- 	(MCPackageLoader new)
  		installSnapshot: self;
  		installOrphanage;
  		load!

Item was changed:
  ----- Method: MCSnapshot>>updatePackage: (in category 'loading') -----
  updatePackage: aPackage
+ 	(MCPackageLoader newCurrent)
- 	(MCPackageLoader new)
  		updatePackage: aPackage withSnapshot: self;
  		installOrphanage;
  		load
  		!

Item was changed:
  ----- Method: MCPatchBrowser>>revertSelection (in category 'as yet unclassified') -----
  revertSelection
  	| loader |
  	selection ifNotNil:
+ 		[loader := MCPackageLoader newCurrent.
- 		[loader := MCPackageLoader new.
  		selection inverse applyTo: loader.
  		loader loadWithName: self changeSetNameForInstall ]!

Item was changed:
  ----- Method: MCMerger>>loadWithNameLike: (in category 'as yet unclassified') -----
  loadWithNameLike: baseName
  	| loader |
+ 	loader := MCPackageLoader newCurrent.
- 	loader := MCPackageLoader new.
  	loader provisions addAll: self provisions.
  	self applyTo: loader.
  	loader loadWithNameLike: baseName!

Item was changed:
  ----- Method: MCPatchBrowser>>installSelection (in category 'as yet unclassified') -----
  installSelection
  	| loader |
  	selection ifNotNil:
+ 		[loader := MCPackageLoader newCurrent.
- 		[loader := MCPackageLoader new.
  		selection applyTo: loader.
  		loader loadWithName: self changeSetNameForInstall ]!

Item was changed:
  ----- Method: MCWorkingCopy>>backportChangesTo: (in category 'operations') -----
  backportChangesTo: aVersionInfo
  	| baseVersion fullPatch currentVersionInfo currentVersion newSnapshot newAncestry |
  	currentVersionInfo := self currentVersionInfo.
  	baseVersion := self repositoryGroup versionWithInfo: aVersionInfo.
  	currentVersion := self repositoryGroup versionWithInfo: currentVersionInfo.
  	fullPatch := currentVersion snapshot patchRelativeToBase: baseVersion snapshot.
  	(MCChangeSelectionRequest new
  		patch: fullPatch;
  		label: 'Changes to Backport';
  		signal ) ifNotNilDo:
  		[:partialPatch |
  		newSnapshot := MCPatcher apply: partialPatch to: baseVersion snapshot.
  		newAncestry := MCWorkingAncestry new
  							addAncestor: aVersionInfo;
  							addStepChild: currentVersionInfo;
  							yourself.
  
+ 		(MCPackageLoader newCurrent) 
- 		(MCPackageLoader new) 
  			updatePackage: package withSnapshot: newSnapshot;
  			installOrphanage.
  			
  		ancestry := newAncestry.
  		self modified: false; modified: true]!

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

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

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

Item was changed:
  ----- Method: MCSnapshotBrowser>>loadClassSelectionDefinition (in category 'listing') -----
  loadClassSelectionDefinition
  
  	| classDefinition |
  	
  	classSelection ifNil: [ ^self ].
  
  	classDefinition := items 
  		detect: [ :defn | defn isClassDefinition and: [ defn className = classSelection ] ].
  	
+ 	(MCPackageLoader newCurrent) 
- 	(MCPackageLoader new) 
  		addDefinition: classDefinition;
  		load
  	!

Item was changed:
  ----- Method: MCWorkingCopy>>unload (in category 'operations') -----
  unload
+ 	MCPackageLoader newCurrent unloadPackage: self package.
- 	MCPackageLoader new unloadPackage: self package.
  	self unregister.!

Item was added:
+ ----- Method: MCFileDefinition>>edLoad: (in category 'as yet unclassified') -----
+ edLoad: editor
+ 
+ 	FileDirectory default copyFileNamed: self pathToSnapshotFull toFileNamed: self pathToOriginalFull!

Item was changed:
  ----- Method: MCMerger>>load (in category 'as yet unclassified') -----
  load
  	| loader |
+ 	loader := MCPackageLoader newCurrent.
- 	loader := MCPackageLoader new.
  	loader provisions addAll: self provisions.
  	self applyTo: loader.
  	loader load!

Item was changed:
  ----- Method: MCVersionLoader>>loadWithNameLike: (in category 'loading') -----
  loadWithNameLike: aString
  	| loader |
  	self checkForModifications.
+ 	loader := MCPackageLoader newCurrent.
- 	loader := MCPackageLoader new.
  	versions size > 1 ifTrue: [ loader beMultiplePackage ].
  	 
  	versions do: [:ea |
  		ea canOptimizeLoading
  			ifTrue: [ea patch applyTo: loader]
  			ifFalse: [loader updatePackage: ea package withSnapshot: ea snapshot
  			]
  	].
  	loader 	installOrphanage;
  			loadWithNameLike: aString.
  	versions do: [:ea | ea workingCopy loaded: ea]!

Item was removed:
- ----- Method: MCPackageLoader>>loadComplete (in category 'private') -----
- loadComplete!

Item was removed:
- ----- Method: MCPackageLoader>>useChangeSetNamed:during: (in category 'private') -----
- useChangeSetNamed: baseName during: aBlock
- 	"Use the named change set, or create one with the given name."
- 	| changeHolder oldChanges newChanges |
- 	changeHolder := (ChangeSet respondsTo: #newChanges:)
- 						ifTrue: [ChangeSet]
- 						ifFalse: [Smalltalk].
- 	oldChanges := (ChangeSet respondsTo: #current)
- 						ifTrue: [ChangeSet current]
- 						ifFalse: [Smalltalk changes].
- 
- 	newChanges := (ChangeSorter changeSetNamed: baseName) ifNil: [ ChangeSet new name: baseName ].
- 	changeHolder newChanges: newChanges.
- 	[aBlock value] ensure: [changeHolder newChanges: oldChanges].
- !

Item was removed:
- ----- Method: MCPackageLoader>>warnAboutErrors: (in category 'private') -----
- warnAboutErrors: errors
- 	errors isEmpty ifFalse: [ self notify: (self errorDefinitionWarning: errors) ]
- !

Item was removed:
- ----- Method: MCPackageLoader>>beUnloading (in category 'public') -----
- beUnloading
- 
- 	 "stub"!

Item was removed:
- ----- Method: MCPackageLoader>>loadWithName: (in category 'public') -----
- loadWithName: baseName
- 	self analyze.
- 	unloadableDefinitions isEmpty ifFalse: [self warnAboutDependencies].
- 	self useChangeSetNamed: baseName during: [self basicLoad]!

Item was removed:
- ----- Method: MCPackageLoader>>beMultiplePackage (in category 'public') -----
- beMultiplePackage
- 
- 	isMultiplePackage := true!

Item was removed:
- ----- Method: MCPackageLoader>>orderedAdditions (in category 'private') -----
- orderedAdditions
- 	^ additions!

Item was removed:
- ----- Method: MCPackageLoader>>shouldWarnAboutErrors (in category 'private') -----
- shouldWarnAboutErrors
- 	^ errorDefinitions isEmpty not and: [false "should make this a preference"]!

Item was removed:
- ----- Method: MCPackageLoader>>updatePackage:withSnapshot: (in category 'public') -----
- updatePackage: aPackage withSnapshot: aSnapshot
- 	|  patch packageSnap |
- 	packageSnap := aPackage snapshot.
- 	patch := aSnapshot patchRelativeToBase: packageSnap.
- 	patch applyTo: self.
- 	packageSnap definitions do: [:ea | self provisions addAll: ea provisions]
- !

Item was removed:
- ----- Method: MCPackageLoader2>>tryToLoad: (in category 'obsolete') -----
- tryToLoad: aDefinition
- 	[aDefinition loadOver: (self obsoletionFor: aDefinition)] on: Error do: [errorDefinitions add: aDefinition].!

Item was removed:
- ----- Method: MCPackageLoader>>errorDefinitionWarning (in category 'private') -----
- errorDefinitionWarning
- 	^ String streamContents:
- 		[:s |
- 		s nextPutAll: 'The following definitions had errors while loading.  Press Proceed to try to load them again (they may work on a second pass):'; cr.
- 		errorDefinitions do: [:ea | s space; space; nextPutAll: ea summary; cr]] !

Item was removed:
- ----- Method: MCPackageLoader>>tryToLoad: (in category 'private') -----
- tryToLoad: aDefinition
- 	[aDefinition loadOver: (self obsoletionFor: aDefinition)] on: Error do: [errorDefinitions add: aDefinition].!

Item was removed:
- ----- Method: MCPackageLoader>>addDefinition: (in category 'patch ops') -----
- addDefinition: aDefinition
- 	additions add: aDefinition!

Item was removed:
- ----- Method: MCPackageLoader>>errorDefinitionWarning: (in category 'private') -----
- errorDefinitionWarning: erroredDefns
- 	^ String streamContents:
- 		[:s |
- 		s nextPutAll: 'The following definitions had errors while loading.  Press Proceed to try to load them again (they may work on a second pass):'; cr.
- 		erroredDefns do: [:ea | 
- 			s space; space; 
- 			  nextPutAll: ea summary;
- 			  space; 
- 			  nextPutAll: (ea because ifNil: [ '' ]); cr]] !

Item was removed:
- ----- Method: MCPackageLoader>>load (in category 'public') -----
- load
- 	self analyze.
- 	unloadableDefinitions isEmpty ifFalse: [self warnAboutDependencies].
- 	self useNewChangeSetDuring: [self basicLoad]!

Item was removed:
- ----- Method: MCPackageLoader>>provisions (in category 'private') -----
- provisions
- 	^ provisions ifNil: [provisions := Set withAll: Smalltalk keys]!

Item was removed:
- ----- Method: MCPackageLoader>>basicLoad (in category 'private') -----
- basicLoad
- 	errorDefinitions := OrderedCollection new.
- 	[[additions do: [:ea | self tryToLoad: ea] displayingProgress: 'Loading...'.
- 	removals do: [:ea | ea unload] displayingProgress: 'Cleaning up...'.
- 	self shouldWarnAboutErrors ifTrue: [self warnAboutErrors].
- 	errorDefinitions do: [:ea | ea loadOver: (self obsoletionFor: ea)] displayingProgress: 'Reloading...'.
- 	additions do: [:ea | ea postloadOver: (self obsoletionFor: ea)] displayingProgress: 'Initializing...']
- 		on: InMidstOfFileinNotification 
- 		do: [:n | n resume: true]]
- 			ensure: [self flushChangesFile]!

Item was removed:
- ----- Method: MCPackageLoader>>obsoletionFor: (in category 'private') -----
- obsoletionFor: aDefinition
- 	^ obsoletions at: aDefinition ifAbsent: [nil]!

Item was removed:
- ----- Method: MCPackageLoader>>flushChangesFile (in category 'private') -----
- flushChangesFile
- 	"The changes file is second in the SourceFiles array"
- 
- 	(SourceFiles at: 2) flush!

Item was removed:
- ----- Method: MCPackageLoader>>warnAboutErrors (in category 'private') -----
- warnAboutErrors
- 	self notify: self errorDefinitionWarning.
- !

Item was removed:
- ----- Method: MCPackageLoader>>installOrphanage (in category 'private') -----
- installOrphanage
- 
- 	 !

Item was removed:
- ----- Method: MCPackageLoader1b>>tryToLoad: (in category 'private') -----
- tryToLoad: aDefinition
- 	[aDefinition loadOver: (self obsoletionFor: aDefinition)] on: Error do: [errorDefinitions add: aDefinition].!

Item was removed:
- ----- Method: MCPackageLoader>>tryToLoad:errors: (in category 'private') -----
- tryToLoad: aDefinition errors: errs
- 
- 	"a method used in some MC1 versions > md.308+"
- 
- 	[aDefinition loadOver: (self obsoletionFor: aDefinition)] on: Error do: [errs add: aDefinition].!

Item was removed:
- ----- Method: MCPackageLoader>>modifyDefinition:to: (in category 'patch ops') -----
- modifyDefinition: old to: new
- 	self addDefinition: new.
- 	obsoletions at: new put: old.!

Item was removed:
- ----- Method: MCPackageLoader>>warnAboutDependencies (in category 'private') -----
- warnAboutDependencies 
- 	self notify: self dependencyWarning!

Item was removed:
- ----- Method: MCPackageLoader>>orderDefinitionsForLoading: (in category 'private') -----
- orderDefinitionsForLoading: aCollection
- 	^ (self sorterForItems: aCollection) orderedItems!

Item was removed:
- ----- Method: MCPackageLoader>>successfullyLoaded: (in category 'private') -----
- successfullyLoaded: ea 
- 
- 	"dummy"
- 
- 	 !

Item was removed:
- ----- Method: MCPackageLoader>>isUnloading (in category 'public') -----
- isUnloading 
- 
- 	^ isUnloading ifNil: [ false ]!

Item was removed:
- ----- Method: MCPackageLoader>>useNewChangeSetDuring: (in category 'private') -----
- useNewChangeSetDuring: aBlock
- 	^self useNewChangeSetNamedLike: 'MC' during: aBlock!

Item was removed:
- ----- Method: MCPackageLoader>>isMultiplePackage (in category 'public') -----
- isMultiplePackage
- 
- 	^ isMultiplePackage == true!

Item was removed:
- ----- Method: MCPackageLoader>>initialize (in category 'private') -----
- initialize
- 	additions := OrderedCollection new.
- 	errorDefinitions := OrderedCollection new.
- 	removals := OrderedCollection new.
- 	obsoletions := Dictionary new.
- !

Item was removed:
- ----- Method: MCPackageLoader>>analyzeMulti (in category 'private') -----
- analyzeMulti
- 	| index |
- 	index := MCDefinitionIndex definitions: additions.
- 	removals removeAllSuchThat: [:removal |
- 		(index definitionLike: removal
- 			ifPresent: [:addition | obsoletions at: addition put: removal]
- 			ifAbsent: []) notNil].!

Item was removed:
- ----- Method: MCPackageLoader>>removeDefinition: (in category 'patch ops') -----
- removeDefinition: aDefinition
- 	removals add: aDefinition!

Item was removed:
- ----- Method: MCPackageLoader>>useNewChangeSetNamedLike:during: (in category 'private') -----
- useNewChangeSetNamedLike: baseName during: aBlock
- 	^self useChangeSetNamed: (ChangeSet uniqueNameLike: baseName) during: aBlock!

Item was removed:
- ----- Method: MCPackageLoader>>loadWithNameLike: (in category 'public') -----
- loadWithNameLike: baseName
- 	self analyze.
- 	unloadableDefinitions isEmpty ifFalse: [self warnAboutDependencies].
- 	self useNewChangeSetNamedLike: baseName during: [self basicLoad]!

Item was removed:
- ----- Method: MCPackageLoader>>analyze (in category 'private') -----
- analyze
- 	| sorter |
- 	
- 	self isMultiplePackage ifTrue: [ self analyzeMulti ].
- 	
- 	sorter := self sorterForItems: additions.
- 	additions := sorter orderedItems.
- 	requirements := sorter externalRequirements.
- 	unloadableDefinitions := sorter itemsWithMissingRequirements asSortedCollection.
- 	
- 	sorter := self sorterForItems: removals.
- 	removals := sorter orderedItems reversed.!

Item was removed:
- ----- Method: MCPackageLoader>>sorterForItems: (in category 'private') -----
- sorterForItems: aCollection
- 	| sorter |
- 	sorter := MCDependencySorter items: aCollection.
- 	sorter addExternalProvisions: self provisions.
- 	^ sorter!

Item was removed:
- ----- Method: MCDefinition>>loadOver: (in category 'obsolete') -----
- loadOver: aDefinition
- 	"this method is now obsolete, it runs when old versions of Monticello are used to load this one.
- 	It is also the only place in the transition where you can put 'initialization' code if you have to"
- 	
- 	self load
- 	!

Item was removed:
- ----- Method: MCScriptDefinition>>load (in category 'as yet unclassified') -----
- load
- 	self installScript!

Item was removed:
- ----- Method: MCPackageLoader>>dependencyWarning (in category 'private') -----
- dependencyWarning
- 	^ String streamContents:
- 		[:s |
- 		s nextPutAll: 'This package depends on the following classes:'; cr.
- 		requirements do: [:ea | s space; space; nextPutAll: ea; cr].
- 		s nextPutAll: 'You must resolve these dependencies before you will be able to load these definitions: '; cr.
- 		unloadableDefinitions do: [:ea | s space; space; nextPutAll: ea summary; cr]] !

Item was removed:
- ----- Method: MCPackageLoader>>installSnapshot: (in category 'public') -----
- installSnapshot: aSnapshot
- 	| patch |
- 	patch := aSnapshot patchRelativeToBase: MCSnapshot empty.
- 	patch applyTo: self.
- !

Item was removed:
- ----- Method: MCPackageLoader>>unloadPackage: (in category 'public') -----
- unloadPackage: aPackage
-  
- 	(self 
- 		updatePackage: aPackage withSnapshot: MCSnapshot empty;
- 		beUnloading;
- 		loadWithNameLike: aPackage name, '-unload';
- 		yourself)
- 		orphanage packageUnloaded: aPackage packageInfo.	!

Item was removed:
- ----- Method: MCPackageLoader>>tryToUnload:errors: (in category 'private') -----
- tryToUnload: aDefinition errors: errs
- 
- 	"a method used in some MC1 versions > md.308+"
- 
- 	[aDefinition unload ] on: Error do: [errs add: aDefinition].!



More information about the Packages mailing list