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

squeaksource-noreply at iam.unibe.ch squeaksource-noreply at iam.unibe.ch
Wed Aug 13 07:46:12 UTC 2008


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

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

Name: SystemEditor-mtf.115
Author: mtf
Time: 13 August 2008, 12:44:35 am
UUID: 9817a1d9-91ee-4f7f-b4b4-bc9cf4856f30
Ancestors: SystemEditor-mtf.114

renamed the Behavior-derived MetaclassEditor to OldMetaclassEditor, and created a new MetaclassEditor derived from ClassDescriptionEditor

I believe that MetaclassEditor derives more from ClassDescriptionEditor than from Behavior, so I'll duplicate the necessary parts of Behavior rather than those of ClassDescriptionEditor

=============== Diff against SystemEditor-mtf.114 ===============

Item was changed:
  ----- Method: MetaclassEditor>>definitionST80 (in category 'reflecting') -----
  definitionST80
  	^ String streamContents: 
  		[:strm |
  		strm print: self;
  			crtab;
  			nextPutAll: 'instanceVariableNames: ';
  			store: self instanceVariablesString]!

Item was added:
+ ----- Method: OldMetaclassEditor>>subject (in category 'accessing') -----
+ subject
+ 	^ editor subject ifNotNilDo: [:subject | subject class]!

Item was changed:
  ----- Method: RootClassEditor class>>classMetaclassEditor (in category 'instance creation') -----
  classMetaclassEditor
+ 	^ OldRootMetaclassEditor!
- 	^ RootMetaclassEditor!

Item was added:
+ ----- Method: OldMetaclassEditor>>methods (in category 'accessing') -----
+ methods
+ 	^ methods ifNil: [methods := MethodDictionaryEditor for: self]!

Item was changed:
  ----- Method: MetaclassEditor>>edMethodsDo: (in category 'building') -----
  edMethodsDo: aBlock
  	methods ifNotNil: [methods do: aBlock]!

Item was added:
+ ----- Method: OldMetaclassEditor>>theNonMetaClass (in category 'reflecting') -----
+ theNonMetaClass
+ 	^ editor!

Item was added:
+ OldMetaclassEditor subclass: #OldRootMetaclassEditor
+ 	instanceVariableNames: ''
+ 	classVariableNames: ''
+ 	poolDictionaries: ''
+ 	category: 'SystemEditor-Editors'!

Item was added:
+ ----- Method: OldRootMetaclassEditor class>>classClassEditor (in category 'instance creation') -----
+ classClassEditor
+ 	^ RootClassEditor!

Item was changed:
  ----- Method: MetaclassEditor>>indexIfCompact (in category 'reflecting') -----
  indexIfCompact
  	self subject ifNotNil: [^ self subject indexIfCompact].
  	^ 0!

Item was added:
+ ----- Method: RootMetaclassEditor>>edRequiresBuild (in category 'building') -----
+ edRequiresBuild
+ 	^ false!

Item was added:
+ ----- Method: OldRootMetaclassEditor>>product (in category 'building') -----
+ product
+ 	^ nil!

Item was added:
+ ----- Method: OldMetaclassEditor>>superclass: (in category 'editing') -----
+ superclass: aClass 
+ 	superEditor := self system edEditorFor: aClass!

Item was changed:
  ----- Method: MetaclassEditor>>removeInstVarName: (in category 'editing') -----
  removeInstVarName: aString 
  	instVarNames ifNil: [instVarNames := self subject instVarNames].
  	instVarNames := instVarNames copyWithout: aString!

Item was changed:
  ----- Method: MetaclassEditor>>edBuild (in category 'building') -----
  edBuild
  	| result class |
  	class := self subject ifNil: [Metaclass] ifNotNilDo: [:subject | subject class].
  	result := class basicNew.
  	result
  		superclass: self edSuperclass
  		methodDictionary: MethodDictionary new
  		format: self format;		
  		organization: self organization build.
  	result setInstVarNames: self instVarNames.
  	^ result!

Item was added:
+ ----- Method: OldMetaclassEditor>>compile:classified:withStamp:notifying:logSource: (in category 'editing') -----
+ compile: source classified: category withStamp: aString notifying: anObject logSource: aBoolean
+ 	| cm |
+ 	cm := MethodEditor
+ 			source: source
+ 			classified: category
+ 			stamp: aString
+ 			notifying: anObject
+ 			logging: aBoolean.
+ 	self methods add: cm.!

Item was added:
+ ----- Method: OldMetaclassEditor>>edMethodAt:ifAbsent: (in category 'editing') -----
+ edMethodAt: aSelector ifAbsent: aBlock
+ 	^ self methods at: aSelector ifAbsent: aBlock!

Item was added:
+ ----- Method: OldMetaclassEditor>>instVarNames (in category 'reflecting') -----
+ instVarNames
+ 	"Override the implemenation in Behavior. That will return the inst vars of 
+ 	ClassEditor, but we want the inst vars of the subject's class."
+ 
+ 	self isDebuggingAsEditor ifTrue: [^ super instVarNames].
+ 	^ instVarNames ifNil: [self subject instVarNames]!

