[Pkg] SystemEditor: SystemEditor-Squeak-mtf.160.mcz

squeak-dev-noreply at lists.squeakfoundation.org squeak-dev-noreply at lists.squeakfoundation.org
Wed Nov 26 23:04:41 UTC 2008


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

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

Name: SystemEditor-Squeak-mtf.160
Author: mtf
Time: 26 November 2008, 4:04:25 pm
UUID: dffd68d7-7612-40f1-903e-7b5846fa620a
Ancestors: SystemEditor-Squeak-mtf.159

made building work in debug mode, and made debug mode the default

=============== Diff against SystemEditor-Squeak-mtf.159 ===============

Item was added:
+ ----- Method: Behavior>>edAllInstVarNames (in category '*systemeditor-squeak') -----
+ edAllInstVarNames
+ 	^ self allInstVarNames!

Item was added:
+ ----- Method: RootMetaclassEditor>>edAllInstVarNames (in category 'accessing') -----
+ edAllInstVarNames
+ 	^ #()!

Item was changed:
+ ----- Method: SystemEditor>>debug (in category 'debugging') -----
- ----- Method: SystemEditor>>debug (in category 'accessing') -----
  debug
  "see MetaclassEditor>>isDebuggingAsEditor"
  
+ 	^ debug ifNil: [true]!
- 	^ debug ifNil: [false]!

Item was added:
+ ----- Method: ClassDescriptionEditor>>edAllInstVarNames (in category 'accessing') -----
+ edAllInstVarNames
+ 	^ self superclassOrEditor edAllInstVarNames , self edInstVarNames!

Item was changed:
  ----- Method: ClassDescriptionEditor>>instVarNames (in category 'editing') -----
  instVarNames
+ 	^ self edInstVarNames!
- 	^ instVarNames ifNil: [self subject instVarNames]!

Item was changed:
  AbstractEditor subclass: #PureBehaviorEditor
+ 	instanceVariableNames: 'superclass methodDict format subject product system methods organization properties decorators compilerClass'
- 	instanceVariableNames: 'superclass methodDict format subject product system methods organization properties decorators'
  	classVariableNames: 'ReservedNames'
  	poolDictionaries: ''
  	category: 'SystemEditor-Squeak'!

Item was changed:
  ----- Method: ClassDescriptionEditor>>instSize (in category 'reflecting') -----
  instSize
+ 	^ self edInstSize!
- 	^ self instVarNames size + self superclassOrEditor instSize!

Item was changed:
  ----- Method: MetaclassEditor>>edBuild (in category 'building') -----
  edBuild
+ 	| class |
- 	| result class |
  	class := self subject ifNil: [Metaclass] ifNotNil: [self subject class].
+ 	product := class basicNew.
- 	result := class basicNew.
  	"Create a temporary MethodDictionary to catch code written by SyntaxError dialogs. MethodDictionaryEditor will overwrite this. See MethodEditor>>compileFor:"
+ 	product
- 	result
  		superclass: self edSuperclass
  		methodDictionary: MethodDictionary new
  		format: self format;		
  		organization: self organization edBuild.
+ 	product setInstVarNames: self edInstVarNames.
- 	result setInstVarNames: self instVarNames.
  	self decoratorsDo: [:ea | ea edBuildInto: product].
+ 	^ product!
- 	^ result!

Item was added:
+ ----- Method: Behavior>>edInstSize (in category '*systemeditor-squeak') -----
+ edInstSize
+ 	^ self instSize!

Item was added:
+ ----- Method: RootClassEditor>>edInstSize (in category 'accessing') -----
+ edInstSize
+ 	^ 0!

Item was added:
+ ----- Method: RootClassEditor>>edAllInstVarNames (in category 'accessing') -----
+ edAllInstVarNames
+ 	^ #()!

Item was added:
+ ----- Method: Behavior>>edInstVarNames (in category '*systemeditor-squeak') -----
+ edInstVarNames
+ 	^ self instVarNames!

Item was added:
+ ----- Method: ClassDescriptionEditor>>edInstSize (in category 'accessing') -----
+ edInstSize
+ 	^ self edInstVarNames size + self superclassOrEditor edInstSize!

Item was changed:
  ClassDescriptionEditor subclass: #ClassEditor
+ 	instanceVariableNames: 'name classVarNames sharedPools category'
- 	instanceVariableNames: 'name classVarNames sharedPools category compilerClass'
  	classVariableNames: ''
  	poolDictionaries: ''
  	category: 'SystemEditor-Squeak'!

Item was added:
+ ----- Method: ClassDescriptionEditor>>edInstVarNames (in category 'accessing') -----
+ edInstVarNames
+ 	^ instVarNames ifNil: [self subject instVarNames]!

Item was added:
+ ----- Method: ClassDescriptionEditor>>edSuperFormat (in category 'building') -----
+ edSuperFormat
+ 	^ self superclassOrEditor 
+ 		ifNotNilDo: [ :ed | ClassFormat fromBits: ed format ]
+ 		ifNil: [ ClassFormat named ]!

Item was changed:
  ----- Method: ClassEditor>>ensuredCompilerClass (in category 'accessing') -----
  ensuredCompilerClass
  "Answer my  product's compilerClass, building it if necessary"
  
  	| methodEditor method |
