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

squeak-dev-noreply at lists.squeakfoundation.org squeak-dev-noreply at lists.squeakfoundation.org
Tue Oct 14 03:11:13 UTC 2008


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

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

Name: SystemEditor-mtf.133
Author: mtf
Time: 13 October 2008, 4:45:55 pm
UUID: 12257b48-e46f-44a4-89dc-f691de4ccbd2
Ancestors: SystemEditor-mtf.132

Removed a bunch of redundant methods in MetaclassEditor

Refactored editor heiarchy to include PureBehaviorEditor, a superclass for both Classes and Traits. It handles methods and organization

=============== Diff against SystemEditor-mtf.132 ===============

Item was added:
+ ----- Method: PureBehaviorEditor>>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: PureBehaviorEditor>>edMethodAt:ifAbsent: (in category 'editing') -----
+ edMethodAt: aSelector ifAbsent: aBlock
+ 	^ self methods at: aSelector ifAbsent: aBlock!

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

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

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

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

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

Item was added:
+ ----- Method: PureBehaviorEditor>>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: PureBehaviorEditor>>acceptsLoggingOfCompilation (in category 'reflecting') -----
+ acceptsLoggingOfCompilation
+ 
+ 	self subject ifNil: [ ^ true ].
+ 	^ self subject acceptsLoggingOfCompilation!

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

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

Item was added:
+ ----- Method: PureBehaviorEditor>>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:
  ClassDescriptionEditor subclass: #ClassEditor
+ 	instanceVariableNames: 'name classVarNames sharedPools category'
- 	instanceVariableNames: 'subject product system name classVarNames sharedPools category'
  	classVariableNames: ''
  	poolDictionaries: ''
  	category: 'SystemEditor-Editors'!

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

Item was added:
+ ----- Method: PureBehaviorEditor>>ultimateSourceCodeAt:ifAbsent: (in category 'reflecting') -----
+ ultimateSourceCodeAt: selector ifAbsent: aBlock
+ 	"Return the source code at selector"
+ 	
+ 	^self sourceCodeAt: selector ifAbsent: aBlock!

Item was added:
+ ----- Method: PureBehaviorEditor class>>initialize (in category 'initialize-release') -----
+ initialize
+ 	| strings |
+ 	strings := #('self' 'super' 'true' 'false' 'nil' 'thisContext').
+ 	ReservedNames := strings, strings collect: [:ea | ea asSymbol].!

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

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

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

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

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

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

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

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

Item was changed:
+ ----- Method: MetaclassEditor>>instVarNames (in category 'debugging') -----
- ----- 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: PureBehaviorEditor>>compiledMethodAt: (in category 'editing') -----
+ compiledMethodAt: aSelector
+ 
+ 	^ self compiledMethodAt: aSelector ifAbsent: [ self error: 'key not found' ]!

Item was changed:
+ ----- Method: MetaclassEditor>>instSize (in category 'debugging') -----
- ----- 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 superclassOrEditor instSize!

Item was added:
+ ----- Method: PureBehaviorEditor>>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>>isUniClass (in category 'debugging') -----
- ----- Method: MetaclassEditor>>isUniClass (in category 'reflecting') -----
  isUniClass
  	"The debugger sometimes sends this message"
  	^ false!

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

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

Item was changed:
+ ----- Method: MetaclassEditor>>lookupSelector: (in category 'debugging') -----
- ----- 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
+ 		ifNotNil: [self subject format ~= self format]
- 		ifNotNilDo: [:subject | subject format ~= self format]
  		ifNil: [false]!

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

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

Item was changed:
+ PureBehaviorEditor subclass: #ClassDescriptionEditor
+ 	instanceVariableNames: 'superEditor type instVarNames'
+ 	classVariableNames: ''
- 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: PureBehaviorEditor>>edMethodAt: (in category 'editing') -----
+ edMethodAt: aSelector
+ 	^ self methods at: aSelector!

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

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

Item was changed:
+ ----- Method: MetaclassEditor>>allInstVarNames (in category 'debugging') -----
- ----- 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: PureBehaviorEditor>>methods (in category 'accessing') -----
+ methods
+ 	^ methods ifNil: [methods := MethodDictionaryEditor for: self]!

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

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

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

Item was removed:
- ----- 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 removed:
- ----- Method: ClassDescriptionEditor>>edMethodAt:ifAbsent: (in category 'editing') -----
- edMethodAt: aSelector ifAbsent: aBlock
- 	^ self methods at: aSelector ifAbsent: aBlock!

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

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

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

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

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

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

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

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

Item was removed:
- ----- 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 removed:
- ----- 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 removed:
- ----- Method: ClassDescriptionEditor>>literalScannedAs:notifying: (in category 'compiling') -----
- literalScannedAs: literal notifying: anEncoder 
- 	literal isVariableBinding ifTrue: [self halt].
- 	^ literal!

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

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

Item was removed:
- ----- 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 removed:
- ----- Method: ClassDescriptionEditor>>methods (in category 'accessing') -----
- methods
- 	^ methods ifNil: [methods := MethodDictionaryEditor for: self]!

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

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

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

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

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

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

Item was removed:
- ----- 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 removed:
- ----- Method: MetaclassEditor>>edClassFormat (in category 'building') -----
- edClassFormat
- 	^ ClassFormat
- 		size: self instSize
- 		type: self typeOfClass
- 		index: self indexIfCompact!

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

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

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

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

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

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

Item was removed:
- ----- 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 removed:
- ----- Method: ClassDescriptionEditor>>propertyAt: (in category 'accessing properties') -----
- propertyAt: key
- 
- 	^self propertyAt: key ifAbsent: [nil]!

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

Item was removed:
- ----- 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 removed:
- ----- Method: ClassDescriptionEditor>>compiledMethodAt: (in category 'reflecting') -----
- compiledMethodAt: aSelector
- 
- 	^ self compiledMethodAt: aSelector ifAbsent: [ self error: 'key not found' ]!

Item was removed:
- ----- 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 removed:
- ----- Method: MetaclassEditor>>organization (in category 'reflecting') -----
- organization
- 	^ organization ifNil: [organization := OrganizationEditor for: self]!

Item was removed:
- ----- 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 removed:
- ----- 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 removed:
- ----- Method: ClassDescriptionEditor>>includesSelector: (in category 'reflecting') -----
- includesSelector: aSelector
- 	^ (methods ifNil: [self subject] ifNotNil: [methods])
- 		includesSelector: aSelector!

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

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

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

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

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

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

Item was removed:
- ----- Method: ClassEditor class>>initialize (in category 'initialize-release') -----
- initialize
- 	| strings |
- 	strings := #('self' 'super' 'true' 'false' 'nil' 'thisContext').
- 	ReservedNames := strings, strings collect: [:ea | ea asSymbol].!



More information about the Packages mailing list