Item was changed:
  ----- Method: MetaclassEditor class>>classClassEditor (in category 'instance creation') -----
  classClassEditor
  "Answers the class of my instance-side editor"
  
  	^ ClassEditor!

Item was added:
+ ----- Method: RootMetaclassEditor>>typeOfClass (in category 'reflecting') -----
+ typeOfClass
+ 	^ #normal!

Item was changed:
  ----- Method: ClassEditor class>>classMetaclassEditor (in category 'instance creation') -----
  classMetaclassEditor
  "Answer the class of editors for my instances' cooresponding metaclass editor"
  
+ 	^ OldMetaclassEditor!
- 	^ MetaclassEditor!

Item was changed:
  ----- Method: MetaclassEditor>>isMeta (in category 'reflecting') -----
  isMeta
  	^ true!

Item was added:
+ ----- Method: OldMetaclassEditor class>>new (in category 'instance creation') -----
+ new
+ 	| instance |
+ 	instance := self basicNew.
+ 	instance
+ 		superclass: self classClassEditor
+ 		methodDictionary: MethodDictionary new
+ 		format: self classClassEditor format.
+ 	^ instance!

Item was added:
+ ----- Method: OldMetaclassEditor>>instSize (in category 'reflecting') -----
+ instSize
+ 	"Override the implemenation in Behavior, so that when inspecting the
+ 	ClassEditor, it will look like a regular Class"
+ 
+ 	self isDebuggingAsEditor ifTrue: [^ super instSize].
+ 	^ self instVarNames size + (self edSuperclass
+ 		ifNil: [0] ifNotNilDo: [:ed | ed instSize])!

Item was added:
+ ----- Method: OldMetaclassEditor>>classSide (in category 'reflecting') -----
+ classSide
+ 	^self theMetaClass!

Item was changed:
  ----- Method: MetaclassEditor>>system (in category 'accessing') -----
  system
  	^ editor system!

Item was changed:
  ----- Method: MetaclassEditor>>product (in category 'building') -----
  product
  	^ editor product class!

Item was added:
+ ----- Method: OldMetaclassEditor>>instanceVariableNames: (in category 'reflecting') -----
+ instanceVariableNames: instString
+ 	instVarNames := Scanner new scanFieldNames: instString!

Item was added:
+ ----- Method: OldMetaclassEditor>>format (in category 'reflecting') -----
+ format
+ "Override the implemenation in Behavior. That will return the format of ClassEditor, but we want the format of the subject's meta class"
+ 
+ 	^ self edClassFormat bits!

Item was changed:
  ----- Method: MetaclassEditor>>edRequiresBuild (in category 'building') -----
  edRequiresBuild
  	^ (superEditor ~~ nil) | (instVarNames ~~ nil) | (methods ~~ nil)!

Item was changed:
  ----- Method: MetaclassEditor>>classPool (in category 'reflecting') -----
  classPool
  	^ editor classPool!

Item was added:
+ ----- Method: OldRootMetaclassEditor class>>canEdit:for: (in category 'instance creation') -----
+ canEdit: anObject for: anEditor
+ 	^ false!

Item was changed:
  ----- Method: MetaclassEditor>>compiledMethodAt: (in category 'reflecting') -----
  compiledMethodAt: aSelector
  	^ self subjectDo: [:subject | subject compiledMethodAt: aSelector]!

Item was added:
+ ----- Method: OldMetaclassEditor>>definition (in category 'reflecting') -----
+ definition
+ 	^ self definitionST80!

Item was changed:
  ----- Method: MetaclassEditor>>compile:classified: (in category 'editing') -----
  compile: source classified: cat
  	^ self 
  		compile: source
  		classified: cat
  		withStamp: Utilities changeStamp
  		notifying: nil
  		logSource: self acceptsLoggingOfCompilation !

Item was added:
+ ----- Method: RootMetaclassEditor>>edRegisterEditor (in category 'initialize-release') -----
+ edRegisterEditor
+ "Do nothing"!

Item was added:
+ ----- Method: OldMetaclassEditor>>compile:classified:withStamp:notifying: (in category 'editing') -----
+ compile: source classified: cat withStamp: aString notifying: anObject
+ 	^ self 
+ 		compile: source
+ 		classified: cat
+ 		withStamp: aString
+ 		notifying: anObject
+ 		logSource: self acceptsLoggingOfCompilation !

Item was added:
+ ----- Method: OldMetaclassEditor>>isUniClass (in category 'reflecting') -----
+ isUniClass
+ 	"The debugger sometimes sends this message"
+ 	^ false!

Item was added:
+ ----- Method: OldMetaclassEditor>>acceptsLoggingOfCompilation (in category 'reflecting') -----
+ acceptsLoggingOfCompilation
+ 
+ 	^ self instanceSide acceptsLoggingOfCompilation!

Item was added:
+ ----- Method: OldMetaclassEditor>>superclass (in category 'reflecting') -----
+ superclass
+ 	| subjectSuperclass |
+ 	superEditor ifNotNil: [^ superEditor].
+ 	subjectSuperclass := self subject
+ 		ifNil: [Object]
+ 		ifNotNil: [self subject superclass].
+ 	^ self system edEditorFor: subjectSuperclass!

