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

squeaksource-noreply at iam.unibe.ch squeaksource-noreply at iam.unibe.ch
Tue Aug 12 22:30:21 UTC 2008


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

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

Name: SystemEditor-mtf.112
Author: mtf
Time: 12 August 2008, 3:30:26 pm
UUID: a6b9a676-4bf5-48ed-88e1-2ff45642b662
Ancestors: SystemEditor-mtf.106

I went way too long without comitting this:
- Created ClassDescriptionEditor and moved all the methods ClassEditor and MetaclassEditor should share down there
- Created RootClassEditor to simplify queries that recurse up the class heiarchy
- fixed a bug in MethodDictionaryEditor that caused global variables to raise an error during compilation
- Made ClassEditor and MetaclassEditor be easily subclassable, so that a custom ClassEditor can have a custom MetaclassEditor
- Removed dependence on keith's fancy progress bar stuff

=============== Diff against SystemEditor-mtf.106 ===============

Item was changed:
  ----- Method: MethodDictionaryEditor>>recompile:from:for: (in category 'building') -----
  recompile: aSelector from: aCompiledMethod for: aClassEditor
  	| trailer node |
  	aClassEditor edRequiresRecompile ifFalse: [^ aCompiledMethod].
  	trailer := aCompiledMethod trailer.
  	node := aClassEditor compilerClass new
  			compile: (aCompiledMethod 
  						getSourceFor: aSelector 
  						in: aClassEditor)
+ 			in: aClassEditor product
- 			in: aClassEditor
  			notifying: nil
  			ifFail: [self error: 'Compilation failed'].
  	node selector == aSelector ifFalse: [self error: 'selector changed!!'].
  	^ node generate: trailer!

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

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

Item was changed:
  Object subclass: #ObjectMigrator
  	instanceVariableNames: 'origin destination'
  	classVariableNames: ''
  	poolDictionaries: ''
  	category: 'SystemEditor-Editors'!
+ 
+ !ObjectMigrator commentStamp: 'mtf 7/14/2008 11:59' prior: 0!
+ My instances store an old and new version of a single object that will be swapped during MigrationTransaction>>commit!

Item was added:
+ ----- Method: ClassDescriptionEditor>>sourceCodeAt:ifAbsent: (in category 'reflecting') -----
+ sourceCodeAt: aSelector ifAbsent: aBlock
+ 	^ (self edMethodAt: aSelector ifAbsent: aBlock) source!

Item was added:
+ ----- Method: ClassDescriptionEditor>>typeOfClass: (in category 'accessing') -----
+ typeOfClass: aSymbol
+ 	type := aSymbol!

Item was changed:
+ ----- Method: ClassEditor>>edIsValid (in category '*SystemEditor-Tests') -----
- ----- Method: ClassEditor>>edIsValid (in category 'testing') -----
  edIsValid
  	[self validate]
  		on: InvalidSystemChange
  		do: [:ex | ^ false].
  	^ true!

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: 'Comitting...'].
- 	
  	[migration commit.
  	export commit.
  	self edCommitRemovals.
  	self edRecategorize.] valueUnpreemptively.
  	
  	^ true!

Item was added:
+ ----- Method: ClassDescriptionEditor>>superclass: (in category 'editing') -----
+ superclass: aClassOrEditor 
+ 	superEditor := self environment edEditorFor: aClassOrEditor!

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

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

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

Item was added:
+ ----- Method: ClassDescriptionEditor>>validateFormat (in category 'validating') -----
+ validateFormat
+ 	self edClassFormat
+ 		validate;
+ 		validateAgainstSuper: self edSuperFormat;
+ 		validateAgainstOld: self edOldFormat!

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

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

Item was added:
+ ----- Method: ClassDescriptionEditor>>isWords (in category 'testing') -----
+ isWords
+ 	^ #(words weak variable) includes: self typeOfClass !

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

Item was added:
+ ----- Method: ClassDescriptionEditor>>propertyAt:ifAbsent: (in category 'accessing properties') -----
+ propertyAt: key ifAbsent: aBlock
+ 
+ 	properties ifNil: [^ aBlock value].
+ 	^ properties at: key ifAbsent: aBlock!

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

Item was added:
+ ----- Method: ClassDescriptionEditor>>whichCategoryIncludesSelector: (in category 'reflecting') -----
+ whichCategoryIncludesSelector: aSymbol 
+ 	^ self organization categoryOfElement: aSymbol!

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

