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

squeak-dev-noreply at lists.squeakfoundation.org squeak-dev-noreply at lists.squeakfoundation.org
Sun Mar 29 02:27:18 UTC 2009


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

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

Name: Monticello.impl-kph.643
Author: kph
Time: 29 March 2009, 2:26:59 am
UUID: 9c2bfdd9-0030-4032-a5d0-49de49cf33e1
Ancestors: Monticello.impl-kph.642

+ refactored instanciation of MCDefinitions
+ added support for preserving methodCategorisation order

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

Item was added:
+ ----- Method: MCScriptDefinition>>zapProperties (in category 'as yet unclassified') -----
+ zapProperties.
+ 
+ 	properties := nil!

Item was added:
+ ----- Method: MCClassDefinition>>category: (in category 'accessing') -----
+ category: anObject
+ 	"Set the value of category"
+ 
+ 	category := anObject!

Item was added:
+ ----- Method: MCClassTraitDefinition>>zapProperties (in category 'accessing') -----
+ zapProperties.
+ 
+ 	properties := nil!

Item was added:
+ ----- Method: MCClassDefinition>>setClassInstVarNames: (in category 'accessing') -----
+ setClassInstVarNames: civarArray
+ 	self addVariables: civarArray ofType: MCClassInstanceVariableDefinition.!

Item was changed:
  ----- Method: MCDefinition>>storeDataOn: (in category 'annotations') -----
  storeDataOn: aDataStream
  
  	"we only ignore trailing instVars that are nil"
   
  	| lastNotNil |
  