Item was added:
+ ----- Method: OldMetaclassEditor>>isDebuggingAsEditor (in category 'debugging') -----
+ isDebuggingAsEditor
+ 	"To be transparent enough to fool most existing software,
+ 	MetaclassEditors must answer their subject's instance variables when
+ 	sent the message allInstVarNames. However, this message is also used by
+ 	the debugger, inspector, and explorer, when inspecting ClassEditors, and
+ 	an inspector should see the real instance variables of ClassEditor rather
+ 	than those of the MetaclassEditor's subject. So there is a conflict of
+ 	interest already.
+ 	
+ 	But it gets worse. If you do open an inspector on an object that is
+ 	reporting wrong information about it's instance variables, Bad things
+ 	happen. Specifically, the inspector calls instVarAt: on an instance
+ 	variable that does not exist, leading to an error every time the display
+ 	is updated. Less severe, instVarAt: will answer nonsensical. 
+ 	
+ 	So I took the instance variable proxying behavior all the way so that it
+ 	successfully fools the debugger, inspector, and explorer into seeing
+ 	proxied instance variables (see the senders af this message if you want
+ 	to know how). But there is still the original problem that you, the
+ 	programmer want to see the real state of ClassEditor. That is where this
+ 	method comes in.
+ 	
+ 	If this method returns false, everybody sees the proxied instance
+ 	variables. This is the correct behavior. If this method returns false,
+ 	everyone sees the true instance variables of ClassEditor. This is
+ 	incorrect behavior, and breaks the Unit tests, but it is invaluable if
+ 	you are debugging ClassEditor.
+ 	
+ 	Just be sure to make sure this returns false whenever making a release"
+ 	^ false!

Item was added:
+ ----- Method: OldMetaclassEditor>>removeSelector: (in category 'editing') -----
+ removeSelector: aSymbol 
+ 	methods ifNil: [methods := MethodDictionaryEditor for: self].
+ 	methods remove: aSymbol.!

Item was added:
+ ----- Method: OldMetaclassEditor>>lookupSelector: (in category 'metaclass') -----
+ lookupSelector: aSelector
+ 	
+ 	"Override the implementation in Behavior to make ClassEditor
+ 	debuggable. The debugger calls this during simulated execution,
+ 	and since we override #includesSelector and #superclass to 
+ 	reflect on the subject, we get incorrect method dispatch."
+ 
+ 	| lookupClass dict |
+ 	lookupClass := self.
+ 	[lookupClass == nil] whileFalse: 
+ 		[dict := lookupClass instVarAt: 2.
+ 		(dict includesKey: aSelector)
+ 			ifTrue: [^ dict at: aSelector].
+ 		lookupClass := lookupClass instVarAt: 1].
+ 	^ nil!

Item was added:
+ ----- Method: OldMetaclassEditor>>edRequiresSubclassRebuild (in category 'building') -----
+ edRequiresSubclassRebuild
+ 	^ self subject
+ 		ifNotNilDo: [:subject | subject format ~= self format]
+ 		ifNil: [false]!

Item was changed:
  ----- Method: MetaclassEditor>>instanceSide (in category 'reflecting') -----
  instanceSide
  	^ self theNonMetaClass!

Item was added:
+ ----- Method: OldMetaclassEditor>>hasComment (in category 'reflecting') -----
+ hasComment
+ 	^ self instanceSide hasComment!

Item was changed:
  ----- Method: MetaclassEditor>>addInstVarName: (in category 'editing') -----
  addInstVarName: aString 
  	instVarNames ifNil: [instVarNames := self subject instVarNames].
  	instVarNames := instVarNames copyWith: aString!

Item was added:
+ ----- Method: OldMetaclassEditor>>compile:classified:notifying: (in category 'editing') -----
+ compile: source classified: cat notifying: anObject
+ 	^ self 
+ 		compile: source
+ 		classified: cat
+ 		withStamp: Utilities changeStamp
+ 		notifying: anObject
+ 		logSource: self acceptsLoggingOfCompilation !

Item was changed:
  ----- Method: MetaclassEditor>>printOn: (in category 'printing') -----
  printOn: aStream
  	aStream
  		nextPutAll: 'a MetaclassEditor on: ';
  		print: editor subject !

Item was changed:
  ----- Method: MetaclassEditor>>includesSelector: (in category 'reflecting') -----
  includesSelector: aSelector
  	^ (methods ifNil: [self subject] ifNotNil: [methods])
  		includesSelector: aSelector!

Item was changed:
  ----- Method: MetaclassEditor>>comment (in category 'reflecting') -----
  comment
  	^ self instanceSide comment!

Item was changed:
  ----- Method: MetaclassEditor>>environment (in category 'reflecting') -----
  environment
  	^ self system!

Item was changed:
  ----- Method: MetaclassEditor>>rearrangeInstVarNames: (in category 'editing') -----
  rearrangeInstVarNames: associations
  	"The associations are name -> pos and cover the subset
  	of vars that should be moved. The old just fill in the holes."
  
  	instVarNames := ClassEditor rearrangeVarNames: associations oldNames: instVarNames!

Item was changed:
  ----- Method: MetaclassEditor>>new (in category 'metaclass') -----
  new
  	^ editor := self basicNew!

