[Pkg] SystemEditor: SystemEditor-mtf.150.mcz

squeak-dev-noreply at lists.squeakfoundation.org squeak-dev-noreply at lists.squeakfoundation.org
Thu Oct 30 05:42:43 UTC 2008


A new version of SystemEditor was added to project SystemEditor:
http://www.squeaksource.com/SystemEditor/SystemEditor-mtf.150.mcz

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

Name: SystemEditor-mtf.150
Author: mtf
Time: 29 October 2008, 10:42:16 pm
UUID: 4ecd5671-b3c8-43e3-892b-067d830f25fc
Ancestors: SystemEditor-mtf.149, SystemEditor-mtf.147

- added edPostLoad hook to editors and decorators
- stubbed out the hooks available to ClassDecorators
- moved subclass list maintainance out of ClassExporter and into a decorator, where it won't bother traits
- made subclass list maintainance a part of editor expansion stage
- gave SystemEditor>>edExpandEditors true recursion detection


=============== Diff against SystemEditor-mtf.149 ===============

Item was added:
+ ----- Method: SubclassListDecorator>>for: (in category 'initialize-release') -----
+ for: aClassEditor
+ 	parent := aClassEditor.
+ 	additions := IdentitySet new.
+ 	removals := IdentitySet new.!

Item was changed:
  ----- Method: SystemEditor>>commit (in category 'building') -----
  commit
  	| migration export |
  	showProgress ifNil: [showProgress := false].
  	self validate.
  
  	self edExpandEditors.
  
  	migration := MigrationTransaction new.
  	self edPrepareMigration: migration.
  
  	export := ClassExporter on: subject.
  	self edPrepareExport: export.
  
  	showProgress ifTrue: [(1 to: 2) do: [:ea | ] displayingProgress: 'Committing...'].
  	[migration commit.
  	export commit.
+ 	self edPostLoad.
  	self edCommitRemovals.
  	self edRecategorize.] valueUnpreemptively.
  	
  	^ true!

Item was added:
+ ----- Method: SystemEditor>>edPostLoad (in category 'building') -----
+ edPostLoad
+ 	additions do: [:ea | ea edPostLoad]!