Item was added:
+ ----- Method: ClassDescriptionEditor>>format (in category 'reflecting') -----
+ format
+ 	^ self edClassFormat bits!

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

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

Item was added:
+ ----- Method: ClassDescriptionEditor>>isBytes (in category 'testing') -----
+ isBytes
+ 	^ self typeOfClass = #bytes!

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

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

Item was added:
+ ----- Method: ClassDescriptionEditor>>propertyAt:ifAbsentPut: (in category 'accessing properties') -----
+ propertyAt: key ifAbsentPut: aBlock
+ 
+ 	^ self propertyAt: key ifAbsent: [
+ 		self propertyAt: key put: aBlock value]!

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

Item was added:
+ ----- Method: ClassDescriptionEditor>>edOldFormat (in category 'building') -----
+ edOldFormat
+ 	^ self subject ifNotNil: [ClassFormat fromBits: self subject format]!

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

Item was added:
+ ----- Method: ClassDescriptionEditor>>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:
+ MetaclassEditor subclass: #RootMetalassEditor
+ 	instanceVariableNames: ''
+ 	classVariableNames: ''
+ 	poolDictionaries: ''
+ 	category: 'SystemEditor-Editors'!

Item was changed:
+ ClassDescriptionEditor subclass: #ClassEditor
+ 	instanceVariableNames: 'subject product system name classVarNames sharedPools category'
+ 	classVariableNames: ''
- AbstractEditor subclass: #ClassEditor
- 	instanceVariableNames: 'subject product system superEditor name type instVarNames classVarNames sharedPools methods category organization properties decorators'
- 	classVariableNames: 'ReservedNames'
  	poolDictionaries: ''
  	category: 'SystemEditor-Editors'!

Item was changed:
+ ----- Method: ClassEditor>>isMeta (in category 'testing') -----
- ----- Method: ClassEditor>>isMeta (in category 'reflecting') -----
  isMeta
  	^ false!

Item was added:
+ ----- Method: ClassDescriptionEditor>>literalScannedAs:notifying: (in category 'compiling') -----
+ literalScannedAs: literal notifying: anEncoder 
+ 	literal isVariableBinding ifTrue: [self halt].
+ 	^ literal!

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

Item was added:
+ ----- Method: ClassDescriptionEditor>>superclass (in category 'reflecting') -----
+ superclass
+ "Answers the editor on my new superclass, creating it if necessary"
+ 
+ 	^ self environment edEditorFor: self superclassOrEditor!

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

Item was added:
+ ----- Method: ClassDescriptionEditor>>removeSelector: (in category 'editing') -----
+ removeSelector: aSymbol 
+ 	self methods remove: aSymbol.!

Item was added:
+ ----- Method: ClassDescriptionEditor>>hasProperty: (in category 'accessing properties') -----
+ hasProperty: aSymbol
+ 	self propertyAt: aSymbol ifAbsent: [^ false].
+ 	^ true!

Item was added:
+ ----- Method: ClassDescriptionEditor>>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: ClassDescriptionEditor>>isBits (in category 'testing') -----
+ isBits
+ 	^ #(bytes words) includes: self typeOfClass!

Item was changed:
  CategorizerEditor subclass: #OrganizationEditor
  	instanceVariableNames: 'classEditor isDirty comment stamp remote repository'
  	classVariableNames: ''
  	poolDictionaries: ''
  	category: 'SystemEditor-Editors'!
+ 
+ !OrganizationEditor commentStamp: 'mtf 7/14/2008 11:28' prior: 0!
+ My instances are editors for ClassOrganizer instances!

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

Item was added:
+ ----- Method: ClassDescriptionEditor>>selectors (in category 'reflecting') -----
+ selectors
+ 	^ self organization allMethodSelectors!

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

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

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

Item was added:
+ ----- Method: ClassDescriptionEditor>>typeOfClass (in category 'accessing') -----
+ typeOfClass
+ 	type ifNotNil: [^ type].
+ 	self subject ifNotNil: [^ self subject typeOfClass].
+ 	^ self superclassOrEditor typeOfClass.!

Item was changed:
  ----- Method: SystemEditor>>edPrepareMigration: (in category 'building') -----
  edPrepareMigration: txn