Item was changed:
  ----- Method: MetaclassEditor>>name (in category 'reflecting') -----
  name
  	^ editor name, ' class'!

Item was changed:
  ----- Method: MetaclassEditor>>subjectDo: (in category 'accessing') -----
  subjectDo: aBlock
  	^ self subject
  		ifNotNilDo: [:subject | aBlock value: subject]
  		ifNil: [self error: 'key not found']!

Item was changed:
  ----- Method: MetaclassEditor>>edInitializeForNewClass (in category 'building') -----
  edInitializeForNewClass
  	superEditor := self system edEditorFor: Object class.
  	instVarNames := Array new.
  	methods := MethodDictionaryEditor for: self!

Item was changed:
  ----- Method: MetaclassEditor>>sourceCodeAt: (in category 'reflecting') -----
  sourceCodeAt: aSelector
  	^ self subjectDo: [:subject | subject sourceCodeAt: aSelector]!

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

Item was added:
+ ----- Method: RootMetaclassEditor class>>classClassEditor (in category 'instance creation') -----
+ classClassEditor
+ 	^ RootClassEditor!

Item was added:
+ ----- Method: OldRootMetaclassEditor>>allSuperclasses (in category 'reflecting') -----
+ allSuperclasses
+ 	^ OrderedCollection new!

Item was changed:
  ----- Method: MetaclassEditor>>edMethodAt: (in category 'editing') -----
  edMethodAt: aSelector
  	^ self methods at: aSelector!

Item was added:
+ ----- Method: OldRootMetaclassEditor>>subject (in category 'accessing') -----
+ subject
+ 	^ nil!

Item was added:
+ ----- Method: OldMetaclassEditor>>allInstVarNames (in category 'reflecting') -----
+ allInstVarNames
+ 	 "specialized in order to enable debugger to show as self"
+ 	
+ 	self isDebuggingAsEditor ifTrue: [^ super allInstVarNames].
+ 	^ self edSuperclass
+ 		ifNil: [self instVarNames copy]
+ 		ifNotNil: [self edSuperclass allInstVarNames, self instVarNames]!

Item was changed:
  ----- Method: MetaclassEditor>>methodDictionary (in category 'reflecting') -----
  methodDictionary
  	| methodEditor |
  	(methods isNil and: [self edRequiresRecompile not]) ifTrue: [^ self subject methodDictionary].
  	methodEditor := methods ifNil: [MethodDictionaryEditor for: self].
  	^ methodEditor buildFor: self!

Item was changed:
  ----- Method: MetaclassEditor>>definitionST80: (in category 'reflecting') -----
  definitionST80: isST80
  	^ isST80 ifTrue: [self definitionST80] ifFalse: [self definition]!

Item was added:
+ ----- Method: OldMetaclassEditor>>edSuperclass (in category 'building') -----
+ edSuperclass
+ 	^ superEditor
+ 		ifNil: [self subject superclass]
+ 		ifNotNil: [superEditor product]!

Item was changed:
  ----- Method: MetaclassEditor>>edClassFormat (in category 'building') -----
  edClassFormat
  	^ ClassFormat
  		size: self instSize
  		type: self typeOfClass
  		index: self indexIfCompact!

Item was added:
+ ----- Method: RootMetaclassEditor>>product (in category 'building') -----
+ product
+ 	^ nil!

Item was added:
+ ----- Method: OldMetaclassEditor>>typeOfClass (in category 'reflecting') -----
+ typeOfClass
+ 	^ #normal!

Item was added:
+ Behavior subclass: #OldMetaclassEditor
+ 	instanceVariableNames: 'editor superEditor instVarNames methods organization traitComposition'
+ 	classVariableNames: ''
+ 	poolDictionaries: ''
+ 	category: 'SystemEditor-Editors'!

Item was changed:
  ----- Method: MetaclassEditor>>browserDefinition: (in category 'reflecting') -----
  browserDefinition: style
  	^ self definition!

Item was added:
+ ----- Method: OldRootMetaclassEditor>>ultimateSourceCodeAt:ifAbsent: (in category 'reflecting') -----
+ ultimateSourceCodeAt: selector ifAbsent: aBlock
+ "Return the source code at selector, deferring to superclass if necessary"
+ 
+ 	^ aBlock value!

Item was changed:
  ----- Method: MetaclassEditor>>subject (in category 'accessing') -----
  subject
  	^ editor subject ifNotNilDo: [:subject | subject class]!

Item was added:
+ ----- Method: OldMetaclassEditor>>edIsEditor (in category 'testing') -----
+ edIsEditor
+ 	^ true!

Item was added:
+ ----- Method: OldRootMetaclassEditor>>allInstVarNames (in category 'reflecting') -----
+ allInstVarNames
+ 	^ #()!

Item was changed:
  ----- Method: MetaclassEditor>>methods (in category 'accessing') -----
  methods
  	^ methods ifNil: [methods := MethodDictionaryEditor for: self]!

Item was added:
+ ----- Method: OldMetaclassEditor>>theMetaClass (in category 'reflecting') -----
+ theMetaClass
+ 	^ self!