+ 	super ensuredCompilerClass ifNotNil: [^ compilerClass].
- 	compilerClass ifNotNil: [^ compilerClass].
  
+ 	"If we get here, this package is using a compiler that does not yet exist in the system. 
+ 	Compile and run the #compilerClass method it in the context of the system editor.
+ 	Due to how ClassEditor implements #bindingOf:, this will answer the editor for the right compiler"
- 	"Normal case: the compiler is already in the system. Check to see if I have a newer version"
- 	self product compilerClass ifNotNil: [
- 		compilerClass := self system classOrEditorFor: self product compilerClass.
- 		compilerClass edIsEditor ifTrue: [compilerClass := compilerClass product].
- 		^ compilerClass].
- 
- 	"If we get here, this package is presumably using a compiler that does not yet exist in the system. 
- 	Evil evil hackery. Get the method editor, compile it in the context of the system editor,
- 	and run it to find the editor for the new compiler"
  	methodEditor := self class edUltimateMethodAt: #compilerClass.
  	method := methodEditor compileForClass: self using: Compiler new.
  	compilerClass := (self new executeMethod: method) product.
  	compilerClass ifNil: [self error: 'Unknown compiler'].
  	^ compilerClass!

Item was changed:
  ----- Method: ClassDescriptionEditor>>instanceVariablesString (in category 'reflecting') -----
  instanceVariablesString
  	^ String streamContents: 
  		[:stream | 
+ 		self edInstVarNames
- 		self allInstVarNames
  			do: [:ea | stream nextPutAll: ea]
  			separatedBy: [stream nextPut: $ ]]!

Item was changed:
  ----- Method: ClassDescriptionEditor>>allInstVarNames (in category 'reflecting') -----
  allInstVarNames
+ 	^ self edAllInstVarNames!
- 	^ self superclassOrEditor allInstVarNames , self instVarNames!

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 edInstVarNames;
- 		setInstVarNames: self instVarNames;
  		classPoolFrom: self;
  		instVarNamed: #sharedPools put: self sharedPools;
  		organization: self organization edBuild.
  
  		"category and environment are not set here.
  		category will be lazily computed sometime after 
  			SystemEditor >> edRecatogorize runs. (see Class >> category)
  		environment can be left nil, since it has a default value"
  
  	"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 edBuildInto: product].
  
  	"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: ClassDescriptionEditor>>edClassFormat (in category 'building') -----
  edClassFormat
  	^ ClassFormat
+ 		size: self edInstSize
- 		size: self instSize
  		type: self typeOfClass
  		index: self indexIfCompact!

Item was changed:
  ----- Method: ClassDescriptionEditor>>validateInstVarNames (in category 'validating') -----
  validateInstVarNames
+ 	self edInstVarNames do: 
- 	self instVarNames do: 
  		[ :ea | 
  		(ReservedNames includes: ea) ifTrue: [ IllegalVariableName signal ].
+ 		(self superclassOrEditor edAllInstVarNames includes: ea) ifTrue: [ IllegalVariableName signal ].
+ 		self subclassesOrEditors do: [ :class | (class edInstVarNames includes: ea) ifTrue: [ IllegalVariableName signal ] ] ]!
- 		(self superclassOrEditor allInstVarNames includes: ea) ifTrue: [ IllegalVariableName signal ].
- 		self subclassesOrEditors do: [ :class | (class instVarNames includes: ea) ifTrue: [ IllegalVariableName signal ] ] ]!

Item was added:
+ ----- Method: RootMetaclassEditor>>edInstSize (in category 'accessing') -----
+ edInstSize
+ 	^ 0!

Item was changed:
  ----- Method: PureBehaviorEditor>>ensuredCompilerClass (in category 'accessing') -----
  ensuredCompilerClass
  "Answer the compiler for my methods, building it if necessary"
  
+ 	compilerClass ifNotNil: [^ compilerClass].
+ 
+ 	"Check to see if I have a newer version of the compiler"
+ 	self product compilerClass ifNotNil: [
+ 		compilerClass := self system classOrEditorFor: self product compilerClass.
+ 		compilerClass edIsEditor ifTrue: [compilerClass := compilerClass product]].
+ 	^ compilerClass!
- 	^ self product compilerClass!

Item was removed:
- ----- Method: RootClassEditor>>instSize (in category 'reflecting') -----
- instSize
- 	^ 0!

Item was removed:
- ----- Method: RootMetaclassEditor>>instSize (in category 'reflecting') -----
- instSize
- 	^ 0!

Item was removed:
- ----- Method: RootMetaclassEditor>>allInstVarNames (in category 'reflecting') -----
- allInstVarNames
- 	^ #()!

Item was removed:
- ----- Method: ClassEditor>>edSuperFormat (in category 'building') -----
- edSuperFormat
- 	^ self superclassOrEditor 
- 		ifNotNilDo: [ :ed | ClassFormat fromBits: ed format ]
- 		ifNil: [ ClassFormat named ]!

Item was removed:
- ----- Method: RootClassEditor>>allInstVarNames (in category 'reflecting') -----
- allInstVarNames
- 	^ #()!



More information about the Packages mailing list