+ 
+ 	showProgress
+ 		ifFalse:	[editors do: [:ea | ea edPrepareMigration: txn]]
+ 		ifTrue:	[editors do: [:ea | ea edPrepareMigration: txn] displayingProgress: 'Preparing Transaction...']!
-  
- 	editors do: [:ea | 
- 		progressBar ifNotNil: [ progressBar value: #increment ].
- 		ea edPrepareMigration: txn
- 	].
- 	!

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

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

Item was changed:
  ----- Method: ClassEditor class>>new (in category 'instance creation') -----
  new
+ 	^ self classMetaclassEditor new new!
- 	^ MetaclassEditor new new!

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

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

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

Item was changed:
  Object subclass: #SystemEditor
+ 	instanceVariableNames: 'subject editors removals organization showProgress'
- 	instanceVariableNames: 'subject editors removals progressBar organization'
  	classVariableNames: ''
  	poolDictionaries: ''
  	category: 'SystemEditor-Editors'!

Item was changed:
+ ----- Method: ClassEditor>>name (in category 'accessing') -----
- ----- Method: ClassEditor>>name (in category 'reflecting') -----
  name
  	^ name ifNil: [subject name]!

Item was added:
+ ----- Method: ClassDescriptionEditor>>withAllSuperclasses (in category 'reflecting') -----
+ withAllSuperclasses
+ 	"Answer an OrderedCollection of the receiver and the receiver's 
+ 	superclasses. The first element is the receiver, 
+ 	followed by its superclass; the last element is Object."
+ 
+ 	| temp |
+ 	temp := self allSuperclasses.
+ 	temp addFirst: self.
+ 	^ temp!

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

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

Item was changed:
+ AbstractEditor subclass: #CategorizerEditor
- Object subclass: #CategorizerEditor
  	instanceVariableNames: 'subject addedCategories renamedCategories removedCategories'
  	classVariableNames: ''
  	poolDictionaries: ''
  	category: 'SystemEditor-Editors'!
  
  !CategorizerEditor commentStamp: '<historical>' prior: 0!
  An abstract superclass for editors of Categorizers. Takes care of most of the hassle of implementing the public interface of a Categorizer!

Item was added:
+ ----- Method: ClassDescriptionEditor>>propertyAt:put: (in category 'accessing properties') -----
+ propertyAt: aSymbol put: value
+ 
+ 	properties ifNil: [properties := Dictionary new].
+ 	^ properties at: aSymbol put: value!

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

Item was added:
+ ----- Method: ClassDescriptionEditor>>compiledMethodAt:ifAbsent: (in category 'reflecting') -----
+ compiledMethodAt: aSelector ifAbsent: aBlock
+ 	^ self edMethodAt: aSelector ifAbsent: aBlock!

Item was added:
+ ----- Method: ClassDescriptionEditor>>isWeak (in category 'testing') -----
+ isWeak
+ 	^ self typeOfClass = #weak!

Item was changed:
+ ----- Method: ClassEditor>>parserClass (in category 'debugging') -----
- ----- Method: ClassEditor>>parserClass (in category 'reflecting') -----
  parserClass
  	^ self class parserClass!

Item was added:
+ ClassEditor subclass: #RootClassEditor
+ 	instanceVariableNames: ''
+ 	classVariableNames: ''
+ 	poolDictionaries: ''
+ 	category: 'SystemEditor-Editors'!
+ 
+ !RootClassEditor commentStamp: 'mtf 7/29/2008 08:37' prior: 0!
+ My instances represent ClassEditors on the concept of "ProtoObject's superclass", the primitive object from which every class, without exception, inherits. I exist so that queries that involve the superclass do not have to be special-cased in case the superclass really is nil.!

Item was added:
+ ----- Method: ClassDescriptionEditor>>acceptsLoggingOfCompilation (in category 'reflecting') -----
+ acceptsLoggingOfCompilation
+ 
+ 	self subject ifNil: [ ^ true ].
+ 	^ self subject acceptsLoggingOfCompilation!

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

Item was changed:
+ ----- Method: ClassEditor>>category: (in category 'reflecting') -----
- ----- Method: ClassEditor>>category: (in category 'editing') -----
  category: aSymbol
  	category := aSymbol!

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

Item was added:
+ ----- Method: ClassDescriptionEditor>>sourceCodeTemplate (in category 'reflecting') -----
+ sourceCodeTemplate
+ 	^ self class sourceCodeTemplate!

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

Item was added:
+ ----- Method: ClassDescriptionEditor>>propertyAt: (in category 'accessing properties') -----
+ propertyAt: key
+ 
+ 	^self propertyAt: key ifAbsent: [nil]!

Item was changed:
+ ----- Method: ClassEditor>>instVarAt:put: (in category 'debugging') -----
- ----- Method: ClassEditor>>instVarAt:put: (in category 'reflecting') -----
  instVarAt: index put: anObject
  	"Override the implemenation in Object. That will set the inst vars of 
  	ClassEditor, but we want the inst vars of the subject."
  
  	self class isDebuggingAsEditor ifTrue: [^ super instVarAt: index put: anObject].
  	
  	"If the insance variable has not yet been installed, return nil"
  	self subject ifNil: [^ self].
  	index > self subject class instSize ifTrue: [^ self].
  	
  	^ self subject instVarAt: index put: anObject!

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

Item was added:
+ ----- 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 changed:
  ----- Method: SystemEditor>>commitWithProgress (in category 'building') -----
+ commitWithProgress
- commitWithProgress 
- 
- 	  'Loading...'
- 
- 		 displayProgress: progressBar at: Sensor cursorPoint
- 			from: 0 to: (editors size * 2)
- 			during: [ :bar |
- 	 			self setProgressBar: bar.
- 	 			self commit.
- 				self setProgressBar: nil.
- 			].
- 		
  
+ 	showProgress := true.
+ 	self commit.
+ 	showProgress := false.!
-  !

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"
- 	"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!
- 	| superFormat |
- 	superFormat := ClassFormat fromBits: self edSuperclass format.
- 	^ (superFormat namedSubclass: self instVarNames size) bits!

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

Item was added:
+ ----- Method: ClassDescriptionEditor>>compiledMethodAt: (in category 'reflecting') -----
+ compiledMethodAt: aSelector
+ 
+ 	^ self compiledMethodAt: aSelector ifAbsent: [ self error: 'key not found' ]!

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

Item was added:
+ ----- Method: ClassDescriptionEditor>>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: ClassDescriptionEditor>>edSuperclass (in category 'building') -----
+ edSuperclass
+ "Answer my product's superclass, building it if necessary"
+ 
+ 	^ self superclass product!

Item was added:
+ ----- Method: ClassDescriptionEditor>>superclassOrEditor (in category 'accessing') -----
+ superclassOrEditor
+ "Answer my superclass as either an editor or class, whichever is easier. Does not add anything to my SystemEditor"
+ 
+ 	^ superEditor
+ 		ifNil: [ self subject superclass
+ 			ifNil: [RootClassEditor on: nil for: self environment]]!

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

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

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

Item was added:
+ ----- Method: ClassDescriptionEditor>>ensureInstVarName: (in category 'editing') -----
+ ensureInstVarName: aString 
+ 	(self allInstVarNames includes: aString)
+ 		ifFalse: [ self addInstVarName: aString].
+ 		 !

Item was added:
+ ----- Method: ClassDescriptionEditor>>isVariable (in category 'testing') -----
+ isVariable
+ 	^ (self typeOfClass = #normal) not!

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

Item was added:
+ AbstractEditor subclass: #ClassDescriptionEditor
+ 	instanceVariableNames: 'superclass methodDict format superEditor methods type instVarNames organization properties decorators'
+ 	classVariableNames: 'ReservedNames'
+ 	poolDictionaries: ''
+ 	category: 'SystemEditor-Editors'!
+ 
+ !ClassDescriptionEditor commentStamp: 'mtf 7/29/2008 21:55' prior: 0!
+ I am an abstract superclass for both ClassEditor and MetaclassEditor.
+ 
+ I implement  the Behavior protocol: my instances can create instances. This means that my first three variables must remain 'superclass methodDict format', as the VM accesses them positionally, and my superclasses must not define any instance vairables. Only MetaclassEditor makes use of these ivars, but they are defined here to avoid duplicating a lot of ivars and accessing methods between ClassEditor and MetaclassEditor!

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

Item was changed:
  Object subclass: #InstanceMigrator
  	instanceVariableNames: 'map instSize origin destination'
  	classVariableNames: ''
  	poolDictionaries: ''
  	category: 'SystemEditor-Editors'!
+ 
+ !InstanceMigrator commentStamp: 'mtf 7/14/2008 23:51' prior: 0!
+ My instances are responsible for finding instances of an old class and building them in a new format, to be swapped during MigrationTransaction>>commit!

Item was added:
+ ----- Method: ClassDescriptionEditor>>compilerClass (in category 'reflecting') -----
+ compilerClass
+ 	^ self subject 
+ 		ifNil: [Compiler]
+ 		ifNotNil: [self subject compilerClass]!

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

Item was added:
+ ----- Method: ClassDescriptionEditor>>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: ClassEditor>>instVarAt: (in category 'debugging') -----
- ----- Method: ClassEditor>>instVarAt: (in category 'reflecting') -----
  instVarAt: index
  	"Override the implemenation in Object. That will return the inst vars of 
  	ClassEditor, but we want the inst vars of the subject."
  
  	self class isDebuggingAsEditor ifTrue: [^ super instVarAt: index].
  	
  	"If the insance variable has not yet been installed, return nil"
  	self subject ifNil: [^ nil].
  	index > self subject class instSize ifTrue: [^ nil].
  	
  	^ self subject instVarAt: index!

Item was changed:
  ----- Method: SystemEditor>>edSubclassesOf: (in category 'building') -----
+ edSubclassesOf: anEditor 
- edSubclassesOf: anEditor
  	| subeditors |
  	subeditors := OrderedCollection new.
+ 	anEditor subject ifNotNilDo: 
+ 		[ :class | 
+ 		subeditors addAll: (class subclasses collect: [ :ea | self edEditorFor: ea ]) ].
+ 	editors do: [ :ea | ea superclassOrEditor == anEditor ifTrue: [ subeditors add: ea ] ].
+ 	^ subeditors asArray!
- 	anEditor subject ifNotNilDo: [:class | subeditors addAll: (class subclasses collect: [:ea | self edEditorFor: ea])].
- 	editors do: [:ea | ea edSuperEditor == anEditor ifTrue: [subeditors add: ea]].
- 	^ subeditors asArray
- 	!

Item was added:
+ ----- Method: ClassDescriptionEditor>>sourceCodeAt: (in category 'reflecting') -----
+ sourceCodeAt: aSelector
+ 	^ self sourceCodeAt: aSelector ifAbsent: [nil]!

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

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

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

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

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

Item was added:
+ ----- Method: ClassDescriptionEditor>>decoratorsDo: (in category 'accessing') -----
+ decoratorsDo: aBlock
+ 	decorators ifNotNil: [decorators do: aBlock]!

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

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

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

Item was added:
+ ----- Method: ClassDescriptionEditor>>allSuperclasses (in category 'reflecting') -----
+ allSuperclasses
+ "Answer an OrderedCollection of the receiver's and the receiver's ancestor's superclasses. The first element is the receiver's immediate superclass, followed by its superclass; the last element is Object."
+ 
+ 	^ self superclass withAllSuperclasses!

Item was changed:
  ----- Method: SystemEditor>>edPrepareExport: (in category 'building') -----
  edPrepareExport: exporter
  
+ 	showProgress
+ 		ifFalse:	[editors do: [:ea | ea edPrepareExport: exporter]]
+ 		ifTrue:	[editors do: [:ea | ea edPrepareExport: exporter] displayingProgress: 'Preparing Classes...']!
- 	editors do: [ :ea |  
- 		progressBar ifNotNil: [ progressBar value: #increment ].
- 		ea edPrepareExport: exporter 
- 	].
- !

Item was changed:
  ----- Method: AbstractEditor class>>named:for: (in category 'as yet unclassified') -----
  named: aName for: aDictionaryEditor
  	"Answers a new or existing instance with the given name, and installs it, if necessary"
  	^ aDictionaryEditor at: aName ifAbsent: [
  		(self on: nil for: aDictionaryEditor)
  			setName: aName;
  			edRegisterEditor;
  			yourself]!

Item was added:
+ ----- Method: ClassDescriptionEditor>>isPointers (in category 'testing') -----
+ isPointers
+ 	^ #(normal weak variable) includes: self typeOfClass!

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

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

Item was changed:
  Object subclass: #SourceRepository
  	instanceVariableNames: 'files'
  	classVariableNames: ''
  	poolDictionaries: ''
  	category: 'SystemEditor-Editors'!
+ 
+ !SourceRepository commentStamp: 'mtf 7/14/2008 11:55' prior: 0!
+ I have no idea what this class is for. It is extensivily tested in SystemEditor-Tests, but it is actually only used two places in the code:
+ OrganizationEditor>>writeComment
+ MethodEditor>>logCompilationFrom:for:
+ 
+ I have not examined to see what it does -- Matthew Fulmer!

Item was added:
+ ----- Method: ClassDescriptionEditor>>kindOfSubclass (in category 'reflecting') -----
+ kindOfSubclass
+ 	^ self typeOfClass caseOf: {
+ 		[#normal] -> [' subclass: '].
+ 		[#words] -> [' variableWordSubclass: '].
+ 		[#variable] -> [' variableSubclass: '].
+ 		[#bytes] -> [' variableByteSubclass: '].
+ 		[#weak] -> [' weakSubclass: ' ].
+ 		[#compiledMethod] -> [' variableByteSubclass: ' ]
+ 	} otherwise: [self error: 'Unrecognized class type']!

Item was added:
+ ----- Method: ClassDescriptionEditor>>validate (in category 'validating') -----
+ validate
+ 	self
+ 		validateFormat;
+ 		validateInstVarNames!

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

Item was removed:
- ----- Method: ClassEditor>>elementName (in category 'category browsing') -----
- elementName
- 	"The name this editor will be classified under"
- 	^ self name!

Item was removed:
- ----- Method: ClassEditor>>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 removed:
- ----- Method: ClassEditor>>subjectDo: (in category 'reflecting') -----
- subjectDo: aBlock
- 	^ subject 
- 		ifNotNil: aBlock
- 		ifNil: [self error: 'key not found'] !

Item was removed:
- ----- Method: ClassEditor>>edMethodsDo: (in category 'accessing') -----
- edMethodsDo: aBlock
- 	methods ifNotNil: [methods do: aBlock]!

Item was removed:
- ----- Method: ClassEditor>>isWeak (in category 'reflecting') -----
- isWeak
- 	^ self typeOfClass = #weak!

Item was removed:
- ----- Method: ClassEditor>>sourceCodeAt: (in category 'reflecting') -----
- sourceCodeAt: aSelector
- 	^ self sourceCodeAt: aSelector ifAbsent: [nil]!

Item was removed:
- ----- Method: ClassEditor>>edSuperEditor (in category 'building') -----
- edSuperEditor
- 	^ superEditor ifNil: [subject superclass]!

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

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

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

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

Item was removed:
- ----- Method: ClassEditor>>decoratorsDo: (in category 'accessing') -----
- decoratorsDo: aBlock
- 	decorators ifNotNil: [decorators do: aBlock]!

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

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

Item was removed:
- ----- Method: ClassEditor>>isPointers (in category 'reflecting') -----
- isPointers
- 	^ #(normal weak variable) includes: self typeOfClass!

Item was removed:
- ----- Method: ClassEditor>>propertyAt: (in category 'accessing properties') -----
- propertyAt: key
- 
- 	^self propertyAt: key ifAbsent: [nil]!

Item was removed:
- ----- Method: ClassEditor>>kindOfSubclass (in category 'reflecting') -----
- kindOfSubclass
- 	^ self typeOfClass caseOf: {
- 		[#normal] -> [' subclass: '].
- 		[#words] -> [' variableWordSubclass: '].
- 		[#variable] -> [' variableSubclass: '].
- 		[#bytes] -> [' variableByteSubclass: '].
- 		[#weak] -> [' weakSubclass: ' ].
- 		[#compiledMethod] -> [' variableByteSubclass: ' ]
- 	} otherwise: [self error: 'Unrecognized class type']!

Item was removed:
- ----- Method: ClassEditor>>validateInstVarNames (in category 'validating') -----
- validateInstVarNames
- 	self instVarNames do: 
- 		[:ea | 
- 		(ReservedNames includes: ea) ifTrue: [IllegalVariableName signal].
- 		(self edSuperEditor allInstVarNames includes: ea) ifTrue: [IllegalVariableName signal].
- 		self subclasses do: [:class | (class instVarNames includes: ea) ifTrue: [IllegalVariableName signal]]]!

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

Item was removed:
- ----- Method: ClassEditor>>typeOfClass: (in category 'editing') -----
- typeOfClass: aSymbol
- 	type := aSymbol!

Item was removed:
- ----- Method: ClassEditor>>instVarNames (in category 'reflecting') -----
- instVarNames
- 	^ instVarNames ifNil: [subject instVarNames]!

Item was removed:
- ----- Method: ClassEditor>>validateFormat (in category 'validating') -----
- validateFormat
- 	self edClassFormat
- 		validate;
- 		validateAgainstSuper: self edSuperFormat;
- 		validateAgainstOld: self edOldFormat!

Item was removed:
- ----- Method: SystemEditor>>setProgressBar: (in category 'initialize-release') -----
- setProgressBar: bar
- 
- 	progressBar := bar!

Item was removed:
- ----- Method: ClassEditor>>isWords (in category 'reflecting') -----
- isWords
- 	^ #(words weak variable) includes: self typeOfClass !

Item was removed:
- ----- Method: ClassEditor>>ensureInstVarName: (in category 'editing') -----
- ensureInstVarName: aString 
- 	(self allInstVarNames includes: aString)
- 		ifFalse: [ self addInstVarName: aString].
- 		 !

Item was removed:
- ----- Method: ClassEditor>>propertyAt:ifAbsent: (in category 'accessing properties') -----
- propertyAt: key ifAbsent: aBlock
- 
- 	^ properties
- 		ifNil: aBlock
- 		ifNotNil: [properties at: key ifAbsent: aBlock]!

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

Item was removed:
- ----- Method: ClassEditor>>isVariable (in category 'reflecting') -----
- isVariable
- 	^ (self typeOfClass = #normal) not!

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

Item was removed:
- ----- Method: ClassEditor>>format (in category 'reflecting') -----
- format
- 	^ self edClassFormat bits!

Item was removed:
- ----- Method: ClassEditor>>addInstVarName: (in category 'editing') -----
- addInstVarName: aString 
- 	instVarNames ifNil: [instVarNames := subject instVarNames].
- 	(instVarNames includes: aString)
- 		ifFalse: [instVarNames := instVarNames copyWith: aString]!

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

Item was removed:
- ----- Method: ClassEditor>>isBytes (in category 'reflecting') -----
- isBytes
- 	^ self typeOfClass = #bytes!

Item was removed:
- ----- Method: ClassEditor>>compilerClass (in category 'reflecting') -----
- compilerClass
- 	^ subject 
- 		ifNil: [Compiler]
- 		ifNotNil: [subject compilerClass]!

Item was removed:
- ----- Method: ClassEditor>>propertyAt:ifAbsentPut: (in category 'accessing properties') -----
- propertyAt: key ifAbsentPut: aBlock
- 
- 	^ self propertyAt: key ifAbsent: [
- 		self propertyAt: key put: aBlock value]!

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

Item was removed:
- ----- Method: ClassEditor>>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 removed:
- ----- Method: ClassEditor>>superclass (in category 'reflecting') -----
- superclass
- 	superEditor ifNotNil: [^ superEditor].
- 	subject superclass ifNil: [^ nil].
- 	^system edEditorFor: subject superclass!

Item was removed:
- ----- Method: ClassEditor>>hasProperty: (in category 'accessing properties') -----
- hasProperty: aSymbol
- 	self propertyAt: aSymbol ifAbsent: [^ false].
- 	^ true!

Item was removed:
- ----- Method: ClassEditor>>allSuperclasses (in category 'reflecting') -----
- allSuperclasses
- 	"Answer an OrderedCollection of the receiver's and the receiver's  
- 	ancestor's superclasses. The first element is the receiver's immediate  
- 	superclass, followed by its superclass; the last element is Object."
- 	| temp |
- 	^ self superclass == nil
- 		ifTrue: [ OrderedCollection new]
- 		ifFalse: [temp := self superclass allSuperclasses.
- 			temp addFirst: self superclass.
- 			temp]!

Item was removed:
- ----- Method: ClassEditor>>isBits (in category 'reflecting') -----
- isBits
- 	^ #(bytes words) includes: self typeOfClass!

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

Item was removed:
- ----- Method: ClassEditor>>validate (in category 'validating') -----
- validate
- 	self
- 		validateFormat;
- 		validateInstVarNames!

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

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

Item was removed:
- ----- Method: ClassEditor>>sourceCodeAt:ifAbsent: (in category 'reflecting') -----
- sourceCodeAt: aSelector ifAbsent: aBlock
- 	^ (self edMethodAt: aSelector ifAbsent: aBlock) source!

Item was removed:
- ----- Method: ClassEditor>>allInstVarNames (in category 'reflecting') -----
- allInstVarNames
- 	^ self edSuperEditor
- 		ifNil: [self instVarNames copy]
- 		ifNotNil: [self edSuperEditor allInstVarNames, self instVarNames]!

Item was removed:
- ----- Method: ClassEditor>>superclass: (in category 'editing') -----
- superclass: aClassOrEditor 
- 	superEditor := (aClassOrEditor isKindOf: ClassEditor) 
- 				ifTrue: [aClassOrEditor]
- 				ifFalse: [ (ClassEditor on: aClassOrEditor for: system) edRegisterEditor]!

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

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

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

Item was removed:
- ----- Method: ClassEditor>>withAllSuperclasses (in category 'reflecting') -----
- withAllSuperclasses
- 	"Answer an OrderedCollection of the receiver and the receiver's 
- 	superclasses. The first element is the receiver, 
- 	followed by its superclass; the last element is Object."
- 
- 	| temp |
- 	temp := self allSuperclasses.
- 	temp addFirst: self.
- 	^ temp!

Item was removed:
- ----- Method: ClassEditor>>instSize (in category 'reflecting') -----
- instSize
- 	^ self instVarNames size + (self edSuperEditor
- 		ifNil: [0] ifNotNilDo: [:ed | ed instSize])!

Item was removed:
- ----- Method: ClassEditor>>whichCategoryIncludesSelector: (in category 'reflecting') -----
- whichCategoryIncludesSelector: aSymbol 
- 	^ self organization categoryOfElement: aSymbol!

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

Item was removed:
- ----- Method: ClassEditor>>propertyAt:put: (in category 'accessing properties') -----
- propertyAt: aSymbol put: value
- 
- 	properties ifNil: [properties := Dictionary new].
- 	^ properties at: aSymbol put: value!

Item was removed:
- ----- Method: ClassEditor>>compiledMethodAt:ifAbsent: (in category 'reflecting') -----
- compiledMethodAt: aSelector ifAbsent: aBlock
- 	^ self edMethodAt: aSelector ifAbsent: aBlock!

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

Item was removed:
- ----- Method: ClassEditor>>edOldFormat (in category 'building') -----
- edOldFormat
- 	^ subject ifNotNil: [ClassFormat fromBits: subject format]!

Item was removed:
- ----- Method: ClassEditor>>acceptsLoggingOfCompilation (in category 'reflecting') -----
- acceptsLoggingOfCompilation
- 
- 	subject ifNil: [ ^ true ].
- 	
- 	^ subject acceptsLoggingOfCompilation!

Item was removed:
- ----- Method: ClassEditor>>literalScannedAs:notifying: (in category 'compiling') -----
- literalScannedAs: literal notifying: anEncoder 
- 	literal isVariableBinding ifTrue: [self halt].
- 	^ literal!

Item was removed:
- ----- Method: ClassEditor>>sourceCodeTemplate (in category 'reflecting') -----
- sourceCodeTemplate
- 	^ self class sourceCodeTemplate!

Item was removed:
- ----- Method: ClassEditor>>removeSelector: (in category 'editing') -----
- removeSelector: aSymbol 
- 	self methods remove: aSymbol.!

Item was removed:
- ----- Method: ClassEditor>>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 removed:
- ----- Method: ClassEditor>>selectors (in category 'reflecting') -----
- selectors
- 	^ self organization allMethodSelectors!

Item was removed:
- ----- Method: MetaclassEditor>>traitComposition: (in category 'metaclass') -----
- traitComposition: tc
- 
- 	"dummy noop"!

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

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

Item was removed:
- ----- Method: ClassEditor>>typeOfClass (in category 'reflecting') -----
- typeOfClass
- 	type ifNotNil: [^ type].
- 	subject ifNotNil: [^ subject typeOfClass].
- 	^ self edSuperFormat typeOfClass.!



More information about the Packages mailing list