Item was added:
+ ----- Method: OldMetaclassEditor>>edRequiresRecompile (in category 'building') -----
+ edRequiresRecompile
+ 	^ instVarNames ~~ nil!

Item was added:
+ ----- Method: RootMetaclassEditor class>>canEdit:for: (in category 'instance creation') -----
+ canEdit: anObject for: anEditor
+ 	^ false!

Item was added:
+ ----- Method: OldMetaclassEditor>>definitionST80 (in category 'reflecting') -----
+ definitionST80
+ 	^ String streamContents: 
+ 		[:strm |
+ 		strm print: self;
+ 			crtab;
+ 			nextPutAll: 'instanceVariableNames: ';
+ 			store: self instanceVariablesString]!

Item was changed:
  ----- Method: MetaclassEditor>>theNonMetaClass (in category 'reflecting') -----
  theNonMetaClass
  	^ editor!

Item was added:
+ ----- Method: OldMetaclassEditor>>environment (in category 'reflecting') -----
+ environment
+ 	^ self system!

Item was added:
+ ----- Method: OldMetaclassEditor>>edMethodsDo: (in category 'building') -----
+ edMethodsDo: aBlock
+ 	methods ifNotNil: [methods do: aBlock]!

Item was changed:
+ ClassDescriptionEditor subclass: #MetaclassEditor
+ 	instanceVariableNames: 'editor'
- Behavior subclass: #MetaclassEditor
- 	instanceVariableNames: 'editor superEditor instVarNames methods organization traitComposition'
  	classVariableNames: ''
  	poolDictionaries: ''
  	category: 'SystemEditor-Editors'!

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

Item was added:
+ ----- Method: OldRootMetaclassEditor>>instSize (in category 'reflecting') -----
+ instSize
+ 	^ 0!

Item was changed:
  ----- Method: MetaclassEditor>>superclass: (in category 'editing') -----
  superclass: aClass 
  	superEditor := self system edEditorFor: aClass!

Item was added:
+ ----- Method: OldRootMetaclassEditor>>edRequiresRecompile (in category 'building') -----
+ edRequiresRecompile
+ 	^ false!

Item was changed:
  ----- Method: MetaclassEditor>>compile:classified:withStamp:notifying:logSource: (in category 'editing') -----
  compile: source classified: category withStamp: aString notifying: anObject logSource: aBoolean
  	| cm |
  	cm := MethodEditor
  			source: source
  			classified: category
  			stamp: aString
  			notifying: anObject
  			logging: aBoolean.
  	self methods add: cm.!

Item was changed:
  ----- Method: MetaclassEditor>>edMethodAt:ifAbsent: (in category 'editing') -----
  edMethodAt: aSelector ifAbsent: aBlock
  	^ self methods at: aSelector ifAbsent: aBlock!

Item was added:
+ MetaclassEditor subclass: #RootMetaclassEditor
+ 	instanceVariableNames: ''
+ 	classVariableNames: ''
+ 	poolDictionaries: ''
+ 	category: 'SystemEditor-Editors'!

Item was changed:
  ----- Method: MetaclassEditor>>instVarNames (in category 'reflecting') -----
  instVarNames
  	"Override the implemenation in Behavior. That will return the inst vars of 
  	ClassEditor, but we want the inst vars of the subject's class."
  
  	self isDebuggingAsEditor ifTrue: [^ super instVarNames].
  	^ instVarNames ifNil: [self subject instVarNames]!

Item was added:
+ ----- Method: OldMetaclassEditor>>definitionST80: (in category 'reflecting') -----
+ definitionST80: isST80
+ 	^ isST80 ifTrue: [self definitionST80] ifFalse: [self definition]!

Item was added:
+ ----- Method: OldMetaclassEditor>>edClassFormat (in category 'building') -----
+ edClassFormat
+ 	^ ClassFormat
+ 		size: self instSize
+ 		type: self typeOfClass
+ 		index: self indexIfCompact!

Item was added:
+ ----- Method: OldMetaclassEditor>>indexIfCompact (in category 'reflecting') -----
+ indexIfCompact
+ 	self subject ifNotNil: [^ self subject indexIfCompact].
+ 	^ 0!

Item was changed:
  ----- Method: MetaclassEditor class>>new (in category 'instance creation') -----
  new
  	| instance |
  	instance := self basicNew.
  	instance
  		superclass: self classClassEditor
  		methodDictionary: MethodDictionary new
  		format: self classClassEditor format.
  	^ instance!

Item was changed:
  ----- Method: MetaclassEditor>>instSize (in category 'reflecting') -----
  instSize
  	"Override the implemenation in Behavior, so that when inspecting the
  	ClassEditor, it will look like a regular Class"
  
  	self isDebuggingAsEditor ifTrue: [^ super instSize].
  	^ self instVarNames size + (self edSuperclass
  		ifNil: [0] ifNotNilDo: [:ed | ed instSize])!

Item was changed:
  ----- Method: MetaclassEditor>>classSide (in category 'reflecting') -----
  classSide
  	^self theMetaClass!

Item was added:
+ ----- Method: OldMetaclassEditor>>removeInstVarName: (in category 'editing') -----
+ removeInstVarName: aString 
+ 	instVarNames ifNil: [instVarNames := self subject instVarNames].
+ 	instVarNames := instVarNames copyWithout: aString!