+ 	self zapProperties.
+ 	
- 	self class ~= self class storeAsClassForMC1 ifTrue: [ self propertyAt: #class put: self class name ].
- 
- 	self propertyRemoveKey: #because.
- 
  	lastNotNil := (self storeMaxInstVars to: 1 by: -1) detect: [ :n |  (self instVarAt: n) notNil ].
  	 
  	aDataStream
  		beginInstance: self class storeAsClassForMC1
  		size: lastNotNil.
  	1 to: lastNotNil do:
  		[:i | aDataStream nextPut: (self instVarAt: i)].
  
  
  !

Item was added:
+ ----- Method: MCMethodDefinition>>zapProperties (in category 'compiling') -----
+ zapProperties.
+ 
+ 	properties := nil!

Item was added:
+ ----- Method: MCClassDefinition>>initialize (in category 'initializing') -----
+ initialize
+ 	variables := OrderedCollection  new.
+ !

Item was changed:
  ----- Method: MCTool>>listMorph:selection:menu: (in category 'morphic ui') -----
  listMorph: listSymbol selection: selectionSymbol menu: menuSymbol
+ 	^ self classPluggableListMorph
- 	^ PluggableListMorph
  		on: self
  		list: listSymbol
  		selected: selectionSymbol
  		changeSelected: (selectionSymbol, ':') asSymbol
  		menu: menuSymbol!

Item was changed:
  ----- Method: MCTraitParser>>addDefinitionsTo: (in category 'as yet unclassified') -----
  addDefinitionsTo: aCollection
  	| tokens  definition traitCompositionString |
  	tokens := Scanner new scanTokens: source.
  	traitCompositionString := ((ReadStream on: source)
  		match: 'uses:';
  		upToAll: 'category:') withBlanksTrimmed.
+ 	definition := (MCTraitDefinition new
+ 		setName: (tokens at: 3);
+ 		setTraitComposition: traitCompositionString class: nil;
+ 		setCategory:  tokens last;
+ 		setComment:  '' stamp:   '';
+ 		yourself) cached.
+ 		
- 	definition := MCTraitDefinition
- 		name: (tokens at: 3) 
- 		traitComposition: traitCompositionString
- 		category:  tokens last
- 		comment:  ''  
- 		commentStamp:   ''.
  	aCollection add: definition.!

Item was added:
+ ----- Method: MCClassDefinition>>comment: (in category 'accessing') -----
+ comment: anObject
+ 	"Set the value of comment"
+ 
+ 	comment := anObject!

Item was added:
+ ----- Method: MCClassDefinition>>setInstVarNames: (in category 'accessing') -----
+ setInstVarNames: ivarArray
+ 	self addVariables: ivarArray ofType: MCInstanceVariableDefinition.
+ !

Item was added:
+ ----- Method: MCClassDefinition>>setCategory: (in category 'accessing') -----
+ setCategory: anObject
+ 	"Set the value of category"
+ 
+ 	category := anObject!

Item was added:
+ ----- Method: MCClassDefinition>>setComment:stamp: (in category 'accessing') -----
+ setComment: anObject stamp: stampStringOrNil 
+ 	"Set the value of comment"
+ 
+ 	comment := anObject asString withSqueakLineEndings.
+ 	commentStamp := stampStringOrNil ifNil: [self defaultCommentStamp].!

Item was added:
+ ----- Method: MCClassDefinition>>properties (in category 'accessing') -----
+ properties
+ 	"Answer the value of properties"
+ 
+ 	^ properties!

Item was added:
+ ----- Method: MCClassDefinition>>properties: (in category 'accessing') -----
+ properties: anObject
+ 	"Set the value of properties"
+ 
+ 	properties := anObject!

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

Item was changed:
  ----- Method: MCTool>>listMorph:selection: (in category 'morphic ui') -----
  listMorph: listSymbol selection: selectionSymbol
+ 	^ self classPluggableListMorph
- 	^ PluggableListMorph
  		on: self
  		list: listSymbol
  		selected: selectionSymbol
  		changeSelected: (selectionSymbol, ':') asSymbol!

Item was added:
+ ----- Method: MCTool>>classPluggableListMorph (in category 'morphic ui') -----
+ classPluggableListMorph
+ 		
+ 	Smalltalk at: #PluggableListMorph ifPresent: [ :c | ^ c ].		
+ 	Smalltalk at: #OldPluggableListMorph ifPresent: [ :c | ^ c ].		
+ !

Item was changed:
  ----- Method: MCMethodDefinition class>>className:classIsMeta:selector:category:timeStamp:source: (in category 'as yet unclassified') -----
  className: classString
  classIsMeta: metaBoolean
  selector: selectorString
  category: catString
  timeStamp: timeString
  source: sourceString
+ 	^ ((self classForSelector: selectorString meta: metaBoolean) new
- 	^ self instanceLike:
- 		((self classForSelector: selectorString meta: metaBoolean) new
  					initializeWithClassName: classString
  					classIsMeta: metaBoolean
  					selector: selectorString
  					category: catString
  					timeStamp: timeString
+ 					source: sourceString) cached!
- 					source: sourceString)!

Item was added:
+ ----- Method: MCClassDefinition>>commentStamp: (in category 'accessing') -----
+ commentStamp: anObject
+ 	"Set the value of commentStamp"
+ 
+ 	commentStamp := anObject!

Item was changed:
  ----- Method: MCMethodDefinition>>storeDataOn: (in category 'visiting') -----
  storeDataOn: aDataStream
  
  	"we only ignore trailing instVars that are nil"
   
  	| lastNotNil |
  
+ 	self zapProperties.
+ 	
- 	self propertyRemoveKey: #because.
- 
  	lastNotNil := (self storeMaxInstVars to: 1 by: -1) detect: [ :n |  (self instVarAt: n) notNil ].
  	 
  	aDataStream
  		beginInstance: self class storeAsClassForMC1
  		size: lastNotNil.
  	1 to: lastNotNil do:
  		[:i | aDataStream nextPut: (self instVarAt: i)].
  
  
  !

Item was added:
+ ----- Method: MCClassDefinition>>classMethodCategories: (in category 'accessing') -----
+ classMethodCategories: anObject
+ 	"Set the value of classMethodCategories"
+ 
+ 	classMethodCategories := anObject!

Item was added:
+ ----- Method: MCUnlinkedClassDefinition>>zapProperties (in category 'as yet unclassified') -----
+ zapProperties.
+ 
+ 	properties := nil!

Item was added:
+ ----- Method: MCClassDefinition>>methodCategories (in category 'accessing') -----
+ methodCategories
+ 	"Answer the value of methodCategories"
+ 
+ 	^ methodCategories!

Item was added:
+ ----- Method: MCClassDefinition>>edPostload (in category 'system editor') -----
+ edPostload
+ 
+ 	self organize: self actualClass organization with: methodCategories.
+ 	self organize: self actualClass class organization with: classMethodCategories.
+ !

Item was changed:
  ----- Method: MCClassTraitDefinition class>>baseTraitName:classTraitComposition: (in category 'as yet unclassified') -----
  baseTraitName: aString classTraitComposition: classTraitCompositionString
+ 	^ (self new
- 	^self instanceLike: (
- 		self new
  			initializeWithBaseTraitName: aString
+ 			classTraitComposition: classTraitCompositionString) cached!
- 			classTraitComposition: classTraitCompositionString).!

Item was changed:
  ----- Method: MCTool>>listMorph:selection:menu:keystroke: (in category 'morphic ui') -----
  listMorph: listSymbol selection: selectionSymbol menu: menuSymbol keystroke: keystrokeSymbol
+ 	^ (self classPluggableListMorph
- 	^ (PluggableListMorph
  		on: self
  		list: listSymbol
  		selected: selectionSymbol
  		changeSelected: (selectionSymbol, ':') asSymbol
  		menu: menuSymbol)
  		keystrokeActionSelector: keystrokeSymbol;
  		yourself!

Item was changed:
  ----- Method: MCDefinition>>instVarAt:put: (in category 'annotations') -----
  instVarAt: anInteger put: anObject 
  	"Primitive. Store a value into a fixed variable in the receiver. The 
  	numbering of the variables corresponds to the named instance variables. 
  	Fail if the index is not an Integer or is not the index of a fixed variable. 
  	Answer the value stored as the result. Using this message violates the 
  	principle that each object has sovereign control over the storing of 
  	values into its instance variables. Essential. See Object documentation 
  	whatIsAPrimitive."
  
  	| |
  	
  	<primitive: 74>
  
  
  	"Access beyond fixed fields"
  
+ 	"When loading in any definition classes we get called if #instVarAt:put: fails which will occur if in a future version if extra instVars have been added to theses classes, ok, so we dont know what to do with this extra data but we keep it just in case"
- 	"When loading in any definition classes we get called if #instVarAt:put: fails which will occur if in a future version if extra instVars have been added to theses classes, ok, so we dont know what to do with this extra data, so we can slap it into our properties dictionary just in case!!"
  
  	 'extra', anInteger asString in: [ :newName |
  
  			self class addInstVarName: newName. 
  	 		self instVarNamed: newName put: anObject. 
  	 ].	
  	
   !

Item was added:
+ ----- Method: MCClassDefinition>>setMethodCategories:class: (in category 'accessing') -----
+ setMethodCategories: categories class: classSide
+ 	methodCategories := categories.
+ 	classMethodCategories := classSide.!

Item was changed:
  ----- Method: MCVersionLoader class>>loadVersion: (in category 'as yet unclassified') -----
  loadVersion: aVersion
+ 
  	self new
  		addVersion: aVersion;
  		load!

Item was added:
+ ----- Method: MCClassDefinition>>setName: (in category 'accessing') -----
+ setName: anObject
+ 	"Set the value of name"
+ 
+ 	name := anObject!

Item was changed:
  ----- Method: MCScriptDefinition class>>script:packageName: (in category 'as yet unclassified') -----
  script: aString packageName: packageString
+ 	^ (self new initializeWithScript: aString packageName: packageString) cached!
- 	^ self instanceLike: (self new initializeWithScript: aString packageName: packageString)!

Item was added:
+ ----- Method: MCClassDefinition>>methodCategories: (in category 'accessing') -----
+ methodCategories: anObject
+ 	"Set the value of methodCategories"
+ 
+ 	methodCategories := anObject!

Item was changed:
  ----- Method: PseudoClass>>asClassDefinition (in category '*monticello') -----
  asClassDefinition
+ 	^ (MCClassDefinition new
+ 		setName: self name;
+ 		setSuperclassName: self superclass name;
+ 		setCategory: self category; 
+ 		setInstVarNames: self instVarNames;
+ 		setClassVarNames: self classVarNames asSortedCollection;
+ 		setPoolDictionaryNames: self poolDictionaryNames;
+ 		setClassInstVarNames: self class instVarNames;
+ 		setMethodCategories: self organization categories class: self metaClass organization categories;
+ 		setType: self typeOfClass;
+ 		setComment: self organization classComment stamp: self organization commentStamp;
+ 		yourself) cached!
- 	^ MCClassDefinition
- 		name: self name
- 		superclassName: self superclass name
- 		category: self category 
- 		instVarNames: self instVarNames
- 		classVarNames: self classVarNames asSortedCollection
- 		poolDictionaryNames: self poolDictionaryNames
- 		classInstVarNames: self class instVarNames
- 		type: self typeOfClass
- 		comment: self organization classComment	 asString
- 		commentStamp: self organization commentStamp	!

Item was added:
+ ----- Method: MCDefinition>>cached (in category 'accessing') -----
+ cached
+ 
+ 	Instances ifNil: [Instances := WeakSet new].
+ 	^ (Instances like: self) ifNil: [Instances add: self]!

Item was changed:
  ----- Method: MCClassDefinition>>postloadOver: (in category 'installing') -----
  postloadOver: obs		
  
  	self extensions do: [ :ext |  (ext postloadOver: nil).  ext compiledMethod ifNil: [ self error: 'class extension has been obsoleted' ]].
+ 
+ 	self organize: self actualClass organization with: methodCategories.
+ 	self organize: self actualClass class organization with: classMethodCategories.
+ 
-   
  	self propertyRemoveKey: #tmpExtensions.
  	
+ 	MCClassBuilder new doneCompiling: self actualClass.
+ 	
+ 
+ 	!
- 	MCClassBuilder new doneCompiling: self actualClass.!

Item was added:
+ ----- Method: MCClassDefinition>>setTraitComposition:class: (in category 'testing') -----
+ setTraitComposition: aString class: cString
+ 	aString = '{}' ifFalse: [ traitComposition := aString ].
+ 	cString = '{}' ifFalse: [ classTraitComposition := aString ].!

Item was changed:
  ----- Method: MCClassDefinition>>edLoad: (in category 'system editor') -----
  edLoad: editor
  
  	| theClass |
  	theClass := (editor at: superclassName) subclass: name
  		instanceVariableNames: (self stringForVariablesOfType: #isInstanceVariable)
  		classVariableNames: (self stringForVariablesOfType: #isClassVariable)
  		poolDictionaries: (self stringForVariablesOfType: #isPoolImport)
  		category: category.
  
  	self hasTraitComposition ifTrue: [theClass setTraitCompositionFrom:
  		(Compiler evaluate: self traitCompositionString for: editor doItHost logged: false)].
  
  	theClass typeOfClass: type.
  	theClass class instanceVariableNames: (self stringForVariablesOfType: #isClassInstanceVariable). 
  	theClass classComment: comment stamp: commentStamp.
+ 	^ true "we do need an edPostload"!
- 	^ false "we dont need an edPostload"!

Item was changed:
  MCDefinition subclass: #MCClassDefinition
+ 	instanceVariableNames: 'name superclassName variables category type comment commentStamp traitComposition classTraitComposition properties methodCategories classMethodCategories'
- 	instanceVariableNames: 'name superclassName variables category type comment commentStamp traitComposition classTraitComposition properties oldInstVars'
  	classVariableNames: ''
  	poolDictionaries: ''
  	category: 'Monticello-Base-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 added:
+ ----- Method: MCClassDefinition>>name: (in category 'accessing') -----
+ name: anObject
+ 	"Set the value of name"
+ 
+ 	name := anObject!

Item was added:
+ ----- Method: MCDefinition>>cachedInstanceLikeMe (in category 'accessing') -----
+ cachedInstanceLikeMe
+ 
+ 	Instances ifNil: [Instances := WeakSet new].
+ 	^ (Instances like: self) ifNil: [Instances add: self]!

Item was changed:
  ----- Method: MCStReader>>classDefinitionFrom: (in category 'as yet unclassified') -----
  classDefinitionFrom: aPseudoClass
  	| tokens traitCompositionString lastIndex classTraitCompositionString |
  	tokens := Scanner new scanTokens: aPseudoClass definition.
  	traitCompositionString := ((ReadStream on: aPseudoClass definition)
  		match: 'uses:';
  		upToAll: 'instanceVariableNames:') withBlanksTrimmed.
  	classTraitCompositionString := ((ReadStream on: aPseudoClass metaClass definition asString)
  		match: 'uses:';
  		upToAll: 'instanceVariableNames:') withBlanksTrimmed.
  	traitCompositionString isEmpty ifTrue: [traitCompositionString := '{}'].
  	classTraitCompositionString isEmpty ifTrue: [classTraitCompositionString := '{}'].
  	lastIndex := tokens size.
+ 	^ (MCClassDefinition new
+ 		setName: (tokens at: 3);
+ 		setSuperclassName: (tokens at: 1);
+ 		setCategory: (tokens at: lastIndex);
+ 		setIinstVarNames: ((tokens at: lastIndex - 6) findTokens: ' ');
+ 		setClassVarNames: ((tokens at: lastIndex - 4) findTokens: ' ');
+ 		setPoolDictionaryNames: ((tokens at: lastIndex - 2) findTokens: ' ');
+ 		setClassInstVarNames: (self classInstVarNamesFor: aPseudoClass);
+ 		setType: (self typeOfSubclass: (tokens at: 2));
+ 		setComment: (self commentFor: aPseudoClass) stamp: (self commentStampFor: aPseudoClass);
+ 		setTraitComposition: self traitCompositionString class: self class traitCompositionString
+ 		yourself) cached!
- 	^ MCClassDefinition
- 		name: (tokens at: 3)
- 		superclassName: (tokens at: 1)
- 		traitComposition: traitCompositionString
- 		classTraitComposition: classTraitCompositionString
- 		category: (tokens at: lastIndex)
- 		instVarNames: ((tokens at: lastIndex - 6) findTokens: ' ')
- 		classVarNames: ((tokens at: lastIndex - 4) findTokens: ' ')
- 		poolDictionaryNames: ((tokens at: lastIndex - 2) findTokens: ' ')
- 		classInstVarNames: (self classInstVarNamesFor: aPseudoClass)
- 		type: (self typeOfSubclass: (tokens at: 2))
- 		comment: (self commentFor: aPseudoClass)
- 		commentStamp: (self commentStampFor: aPseudoClass)!

Item was changed:
  ----- Method: Trait>>asClassDefinition (in category '*monticello') -----
  asClassDefinition
+ 	^ (MCTraitDefinition new
+ 		setName: self name;
+ 		setTraitComposition: self traitCompositionString class: nil;
+ 		setCategory: self category; 
+ 		setComment: self organization classComment stamp: self organization commentStamp;
+ 		setMethodCategories: self organization categories class: self classTrait organization categories;
+ 		yourself) cached!
- 	^ MCTraitDefinition
- 		name: self name
- 		traitComposition: self traitCompositionString
- 		category: self category 
- 		comment: self organization classComment asString
- 		commentStamp: self organization commentStamp.!

Item was added:
+ ----- Method: MCClassDefinition>>zapProperties (in category 'accessing') -----
+ zapProperties.
+ 
+ 	properties := nil!

Item was changed:
  ----- Method: MCPackageLoader1b>>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 changed:
  ----- Method: MCOrganizationDefinition>>postloadOver: (in category 'as yet unclassified') -----
  postloadOver: oldDefinition
+ 	
  	SystemOrganization categories:
  		(self
  			reorderCategories: SystemOrganization categories
  			original: (oldDefinition ifNil: [#()] ifNotNil: [oldDefinition categories]))!

Item was added:
+ ----- Method: MCClassDefinition>>setType: (in category 'initializing') -----
+ setType: typeSymbol
+ 	"Set the value of type"
+ 
+ 	type := 	name = #CompiledMethod ifTrue: [ #compiledMethod ] ifFalse: [ typeSymbol ].
+ !

Item was added:
+ ----- Method: MCClassDefinition>>setPoolDictionaryNames: (in category 'accessing') -----
+ setPoolDictionaryNames: poolArray
+ 	self addVariables: poolArray ofType: MCPoolImportDefinition.!

Item was changed:
  ----- Method: MCFileDefinition class>>path:packageName: (in category 'as yet unclassified') -----
  path: aString packageName: packageString
+ 	^ (self new initializeWithPath: aString packageName: packageString) cached!
- 	^ self instanceLike: (self new initializeWithPath: aString packageName: packageString)!

Item was added:
+ ----- Method: MCMiscDefinition>>zapProperties (in category 'as yet unclassified') -----
+ zapProperties.
+ 
+ 	properties := nil!

Item was changed:
  ----- Method: MCOrganizationDefinition class>>categories: (in category 'as yet unclassified') -----
  categories: anArray
+ 	^ (self new categories: anArray) cached!
- 	^ self instanceLike: (self new categories: anArray)!

Item was added:
+ ----- Method: MCClassDefinition>>variables: (in category 'accessing') -----
+ variables: anObject
+ 	"Set the value of variables"
+ 
+ 	variables := anObject!

Item was changed:
  ----- Method: Class>>asClassDefinition (in category '*monticello') -----
  asClassDefinition
+ 	^ (MCClassDefinition new
+ 		setName: self name;
+ 		setSuperclassName: self superclass name;
+ 		setCategory: self category;
+ 		setInstVarNames: self instVarNames;
+ 		setClassVarNames: self classVarNames asSortedCollection;
+ 		setPoolDictionaryNames: self poolDictionaryNames;
+ 		setClassInstVarNames: self class instVarNames;
+ 		setType: self typeOfClass;
+ 		setMethodCategories: self organization categories class: self class organization categories;
+ 		setComment: self organization classComment stamp: self organization commentStamp;
+ 		setTraitComposition: self traitCompositionString class: self class traitCompositionString
+ 		yourself) cached
+ 		!
- 	^ MCClassDefinition
- 		name: self name
- 		superclassName: self superclass name
- 		traitComposition: self traitCompositionString
- 		classTraitComposition: self class traitCompositionString
- 		category: self category 
- 		instVarNames: self instVarNames
- 		classVarNames: self classVarNames
- 		poolDictionaryNames: self poolDictionaryNames
- 		classInstVarNames: self class instVarNames
- 		type: self typeOfClass
- 		comment: self organization classComment	 asString
- 		commentStamp: self organization commentStamp	!

Item was added:
+ ----- Method: MCClassDefinition>>organize:with: (in category 'installing') -----
+ organize: organizer with: list
+ 
+ 	list ifNil: [ ^ self ].
+ 	
+ 	organizer categories: (list copyWithAll: (organizer categories difference: list)).
+ 	organizer removeEmptyCategories.
+ !

Item was added:
+ ----- Method: MCClassDefinition>>classMethodCategories (in category 'accessing') -----
+ classMethodCategories
+ 	"Answer the value of classMethodCategories"
+ 
+ 	^ classMethodCategories!

Item was added:
+ ----- Method: MCClassDefinition>>setClassVarNames: (in category 'accessing') -----
+ setClassVarNames: cvarArray
+ 	self addVariables: cvarArray ofType: MCClassVariableDefinition.!

Item was added:
+ ----- Method: MCOrganizationDefinition>>zapProperties (in category 'as yet unclassified') -----
+ zapProperties.
+ 
+ 	properties := nil!

Item was added:
+ ----- Method: MCRepository>>storeVersionVerbatim: (in category 'storing') -----
+ storeVersionVerbatim: aVersion
+ 	self basicStoreVersion: aVersion.
+ 	self sendNotificationsForVersion: aVersion!

Item was changed:
  Object subclass: #MCDefinition
  	instanceVariableNames: ''
  	classVariableNames: 'Instances'
  	poolDictionaries: ''
  	category: 'Monticello-Base'!
  
+ !MCDefinition commentStamp: 'kph 3/29/2009 01:31' prior: 0!
- !MCDefinition commentStamp: 'kph 8/1/2007 10:10' prior: 0!
  Notes:
  
+ Given that monticello uses a binary fileOut, it is not possible to add instance vars to MCDefinition or its subclasses. With the benefit of hindsight this is a slight oversight by the original developers. It makes it almost impossible to improve this heirarchy without breaking compatibility. Aparently the binary was only intended as an optimisation, it was always intented to fall back to parsing the source.st.
- Given that monticello uses a binary fileOut, it is not possible to add instance vars to MCDefinition or its subclasses. With the benefit of hindsight this is a slight oversight by the original developers. It makes it almost impossible to improve this heirarchy without breaking compatibility.
  
  First of all we implement a flag which enables us to enforce MC compatibility #storeAsMC1CompatibleBinary.
  MCDefinition's #storeDataOn: defers to #storeMC1DataOn: which enforces a fixed number of instVars (defined in #storeMaxInstVarsForMC1 and a fixed output class even for specialized subclasses, which old MC's may not recognize.
  
  This ensures that our packages can be viewed in repositoryies by old MC implementations.
  
  For the future.
  1) We remove ignore any restriction upon the number of inst vars that we save, unless a class wants to imlement a specific policy of its own (MCMethodDefinition has a number of instVars which are not worth persisting). 
  2) We implement a properties interface in each class as best we can, we cannot implement it in MCDefinition because the format comatability has to be preserved with older MCs. So we place the instance var in subclasses of MCDefinition after their own inst vars.
+ 3) we change the loading code to be able to load if finds extra instance variables.
- 3) we change the loading code to not-care if when loading if finds extra instance variables. It puts the extra instance varables in the properties dictionary under #extraInstVars. Then when storing we write those extraInstVars so as to preseve the format that we were given.
  4) New subclasses save themselves as a known superclass with extra variables and their class name stored in property #class.
  
  Accessors to properties can be placed in MCDefinition to acceive the same effect as a local instVar. For an example see #because, used in #orphanedBecause:
  
  Other Monticellos need to implement the more tolerant #instVarAt: anInteger put: anObject in order to read our 'relaxed' format. At present I can see no other way of moving forward than to force all other monticellos to patch up!!
  
   !

Item was removed:
- ----- Method: MCClassDefinition class>>name:superclassName:traitComposition:classTraitComposition:category:instVarNames:classVarNames:poolDictionaryNames:classInstVarNames:type:comment:commentStamp: (in category 'instance creation') -----
- name: nameString
- superclassName: superclassString
- traitComposition: traitCompositionString
- classTraitComposition: classTraitCompositionString
- category: categoryString 
- instVarNames: ivarArray
- classVarNames: cvarArray
- poolDictionaryNames: poolArray
- classInstVarNames: civarArray
- type: typeSymbol
- comment: commentString
- commentStamp: stampString
- 	
- 	^ self instanceLike:
- 		(self new initializeWithName: nameString
- 					superclassName: superclassString
- 					traitComposition: traitCompositionString
- 					classTraitComposition: classTraitCompositionString
- 					category: categoryString 
- 					instVarNames: ivarArray
- 					classVarNames: cvarArray
- 					poolDictionaryNames: poolArray
- 					classInstVarNames: civarArray
- 					type: typeSymbol
- 					comment: commentString
- 					commentStamp: stampString)!

Item was removed:
- ----- Method: MCDefinition class>>initialize (in category '') -----
- initialize
- 	"MCDefinition initialize"
- 
- "for the future"
- 	"
- 	Preferences addPreference: #storeMC1CompatibleBinary
- 		categories: #('monticello') default: true
- 		balloonHelp: 'Save using MC1 compatibility, readable by older Monticello versions, but not extensible'
- 		
- 	"
- 	self clearInstances!

Item was removed:
- ----- Method: MCClassDefinition class>>name:superclassName:category:instVarNames:classVarNames:poolDictionaryNames:classInstVarNames:type:comment: (in category 'obsolete') -----
- name: nameString
- superclassName: superclassString
- category: categoryString 
- instVarNames: ivarArray
- classVarNames: cvarArray
- poolDictionaryNames: poolArray
- classInstVarNames: civarArray
- type: typeSymbol
- comment: commentString
- 	^ self 
- 		name: nameString
- 		superclassName: superclassString
- 		category: categoryString 
- 		instVarNames: ivarArray
- 		classVarNames: cvarArray
- 		poolDictionaryNames: poolArray
- 		classInstVarNames: civarArray
- 		type: typeSymbol
- 		comment: commentString
- 		commentStamp: nil!

Item was removed:
- ----- Method: MCClassDefinition class>>name:superclassName:category:instVarNames:comment: (in category 'obsolete') -----
- name: nameString
- superclassName: superclassString
- category: categoryString 
- instVarNames: ivarArray
- comment: commentString
- 	^ self	name: nameString
- 			superclassName: superclassString
- 			category: categoryString 
- 			instVarNames: ivarArray
- 			classVarNames: #()
- 			poolDictionaryNames: #()
- 			classInstVarNames: #()
- 			comment: commentString
- !

Item was removed:
- ----- Method: MCClassDefinition class>>name:superclassName:category:instVarNames:classVarNames:poolDictionaryNames:classInstVarNames:comment: (in category 'obsolete') -----
- name: nameString
- superclassName: superclassString
- category: categoryString 
- instVarNames: ivarArray
- classVarNames: cvarArray
- poolDictionaryNames: poolArray
- classInstVarNames: civarArray
- comment: commentString
- 	^ self	name: nameString
- 			superclassName: superclassString
- 			category: categoryString 
- 			instVarNames: ivarArray
- 			classVarNames: cvarArray
- 			poolDictionaryNames: poolArray
- 			classInstVarNames: civarArray
- 			type: #normal
- 			comment: commentString
- !

Item was removed:
- ----- Method: MCClassDefinition>>initializeWithName:superclassName:traitComposition:classTraitComposition:category:instVarNames:classVarNames:poolDictionaryNames:classInstVarNames:type:comment:commentStamp: (in category 'initializing') -----
- initializeWithName: nameString
- superclassName: superclassString
- traitComposition: traitCompositionString
- classTraitComposition: classTraitCompositionString
- category: categoryString 
- instVarNames: ivarArray
- classVarNames: cvarArray
- poolDictionaryNames: poolArray
- classInstVarNames: civarArray
- type: typeSymbol
- comment: commentString
- commentStamp: stampStringOrNil
- 	name := nameString asSymbol.
- 	self setSuperclassName: superclassString.
- 	self traitComposition: traitCompositionString.
- 	self classTraitComposition:  classTraitCompositionString.
- 	category := categoryString.
- 	name = #CompiledMethod ifTrue: [type := #compiledMethod] ifFalse: [type := typeSymbol].
- 	comment := commentString withSqueakLineEndings.
- 	commentStamp := stampStringOrNil ifNil: [self defaultCommentStamp].
- 	variables := OrderedCollection  new.
- 	self addVariables: ivarArray ofType: MCInstanceVariableDefinition.
- 	self addVariables: cvarArray ofType: MCClassVariableDefinition.
- 	self addVariables: poolArray ofType: MCPoolImportDefinition.
- 	self addVariables: civarArray ofType: MCClassInstanceVariableDefinition.!

Item was removed:
- ----- Method: MCClassDefinition class>>name:superclassName:category:instVarNames:classVarNames:poolDictionaryNames:classInstVarNames:type:comment:commentStamp: (in category 'instance creation') -----
- name: nameString
- superclassName: superclassString
- category: categoryString 
- instVarNames: ivarArray
- classVarNames: cvarArray
- poolDictionaryNames: poolArray
- classInstVarNames: civarArray
- type: typeSymbol
- comment: commentString
- commentStamp: stampString
- 	^ self instanceLike:
- 		(self new initializeWithName: nameString
- 					superclassName: superclassString
- 					traitComposition: '{}'
- 					classTraitComposition: '{}'
- 					category: categoryString 
- 					instVarNames: ivarArray
- 					classVarNames: cvarArray
- 					poolDictionaryNames: poolArray
- 					classInstVarNames: civarArray
- 					type: typeSymbol
- 					comment: commentString
- 					commentStamp: stampString)!

Item was removed:
- ----- Method: MCTraitDefinition class>>name:traitComposition:category:comment:commentStamp: (in category 'as yet unclassified') -----
- name: classNameString traitComposition:  traitCompositionString category:  categoryString comment:  commentString commentStamp:   commentStamp
- 	^ self instanceLike:
- 		(self new initializeWithName: classNameString 
- 			traitComposition:  traitCompositionString
- 			category:  categoryString
- 			comment:  commentString  
- 			commentStamp:   commentStamp)
- !

Item was removed:
- ----- Method: MCClassDefinition>>initializeWithName:superclassName:category:instVarNames:classVarNames:poolDictionaryNames:classInstVarNames:type:comment:commentStamp: (in category 'initializing') -----
- initializeWithName: nameString
- superclassName: superclassString
- category: categoryString 
- instVarNames: ivarArray
- classVarNames: cvarArray
- poolDictionaryNames: poolArray
- classInstVarNames: civarArray
- type: typeSymbol
- comment: commentString
- commentStamp: stampStringOrNil
- 	name := nameString asSymbol.
- 	self setSuperclassName: superclassString.
- 	category := categoryString.
- 	name = #CompiledMethod ifTrue: [type := #compiledMethod] ifFalse: [type := typeSymbol].
- 	comment := commentString withSqueakLineEndings.
- 	commentStamp := stampStringOrNil ifNil: [self defaultCommentStamp].
- 	variables := OrderedCollection  new.
- 	self addVariables: ivarArray ofType: MCInstanceVariableDefinition.
- 	self addVariables: cvarArray ofType: MCClassVariableDefinition.
- 	self addVariables: poolArray ofType: MCPoolImportDefinition.
- 	self addVariables: civarArray ofType: MCClassInstanceVariableDefinition.!

Item was removed:
- ----- Method: MCClassDefinition>>classTraitComposition: (in category 'testing') -----
- classTraitComposition: aString
- 	aString = '{}' ifTrue: [ ^ self ].
- 	classTraitComposition := aString!

Item was removed:
- ----- Method: MCTraitDefinition>>initializeWithName:traitComposition:category:comment:commentStamp: (in category 'initializing') -----
- initializeWithName: classNameString 
- 	traitComposition:  traitCompositionString
- 	category:  categoryString
- 	comment:  commentString  
- 	commentStamp:   commentStampString
- 					
- 		name := classNameString asSymbol.
- 		self traitComposition: traitCompositionString.
- 	     category := categoryString.
- 		comment := commentString withSqueakLineEndings.
- 		commentStamp :=  commentStampString ifNil: [self defaultCommentStamp]
- !

Item was removed:
- ----- Method: MCClassDefinition>>traitComposition: (in category 'testing') -----
- traitComposition: aString
- 	aString = '{}' ifTrue: [ ^ self ].
- 	traitComposition := aString!



More information about the Packages mailing list