Item was added:
+ ----- Method: ClassEditor>>edExpandSubclasses (in category 'building') -----
+ edExpandSubclasses
+ "Make sure my subclasses get recompiled if my bindings have changed"
+ 	| subclasses |
+ 	self edRequiresSubclassRebuild ifFalse: [^ #()].
+ 	subclasses := self subclasses.
+ 	subclasses do: [:ea | ea edInvalidateSuperclass].
+ 	^ subclasses!

Item was added:
+ ----- Method: ClassEditor>>edExpandSuperclass (in category 'building') -----
+ edExpandSuperclass
+ "Fix up subclass references to myself in my old and new superclasses"
+ 
+ 	| newSuperclass oldSuperclass newSupereditor oldSupereditor |
+ 	newSuperclass := self superclassOrEditor.
+ 	newSuperclass edIsEditor ifTrue: [newSuperclass := newSuperclass  subject].
+ 	oldSuperclass := self subject ifNotNil: [self subject superclass].
+ 	oldSuperclass == newSuperclass ifTrue: [^ #()].
+ 
+ 	newSupereditor := self environment edEditorFor: newSuperclass.
+ 	newSupereditor addSubclass: self.
+ 	oldSuperclass ifNil: [^ Array with: newSupereditor].
+ 
+ 	oldSupereditor := self environment edEditorFor: oldSuperclass.
+ 	oldSupereditor removeSubclass: self.
+ 	^ Array with: oldSupereditor with: newSupereditor!

Item was added:
+ ----- Method: ClassDecorator>>validate (in category 'validating') -----
+ validate
+ "Raise an error if the build should not proceed"!

Item was added:
+ ClassDecorator subclass: #SubclassListDecorator
+ 	instanceVariableNames: 'parent additions removals'
+ 	classVariableNames: ''
+ 	poolDictionaries: ''
+ 	category: 'SystemEditor-Editors'!
+ 
+ !SubclassListDecorator commentStamp: 'mtf 10/29/2008 13:56' prior: 0!
+ I remember what subclasses were added to or removed from my parent. Since the subclass list can be nil at times, I cannot migrate it, so I work in edPostLoad!

Item was added:
+ ----- Method: ClassEditor>>removeSubclass: (in category 'reflecting') -----
+ removeSubclass: aClassEditor
+ 	(self decorateWith: SubclassListDecorator) removeSubclass: aClassEditor!

Item was added:
+ ----- Method: SubclassListDecorator>>edPostLoad (in category 'building') -----
+ edPostLoad
+ 	| product |
+ 	product := parent product.
+ 	removals do: [:ea | product removeSubclass: ea product].
+ 	additions do: [:ea | product addSubclass: ea product].!

Item was added:
+ ----- Method: ClassDecorator>>edRequiresRecompile (in category 'building') -----
+ edRequiresRecompile
+ "Answer true if I require my client and all subclasses to be recompiled"
+ 	^ false!

Item was changed:
  ----- Method: SystemEditor>>edExpandEditors (in category 'building') -----
  edExpandEditors
+ 	| queue editor remembered |
+ 	remembered := IdentitySet new.
- 	| queue editor |
  	queue := additions values asOrderedCollection.
+ 	[queue isEmpty] whileFalse: [editor := queue removeFirst.
+ 		(remembered includes: editor) ifFalse: [
+ 			remembered add: editor.
+ 			queue addAll: editor edExpand]]
- 	[queue isEmpty] whileFalse: 
- 		[editor := queue removeFirst.
- 		editor subject ifNotNil: [
- 			queue addAll:  editor edExpand]]
  			
  			!

Item was added:
+ ----- Method: SubclassListDecorator>>removeSubclass: (in category 'accessing') -----
+ removeSubclass: aClassEditor
+ 	removals add: aClassEditor.
+ 	additions remove: aClassEditor ifAbsent: [].!

Item was added:
+ ----- Method: ClassDecorator>>edBuild (in category 'building') -----
+ edBuild
+ "Build what needs to be built into my client's product"!

Item was added:
+ ----- Method: ClassDecorator>>edPostLoad (in category 'building') -----
+ edPostLoad
+ "Do something after the migration is finished"!

Item was added:
+ ----- Method: ClassEditor>>addSubclass: (in category 'reflecting') -----
+ addSubclass: aClassEditor
+ 	(self decorateWith: SubclassListDecorator) addSubclass: aClassEditor!

Item was added:
+ ----- Method: ClassDecorator>>edRequiresBuild (in category 'building') -----
+ edRequiresBuild
+ "Answer true if I need my client to be built afresh"
+ 	^ false!

Item was changed:
  ----- Method: ClassEditor>>edExpand (in category 'building') -----
  edExpand
+ 	^ self edExpandSubclasses, self edExpandSuperclass!
- 	| subclasses |
- 	self edRequiresSubclassRebuild ifFalse: [^ #()].
- 	subclasses := self subclasses.
- 	subclasses do: [:ea | ea edInvalidateSuperclass].
- 	^ subclasses!

Item was changed:
  ----- Method: ClassEditor>>edBuild (in category 'building') -----
  edBuild
  	| meta |
  	meta := self class edBuild.
  	product := subject ifNil: [meta new]
  				ifNotNil: [meta adoptInstance: subject from: subject class].
  	product
  		superclass: self edSuperclass;
  		setFormat: self format;
  		setName: self name;
  		setInstVarNames: self instVarNames;
  		classPoolFrom: self;
  		instVarNamed: #sharedPools put: self sharedPools;
  		organization: self organization edBuild.
  	"Create a temporary MethodDictionary to catch code written by SyntaxError dialogs. MethodDictionaryEditor will overwrite this. See MethodEditor>>compileFor:"
  	product methodDictionary: MethodDictionary new.
+ 	self decoratorsDo: [:ea | ea edBuild].
- 	self name == #NSByteStream ifTrue: [self halt].
- 	self decoratorsDo: [:ea | self halt. ea edBuild].
  
  	"Class methods should be compiled before instance methods,
  	since #compilerClass may be among the class methods.
  	Class methods should be compiled after installing class and pool variables"
  	product class methodDictionary: (self class methods buildFor: self class).
  	product methodDictionary: (self methods buildFor: self).
  	^product!

Item was changed:
  ----- Method: ClassExporter>>export: (in category 'private') -----
  export: aClass
- 	((aClass isBehavior) and: [aClass superclass notNil]
- 		"Don't add aClass as subclass if a subclass exists that will become: aClass.
- 			This can be checked by comparing the names. Otherwise, redundent
- 			subclass entries appear, which makes
- 			SystemNavigation>>allBehaviorsDo: find classes twice"
- 		and: [aClass superclass subclasses noneSatisfy: [:ea | ea name = aClass name]])
- 		ifTrue: [aClass superclass addSubclass: aClass].
  	(environment includesKey: aClass name)
  		ifTrue: [self replace: aClass]
  		ifFalse: [environment at: aClass name put: aClass]!

Item was added:
+ ----- Method: SubclassListDecorator>>addSubclass: (in category 'accessing') -----
+ addSubclass: aClassEditor
+ 	additions add: aClassEditor.
+ 	removals remove: aClassEditor ifAbsent: [].!

Item was added:
+ ----- Method: ClassEditor>>edPostLoad (in category 'building') -----
+ edPostLoad
+ 	self decoratorsDo: [:ea | ea edPostLoad]!

Item was added:
+ ----- Method: ClassDecorator>>edPrepareMigration: (in category 'building') -----
+ edPrepareMigration: txn
+ "Prepare a migration, if necessary"!

Item was changed:
  Object subclass: #ClassExporter
  	instanceVariableNames: 'environment classes oldClasses newClasses'
  	classVariableNames: ''
  	poolDictionaries: ''
  	category: 'SystemEditor-Editors'!
+ 
+ !ClassExporter commentStamp: 'mtf 10/28/2008 18:55' prior: 0!
+ This class does a few things. 
+ - The second step (becomeForward:)of ClassBuilder>>update:to:
+ - add each class to its superclass's subclasses list
+ - add each class to the SystemDictionary Smalltalk!

Item was removed:
- ----- Method: ClassDecorator class>>decoratorsFor: (in category 'as yet unclassified') -----
- decoratorsFor: anEditor
- 	^ self allSubclasses
- 		collect: [:class | class for: anEditor]
- 		thenSelect: [:ea | ea notNil]!



More information about the Packages mailing list