Item was added:
+ ----- Method: OldMetaclassEditor>>edBuild (in category 'building') -----
+ edBuild
+ 	| result class |
+ 	class := self subject ifNil: [Metaclass] ifNotNilDo: [:subject | subject class].
+ 	result := class basicNew.
+ 	result
+ 		superclass: self edSuperclass
+ 		methodDictionary: MethodDictionary new
+ 		format: self format;		
+ 		organization: self organization build.
+ 	result setInstVarNames: self instVarNames.
+ 	^ result!

Item was changed:
  ----- Method: MetaclassEditor>>instanceVariableNames: (in category 'reflecting') -----
  instanceVariableNames: instString
  	instVarNames := Scanner new scanFieldNames: instString!

Item was changed:
  ----- Method: MetaclassEditor>>format (in category 'reflecting') -----
  format
  "Override the implemenation in Behavior. That will return the format of ClassEditor, but we want the format of the subject's meta class"
  
  	^ self edClassFormat bits!

Item was added:
+ ----- Method: OldMetaclassEditor class>>classClassEditor (in category 'instance creation') -----
+ classClassEditor
+ "Answers the class of my instance-side editor"
+ 
+ 	^ ClassEditor!

Item was added:
+ ----- Method: OldMetaclassEditor>>isMeta (in category 'reflecting') -----
+ isMeta
+ 	^ true!

Item was added:
+ ----- Method: OldMetaclassEditor>>product (in category 'building') -----
+ product
+ 	^ editor product class!

Item was added:
+ ----- Method: OldMetaclassEditor>>system (in category 'accessing') -----
+ system
+ 	^ editor system!

Item was changed:
  ----- Method: MetaclassEditor>>definition (in category 'reflecting') -----
  definition
  	^ self definitionST80!

Item was added:
+ ----- Method: OldMetaclassEditor>>edRequiresBuild (in category 'building') -----
+ edRequiresBuild
+ 	^ (superEditor ~~ nil) | (instVarNames ~~ nil) | (methods ~~ nil)!

Item was changed:
  ----- Method: MetaclassEditor>>organization (in category 'reflecting') -----
  organization
  	^ organization ifNil: [organization := OrganizationEditor for: self]!

Item was added:
+ ----- Method: RootMetaclassEditor>>allSuperclasses (in category 'reflecting') -----
+ allSuperclasses
+ 	^ OrderedCollection new!

Item was added:
+ ----- Method: OldMetaclassEditor>>classPool (in category 'reflecting') -----
+ classPool
+ 	^ editor classPool!

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

Item was added:
+ ----- Method: OldMetaclassEditor>>compiledMethodAt: (in category 'reflecting') -----
+ compiledMethodAt: aSelector
+ 	^ self subjectDo: [:subject | subject compiledMethodAt: aSelector]!

Item was changed:
  ----- Method: MetaclassEditor>>compile:classified:withStamp:notifying: (in category 'editing') -----
  compile: source classified: cat withStamp: aString notifying: anObject
  	^ self 
  		compile: source
  		classified: cat
  		withStamp: aString
  		notifying: anObject
  		logSource: self acceptsLoggingOfCompilation !

Item was changed:
  ----- Method: MetaclassEditor>>isUniClass (in category 'reflecting') -----
  isUniClass
  	"The debugger sometimes sends this message"
  	^ false!

Item was changed:
  ----- Method: MetaclassEditor>>acceptsLoggingOfCompilation (in category 'reflecting') -----
  acceptsLoggingOfCompilation
  
  	^ self instanceSide acceptsLoggingOfCompilation!

Item was added:
+ ----- Method: OldMetaclassEditor>>compile:classified: (in category 'editing') -----
+ compile: source classified: cat
+ 	^ self 
+ 		compile: source
+ 		classified: cat
+ 		withStamp: Utilities changeStamp
+ 		notifying: nil
+ 		logSource: self acceptsLoggingOfCompilation !

Item was changed:
  ----- Method: MetaclassEditor>>superclass (in category 'reflecting') -----
  superclass
  	| subjectSuperclass |
  	superEditor ifNotNil: [^ superEditor].
  	subjectSuperclass := self subject
  		ifNil: [Object]
  		ifNotNil: [self subject superclass].
  	^ self system edEditorFor: subjectSuperclass!

Item was changed:
  ----- Method: MetaclassEditor>>isDebuggingAsEditor (in category 'debugging') -----
  isDebuggingAsEditor
  	"To be transparent enough to fool most existing software,
  	MetaclassEditors must answer their subject's instance variables when
  	sent the message allInstVarNames. However, this message is also used by
  	the debugger, inspector, and explorer, when inspecting ClassEditors, and
  	an inspector should see the real instance variables of ClassEditor rather
  	than those of the MetaclassEditor's subject. So there is a conflict of
  	interest already.
  	
  	But it gets worse. If you do open an inspector on an object that is
  	reporting wrong information about it's instance variables, Bad things
  	happen. Specifically, the inspector calls instVarAt: on an instance
  	variable that does not exist, leading to an error every time the display
  	is updated. Less severe, instVarAt: will answer nonsensical. 
  	
  	So I took the instance variable proxying behavior all the way so that it
  	successfully fools the debugger, inspector, and explorer into seeing
  	proxied instance variables (see the senders af this message if you want
  	to know how). But there is still the original problem that you, the
  	programmer want to see the real state of ClassEditor. That is where this
  	method comes in.
  	
  	If this method returns false, everybody sees the proxied instance
  	variables. This is the correct behavior. If this method returns false,
  	everyone sees the true instance variables of ClassEditor. This is
  	incorrect behavior, and breaks the Unit tests, but it is invaluable if
  	you are debugging ClassEditor.
  	
  	Just be sure to make sure this returns false whenever making a release"
  	^ false!

Item was added:
+ ----- Method: OldRootMetaclassEditor>>edRequiresBuild (in category 'building') -----
+ edRequiresBuild
+ 	^ false!

Item was added:
+ ----- Method: RootMetaclassEditor>>ultimateSourceCodeAt:ifAbsent: (in category 'reflecting') -----
+ ultimateSourceCodeAt: selector ifAbsent: aBlock
+ "Return the source code at selector, deferring to superclass if necessary"
+ 
+ 	^ aBlock value!

Item was changed:
  ----- Method: MetaclassEditor>>removeSelector: (in category 'editing') -----
  removeSelector: aSymbol 
  	methods ifNil: [methods := MethodDictionaryEditor for: self].
  	methods remove: aSymbol.!

Item was changed:
  ----- Method: MetaclassEditor>>lookupSelector: (in category 'metaclass') -----
  lookupSelector: aSelector
  	
  	"Override the implementation in Behavior to make ClassEditor
  	debuggable. The debugger calls this during simulated execution,
  	and since we override #includesSelector and #superclass to 
  	reflect on the subject, we get incorrect method dispatch."
  
  	| lookupClass dict |
  	lookupClass := self.
  	[lookupClass == nil] whileFalse: 
  		[dict := lookupClass instVarAt: 2.
  		(dict includesKey: aSelector)
  			ifTrue: [^ dict at: aSelector].
  		lookupClass := lookupClass instVarAt: 1].
  	^ nil!

Item was changed:
  ----- Method: MetaclassEditor>>edRequiresSubclassRebuild (in category 'building') -----
  edRequiresSubclassRebuild
  	^ self subject
  		ifNotNilDo: [:subject | subject format ~= self format]
  		ifNil: [false]!

Item was changed:
  ----- Method: MetaclassEditor>>hasComment (in category 'reflecting') -----
  hasComment
  	^ self instanceSide hasComment!

Item was changed:
  ----- Method: MetaclassEditor>>compile:classified:notifying: (in category 'editing') -----
  compile: source classified: cat notifying: anObject
  	^ self 
  		compile: source
  		classified: cat
  		withStamp: Utilities changeStamp
  		notifying: anObject
  		logSource: self acceptsLoggingOfCompilation !

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

Item was added:
+ ----- Method: OldRootMetaclassEditor>>typeOfClass (in category 'reflecting') -----
+ typeOfClass
+ 	^ #normal!

Item was added:
+ ----- Method: OldMetaclassEditor>>instanceSide (in category 'reflecting') -----
+ instanceSide
+ 	^ self theNonMetaClass!

Item was added:
+ ----- Method: OldMetaclassEditor>>addInstVarName: (in category 'editing') -----
+ addInstVarName: aString 
+ 	instVarNames ifNil: [instVarNames := self subject instVarNames].
+ 	instVarNames := instVarNames copyWith: aString!

Item was added:
+ ----- Method: OldMetaclassEditor>>printOn: (in category 'printing') -----
+ printOn: aStream
+ 	aStream
+ 		nextPutAll: 'a MetaclassEditor on: ';
+ 		print: editor subject !

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

Item was added:
+ ----- Method: OldMetaclassEditor>>includesSelector: (in category 'reflecting') -----
+ includesSelector: aSelector
+ 	^ (methods ifNil: [self subject] ifNotNil: [methods])
+ 		includesSelector: aSelector!

Item was added:
+ ----- Method: OldMetaclassEditor>>comment (in category 'reflecting') -----
+ comment
+ 	^ self instanceSide comment!

Item was added:
+ ----- Method: OldMetaclassEditor>>rearrangeInstVarNames: (in category 'editing') -----
+ rearrangeInstVarNames: associations
+ 	"The associations are name -> pos and cover the subset
+ 	of vars that should be moved. The old just fill in the holes."
+ 
+ 	instVarNames := ClassEditor rearrangeVarNames: associations oldNames: instVarNames!

Item was added:
+ ----- Method: OldMetaclassEditor>>new (in category 'metaclass') -----
+ new
+ 	^ editor := self basicNew!

Item was changed:
  ----- Method: MetaclassEditor>>allInstVarNames (in category 'reflecting') -----
  allInstVarNames
  	 "specialized in order to enable debugger to show as self"
  	
  	self isDebuggingAsEditor ifTrue: [^ super allInstVarNames].
  	^ self edSuperclass
  		ifNil: [self instVarNames copy]
  		ifNotNil: [self edSuperclass allInstVarNames, self instVarNames]!

Item was added:
+ ----- Method: OldMetaclassEditor>>name (in category 'reflecting') -----
+ name
+ 	^ editor name, ' class'!

Item was added:
+ ----- Method: OldMetaclassEditor>>subjectDo: (in category 'accessing') -----
+ subjectDo: aBlock
+ 	^ self subject
+ 		ifNotNilDo: [:subject | aBlock value: subject]
+ 		ifNil: [self error: 'key not found']!

Item was added:
+ ----- Method: OldMetaclassEditor>>edInitializeForNewClass (in category 'building') -----
+ edInitializeForNewClass
+ 	superEditor := self system edEditorFor: Object class.
+ 	instVarNames := Array new.
+ 	methods := MethodDictionaryEditor for: self!

Item was changed:
  ----- Method: MetaclassEditor>>edSuperclass (in category 'building') -----
  edSuperclass
  	^ superEditor
  		ifNil: [self subject superclass]
  		ifNotNil: [superEditor product]!

Item was changed:
  ----- Method: MetaclassEditor>>typeOfClass (in category 'reflecting') -----
  typeOfClass
  	^ #normal!

Item was added:
+ ----- Method: OldMetaclassEditor>>sourceCodeAt: (in category 'reflecting') -----
+ sourceCodeAt: aSelector
+ 	^ self subjectDo: [:subject | subject sourceCodeAt: aSelector]!

Item was added:
+ ----- Method: OldMetaclassEditor>>organization (in category 'reflecting') -----
+ organization
+ 	^ organization ifNil: [organization := OrganizationEditor for: self]!

Item was added:
+ ----- Method: RootMetaclassEditor>>edRequiresRecompile (in category 'building') -----
+ edRequiresRecompile
+ 	^ false!

Item was added:
+ ----- Method: OldRootMetaclassEditor>>edRegisterEditor (in category 'initialize-release') -----
+ edRegisterEditor
+ "Do nothing"!

Item was added:
+ ----- Method: OldMetaclassEditor>>edMethodAt: (in category 'editing') -----
+ edMethodAt: aSelector
+ 	^ self methods at: aSelector!

Item was added:
+ ----- Method: OldMetaclassEditor>>methodDictionary (in category 'reflecting') -----
+ methodDictionary
+ 	| methodEditor |
+ 	(methods isNil and: [self edRequiresRecompile not]) ifTrue: [^ self subject methodDictionary].
+ 	methodEditor := methods ifNil: [MethodDictionaryEditor for: self].
+ 	^ methodEditor buildFor: self!

Item was changed:
  ----- Method: MetaclassEditor>>edIsEditor (in category 'testing') -----
  edIsEditor
  	^ true!

Item was added:
+ ----- Method: OldMetaclassEditor>>browserDefinition: (in category 'reflecting') -----
+ browserDefinition: style
+ 	^ self definition!

Item was changed:
  ----- Method: MetaclassEditor>>edRequiresRecompile (in category 'building') -----
  edRequiresRecompile
  	^ instVarNames ~~ nil!

Item was changed:
  ----- Method: MetaclassEditor>>theMetaClass (in category 'reflecting') -----
  theMetaClass
  	^ self!

Item was removed:
- MetaclassEditor subclass: #RootMetalassEditor
- 	instanceVariableNames: ''
- 	classVariableNames: ''
- 	poolDictionaries: ''
- 	category: 'SystemEditor-Editors'!

Item was removed:
- ----- Method: RootMetalassEditor>>allSuperclasses (in category 'reflecting') -----
- allSuperclasses
- 	^ OrderedCollection new!

Item was removed:
- ----- Method: RootMetalassEditor>>subject (in category 'accessing') -----
- subject
- 	^ nil!

Item was removed:
- ----- Method: RootMetalassEditor class>>canEdit:for: (in category 'instance creation') -----
- canEdit: anObject for: anEditor
- 	^ false!

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

Item was removed:
- ----- Method: RootMetalassEditor>>ultimateSourceCodeAt:ifAbsent: (in category 'reflecting') -----
- ultimateSourceCodeAt: selector ifAbsent: aBlock
- "Return the source code at selector, deferring to superclass if necessary"
- 
- 	^ aBlock value!

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

Item was removed:
- ----- Method: RootMetalassEditor>>typeOfClass (in category 'reflecting') -----
- typeOfClass
- 	^ #normal!

Item was removed:
- ----- Method: RootMetalassEditor>>edRequiresRecompile (in category 'building') -----
- edRequiresRecompile
- 	^ false!

Item was removed:
- ----- Method: RootMetalassEditor>>edRegisterEditor (in category 'initialize-release') -----
- edRegisterEditor
- "Do nothing"!

Item was removed:
- ----- Method: RootMetalassEditor class>>classClassEditor (in category 'instance creation') -----
- classClassEditor
- 	^ RootClassEditor!

Item was removed:
- ----- Method: RootMetalassEditor>>product (in category 'building') -----
- product
- 	^ nil!

Item was removed:
- ----- Method: RootMetalassEditor>>edRequiresBuild (in category 'building') -----
- edRequiresBuild
- 	^ false!



More information about the Packages mailing list