[Pkg] SystemEditor: SystemEditor-Core-mtf.155.mcz

squeak-dev-noreply at lists.squeakfoundation.org squeak-dev-noreply at lists.squeakfoundation.org
Fri Nov 7 06:45:19 UTC 2008


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

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

Name: SystemEditor-Core-mtf.155
Author: mtf
Time: 6 November 2008, 11:45:04 pm
UUID: 449327d2-c6ee-4cfc-b71e-aa6404689abf
Ancestors: SystemEditor-mtf.154

forked from SystemEditor-mtf.154

=============== Diff against SystemEditor-mtf.154 ===============

Item was added:
+ SystemOrganization addCategory: #'SystemEditor-Core'!

Item was removed:
- ----- 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
- 			notifying: nil
- 			ifFail: [self error: 'Compilation failed'].
- 	node selector == aSelector ifFalse: [self error: 'selector changed!!'].
- 	^ node generate: trailer!

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

Item was removed:
- ----- Method: OrganizationEditor>>subject (in category 'accessing') -----
- subject
- 	^ subject ifNil: [classEditor subject ifNotNilDo: [:aClass | subject := aClass organization]]!

Item was removed:
- ----- Method: ClassEditorValidationTest>>test03SameTypeIsValid (in category 'tests') -----
- test03SameTypeIsValid
- 	editor addInstVarName: 'gamma'.
- 	self assert: editor edIsValid !

Item was removed:
- ----- Method: ClassFormat class>>words (in category 'instance creation') -----
- words
- 	^ self size: 0 spec: self wordsSpec index: 0!

Item was removed:
- ----- Method: MethodEditor>>setSource:classified:stamp:notifying:log: (in category 'initialize-release') -----
- setSource: sourceString classified: catString stamp: timestamp notifying: anObject log: aBoolean
- 	source := sourceString.
- 	category := catString.
- 	stamp := timestamp.
- 	requestor := anObject.
- 	log := aBoolean !

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

Item was removed:
- ----- Method: ClassFormatTest>>testIndexedWithInstSize (in category 'tests') -----
- testIndexedWithInstSize
- 	| old new |
- 	old := ClassFormat indexed: 3.
- 	new := old withInstSize: 5.
- 	self assert: new instSize = 5.
- 	self assert: new instSpec = old instSpec.
- 	self assert: new cClassIndex = old cClassIndex!

Item was removed:
- ----- Method: ClassEditor>>edDependentSubclassesDo: (in category 'building') -----
- edDependentSubclassesDo: aBlock
- "Make sure my subclasses get recompiled if my bindings have changed"
- 	self edRequiresSubclassRebuild ifFalse: [^ #()].
- 	self subclassesDo: [:ea |
- 		ea edInvalidateSuperclass.
- 		aBlock value: ea]!

Item was removed:
- ----- Method: MetaclassEditorProtocolTest>>test10SourceCodeAt (in category 'tests') -----
- test10SourceCodeAt
- 	self assert: (editor sourceCodeAt: #ayin) = (editor subject sourceCodeAt: #ayin)!

Item was removed:
- ----- Method: SystemEditorTest>>test13AtIfAbsentEvaluatesBlock (in category 'tests') -----
- test13AtIfAbsentEvaluatesBlock
- 	| object |
- 	object := Object new.
- 	self assert: (editor at: #'Illegal Name' ifAbsent: [object]) == object!

Item was removed:
- ----- Method: ClassDescriptionEditor>>edIsBehavior (in category 'testing') -----
- edIsBehavior
- "Answers true if I am an editor for a Behavior"
- 	^ true!

Item was removed:
- ----- Method: ClassFormat>>validateAgainstSuper: (in category 'validating') -----
- validateAgainstSuper: superFormat
- "Raise an error if a class with my format cannot inherit from a class with superFormat. Adapted from the various checks in the public ClassBuilder methods"
- 
- 	self instSize < superFormat instSize ifTrue: [self error: 'A subclass lost instance variables'].
- 	superFormat isFixed ifTrue: [^ self]. "Any format can inherit from #normal"
- 	superFormat isVariable ~~ self isVariable ifTrue: [self error: 'Cannot derive a fixed class from a variable one'].
- 	superFormat isBits ~~ self isBits ifTrue: [self error: 'Bit and Pointer classes cannot inherit from one another'].
- 	superFormat isBytes ~~ self isBytes ifTrue: [self error: 'Byte and Word classes cannot inherit from one another'].
- 	!

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

Item was removed:
- ----- 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 removed:
- ----- Method: ClassDescriptionEditor>>allSubclassesDo: (in category 'reflecting') -----
- allSubclassesDo: aBlock 
- 	"Evaluate the argument, aBlock, for each of the receiver's subclasses."
- 
- 	self subclassesDo: 
- 		[:cl | 
- 		aBlock value: cl.
- 		cl allSubclassesDo: aBlock]!

Item was removed:
- ----- Method: ClassEditor class>>forNewClassNamed: (in category '*SystemEditor-Tests') -----
- forNewClassNamed: aSymbol
- 	^ self named: aSymbol for: SystemEditor new!

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

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

Item was removed:
- ----- Method: MetaclassEditorProtocolTest>>test08AddAndRemoveSelector (in category 'tests') -----
- test08AddAndRemoveSelector
- 	editor 
- 		compile: 'pe ^ 1'
- 		classified: 'phoenician'
- 		withStamp: 'cwp 5/30/2004 09:27'
- 		notifying: nil
- 		logSource: true.
- 	editor removeSelector: #pe.
- 	self deny: (editor includesSelector: #pe).
- 	!

Item was removed:
- ----- Method: RootClassEditor>>bindingOf: (in category 'reflecting') -----
- bindingOf: varName
- 	^ nil!

Item was removed:
- ----- Method: ClassEditorOntologyTest>>test05ClassPool (in category 'tests') -----
- test05ClassPool
- 	"To have DoIts be executed in the right context by a debugger or inspector,
- 	the generated class needs to be adoptable by FakeClassPool."
- 
- 	self 
- 		shouldnt: [FakeClassPool adopt: editor class]
- 		raise: Error.!

Item was removed:
- Object subclass: #MethodEditor
- 	instanceVariableNames: 'source category stamp requestor log repository'
- 	classVariableNames: ''
- 	poolDictionaries: ''
- 	category: 'SystemEditor-Squeak'!

Item was removed:
- CategorizerTest subclass: #CategoryEditorTest
- 	instanceVariableNames: ''
- 	classVariableNames: ''
- 	poolDictionaries: ''
- 	category: 'SystemEditor-Tests'!

Item was removed:
- ----- Method: ClassEditor>>addSharedPool: (in category 'editing') -----
- addSharedPool: aSharedPool 
- 	sharedPools ifNil: [sharedPools := subject sharedPools].
- 	sharedPools := sharedPools copyWith: aSharedPool!

Item was removed:
- ----- Method: MethodDictionaryEditor>>do: (in category 'building') -----
- do: aBlock
- 	additions do: aBlock!

Item was removed:
- ----- Method: ClassFormat>>validateAgainstOld: (in category 'validating') -----
- validateAgainstOld: oldFormat
- "Raise an error if a class with my format cannot replace a class with oldFormat. Adapted from ClassBuilder >> validateSubclass:canKeepLayoutFrom:forSubclassFormat:"
- 
- 	oldFormat ifNil: [^ self]. "This class is new, so anything works"
- 	(self isWeak and: [oldFormat isVariable]) ifTrue: [^ self].
- 	self typeOfClass ~~ oldFormat typeOfClass
- 		ifTrue: [self error: 'The new class format is incompatable with the old']!

Item was removed:
- ----- Method: ClassEditorProtocolTest>>test08AddSharedPool (in category 'tests') -----
- test08AddSharedPool
- 	| pool |
- 	pool := Dictionary new.
- 	editor addSharedPool: pool.
- 	self assert: editor sharedPools = (editor subject sharedPools copyWith: pool)!

Item was removed:
- ----- Method: EditorSubjectSubTest>>setUp (in category 'running') -----
- setUp
- 	(Smalltalk at: #EditorSubject)
- 		subclass: #EditorSubjectSub
- 		instanceVariableNames: ''
- 		classVariableNames: ''
- 		poolDictionaries: ''
- 		category: 'SystemEditor-Tests'!

Item was removed:
- TestCase subclass: #EditorSubjectSubTest
- 	instanceVariableNames: ''
- 	classVariableNames: ''
- 	poolDictionaries: ''
- 	category: 'SystemEditor-Tests'!

Item was removed:
- ----- Method: SystemEditor>>associationAt: (in category 'reflecting') -----
- associationAt: aSymbol 
- 	^ self 
- 		associationAt: aSymbol 
- 		ifAbsent: [self error: 'key not found']!

Item was removed:
- ----- Method: SystemEditorTest>>migratedClasses (in category 'asserting') -----
- migratedClasses
- 	| migration |
- 	editor edExpandEditors.
- 	migration := MigrationTransaction new.
- 	editor edPrepareMigration: migration.
- 	^ migration migrators collect: [:ea | ea origin].!

Item was removed:
- ----- Method: SystemEditorTest>>test05ClassEditorsKnowTheirSystemEditors (in category 'tests') -----
- test05ClassEditorsKnowTheirSystemEditors
- 	| first |
- 	first := editor at: #EditorSubject.
- 	self assert: first system == editor!

Item was removed:
- ----- Method: SystemEditorTest>>test03AtCreatesClassEditor (in category 'tests') -----
- test03AtCreatesClassEditor
- 	| classEditor |
- 	classEditor := editor at: #EditorSubject.
- 	self assert: classEditor subject = EditorSubject!

Item was removed:
- ----- Method: TestCategoryEditor>>changedElements (in category 'private') -----
- changedElements
- 	^ changes elementArray!

Item was removed:
- ----- Method: ClassEditorProtocolTest>>test07SharedPools (in category 'tests') -----
- test07SharedPools
- 	self assert: editor sharedPools = editor subject sharedPools!

Item was removed:
- CategorizerEditor subclass: #TestCategoryEditor
- 	instanceVariableNames: 'changes removedElements'
- 	classVariableNames: ''
- 	poolDictionaries: ''
- 	category: 'SystemEditor-Tests'!
- 
- !TestCategoryEditor commentStamp: 'mtf 9/11/2007 12:54' prior: 0!
- A editor for Categorizers. I don't preserve order of changed categories. changes is a categorizer that handles all changes!

Item was removed:
- ----- Method: ClassEditorValidationTest>>test01NoChangeIsValid (in category 'tests') -----
- test01NoChangeIsValid
- 	self assert: editor edIsValid !

Item was removed:
- ----- Method: EditorSubjectSubTest class>>isAbstract (in category 'as yet unclassified') -----
- isAbstract
- 	^ self name == #EditorSubjectSubTest!

Item was removed:
- ----- Method: MetaclassEditorProtocolTest>>test04Superclass (in category 'tests') -----
- test04Superclass
- 	
- 	| result |
- 	editor superclass: self class.
- 	result := editor edBuild.
- 	self deny: result == editor subject.
- 	self assert: result superclass == self class.!

Item was removed:
- ----- Method: ClassEditorProtocolTest>>test29InstVarsArentDuplicated (in category 'tests') -----
- test29InstVarsArentDuplicated
- 	editor addInstVarName: 'gamma'.
- 	editor addInstVarName: 'gamma'.
- 	self assert: editor instVarNames = (editor subject instVarNames copyWith: 'gamma')!

Item was removed:
- ----- Method: MethodDictionaryEditor>>setClassEditor: (in category 'initialization') -----
- setClassEditor: aClassEditor
- 	classEditor := aClassEditor.
- 	additions := IdentityDictionary new.
- 	removals := IdentitySet new.!

Item was removed:
- ----- Method: MethodEditorTest>>test05HasDefaultRepository (in category 'tests') -----
- test05HasDefaultRepository
- 	| editor |
- 	editor := MethodEditor
- 			source: 'one ^ 1'
- 			classified: 'numbers'
- 			stamp: 'cwp 12/11/2005 21:58'
- 			notifying: nil
- 			logging: true.
- 	self assert: editor repository = SourceRepository default!

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

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

Item was removed:
- ----- Method: SystemEditorTest>>test19AtDoesntWrapPools (in category 'tests') -----
- test19AtDoesntWrapPools
- 	self assert: (editor at: #Undeclared) == Undeclared!

Item was removed:
- ClassEditorTest subclass: #ClassEditorBuildTest
- 	instanceVariableNames: ''
- 	classVariableNames: ''
- 	poolDictionaries: ''
- 	category: 'SystemEditor-Tests'!

Item was removed:
- DictionaryEditor subclass: #MethodDictionaryEditor
- 	instanceVariableNames: 'classEditor'
- 	classVariableNames: ''
- 	poolDictionaries: ''
- 	category: 'SystemEditor-Squeak'!

Item was removed:
- TestCase subclass: #MetaclassEditorTest
- 	instanceVariableNames: 'editor'
- 	classVariableNames: ''
- 	poolDictionaries: ''
- 	category: 'SystemEditor-Tests'!

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

Item was removed:
- ----- Method: ClassEditor class>>classRootEditor (in category 'instance creation') -----
- classRootEditor
- "Answer the class of editors for the root of my heiarchy"
- 
- 	^ RootClassEditor!

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

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

Item was removed:
- ----- Method: ClassEditorProtocolTest>>test10Superclass (in category 'tests') -----
- test10Superclass
- 	editor superclass: self class.
- 	self shouldnt: [editor edClassFormat] raise: MessageNotUnderstood.
- 	self assert: editor superclass subject == self class.!

Item was removed:
- ----- Method: ClassFormat>>namedSubclass: (in category 'converting') -----
- namedSubclass: nInstVars 
- 	| newSize |
- 	newSize := self instSize + nInstVars.
- 	newSize > 254 ifTrue: [self error: 'Too many instance variables'].
- 	^ newSize = 0
- 		ifTrue: [self class noState]
- 		ifFalse: [self class named: newSize]!

Item was removed:
- ----- Method: MethodEditorTest>>test02LoggingCanBeSupressed (in category 'tests') -----
- test02LoggingCanBeSupressed
- 	| editor actual |
- 	editor := MethodEditor
- 				source: 'one ^ 1'
- 				classified: 'numbers'
- 				stamp: 'cwp 12/11/2005 21:58'
- 				notifying: nil
- 				logging: false.
- 	editor repository: SourceRepository newInternal.
- 	editor compileFrom: nil for: self class.
- 	actual := editor repository changesStream contents.
- 	self assert: actual = 'xxx'!

Item was removed:
- InvalidSystemChange subclass: #InvalidClassFormat
- 	instanceVariableNames: ''
- 	classVariableNames: ''
- 	poolDictionaries: ''
- 	category: 'SystemEditor-Squeak'!

Item was removed:
- ----- Method: ClassDescriptionEditor>>basicNew (in category 'reflecting') -----
- basicNew
- 	"Primitive. Answer an instance of the receiver (which is a class) with no 
- 	indexable variables. Fail if the class is indexable. Essential. See Object 
- 	documentation whatIsAPrimitive."
- 
- 	<primitive: 70>
- 	"space must be low"
- 	self environment signalLowSpace.
- 	^ self basicNew  "retry if user proceeds"
- !

Item was removed:
- ----- Method: PureBehaviorEditor>>edInvalidateOrganization (in category 'building') -----
- edInvalidateOrganization
- "Mark my organization as requiring a rebuild, by setting it non-nil"
- 	self organization!

Item was removed:
- ----- Method: SystemEditorTest>>test11AtIfAbsentFindsExistingEditor (in category 'tests') -----
- test11AtIfAbsentFindsExistingEditor
- 	| object |
- 	object := editor at: #Object.
- 	self assert: (editor at: #Object ifAbsent: [nil]) == object!

Item was removed:
- ----- Method: SystemEditor>>includesKey: (in category 'reflecting') -----
- includesKey: aSymbol 
- 	(removals includes: aSymbol) ifTrue: [^ false].
- 	(additions includesKey: aSymbol) ifTrue:  [^ true].
- 	subject ifNil: [^ false].
- 	(subject includesKey: aSymbol) ifTrue: [^ true].
- 	^ false!

Item was removed:
- ----- Method: SystemOrganizationEditor class>>for: (in category 'as yet unclassified') -----
- for: anEnvironment
- 	^ self new setSystem: anEnvironment!

Item was removed:
- ----- Method: ClassEditor>>definitionST80 (in category 'reflecting') -----
- definitionST80
- 	"Answer a String that defines the receiver."
- 
- 	| aStream |
- 	aStream := WriteStream on: (String new: 300).
- 	self superclass == nil
- 		ifTrue: [aStream nextPutAll: 'ProtoObject']
- 		ifFalse: [aStream nextPutAll: self  superclass name].
- 	aStream nextPutAll: self kindOfSubclass;
- 			store: self name.
- 	aStream cr; tab; nextPutAll: 'instanceVariableNames: ';
- 			store: self instanceVariablesString.
- 	aStream cr; tab; nextPutAll: 'classVariableNames: ';
- 			store: self classVariablesString.
- 	aStream cr; tab; nextPutAll: 'poolDictionaries: ';
- 			store: self sharedPoolsString.
- 	aStream cr; tab; nextPutAll: 'category: ';
- 			store: (SystemOrganization categoryOfElement: self name) asString.
- 
- 	self superclass ifNil: [ 
- 		aStream nextPutAll: '.'; cr.
- 		aStream nextPutAll: self name.
- 		aStream space; nextPutAll: 'superclass: nil'. ].
- 
- 	^ aStream contents!

Item was removed:
- MetaclassEditorTest subclass: #MetaclassEditorBuildTest
- 	instanceVariableNames: ''
- 	classVariableNames: ''
- 	poolDictionaries: ''
- 	category: 'SystemEditor-Tests'!

Item was removed:
- TestCase subclass: #ClassFormatTest
- 	instanceVariableNames: ''
- 	classVariableNames: ''
- 	poolDictionaries: ''
- 	category: 'SystemEditor-Tests'!

Item was removed:
- ----- Method: ClassEditorOntologyTest>>test10CompiledMethodAt (in category 'tests') -----
- test10CompiledMethodAt
- 	"Compiled methods are immutable, so we don't wrap them for editing."
- 
- 	self assert: (editor compiledMethodAt: #het) == (editor subject compiledMethodAt: #het)!

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

Item was removed:
- ----- Method: MetaclassEditorBuildTest>>test05MethodRemoved (in category 'tests') -----
- test05MethodRemoved
- 	
- 	| dict |
- 	editor removeSelector: #ayin.
- 	dict := editor methodDictionary.
- 	self deny: (dict includesKey: #ayin)!

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

Item was removed:
- ----- Method: ClassEditor>>ensureSharedPoolName: (in category 'editing') -----
- ensureSharedPoolName: aString 
- 	(self allSharedPools includes: aString)
- 		ifFalse: [ self addSharedPoolName: aString].
- 		 !

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

Item was removed:
- ----- Method: OrganizationEditorTest>>test07BuildWritesCommentToChangesFile (in category 'tests') -----
- test07BuildWritesCommentToChangesFile
- 	| remote repository result |
- 	repository := SourceRepository newInternal.
- 	editor := OrganizationEditor for: (ClassEditor on: self class)
- 				repository: repository.
- 	editor classComment: 'comment string' stamp: 'cwp 12/11/2005 21:58'.
- 	result := editor edBuild.
- 	remote := result commentRemoteStr.
- 	self assertRemoteString: remote inRepository: repository matches: 'comment string'!

Item was removed:
- ----- Method: ClassEditorOntologyTest>>test08Superclass (in category 'tests') -----
- test08Superclass
- 	"#superclass should return an editor on the subject's superclass"
- 
- 	self assert: editor superclass subject == EditorSubject superclass!

Item was removed:
- ----- Method: MethodEditorTest>>test04SourcePointerIsSet (in category 'tests') -----
- test04SourcePointerIsSet
- 	| editor cm |
- 	editor := MethodEditor
- 			source: 'one ^ 1'
- 			classified: 'numbers'
- 			stamp: 'cwp 12/11/2005 21:58'
- 			notifying: nil
- 			logging: true.
- 	editor repository: SourceRepository newInternal.
- 	cm := editor compileFrom: self for: self class.
- 	self assert: cm sourcePointer = 33554517!

Item was removed:
- ----- Method: SystemEditor>>debug: (in category 'debugging') -----
- debug: aBoolean
- "see MetaclassEditor>>isDebuggingAsEditor"
- 
- 	debug := aBoolean!

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

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

Item was removed:
- ----- Method: SystemEditorTest>>test12AtIfAbsentCreatesEditorForExistingClass (in category 'tests') -----
- test12AtIfAbsentCreatesEditorForExistingClass
- 	self assert: (editor at: #Object ifAbsent: [nil]) subject == Object!

Item was removed:
- ----- Method: ClassExporterTest>>test01ClassIsAddedToEnvironment (in category 'tests') -----
- test01ClassIsAddedToEnvironment
- 	| class |
- 	class := self createClass.
- 	exporter addClass: class.
- 	exporter commit.
- 	self assert: (Smalltalk at: class name) == class
- 	!

Item was removed:
- ----- Method: ClassFormat>>bits (in category 'accessing') -----
- bits
- 	"Based on ClassBuilder>>format:variable:words:pointers:weak - ar 7/11/1999 06:39 "
- 
- 	| bits |
- 	bits := (instSize+1) // 64. 	
- 	bits := (bits bitShift: 5) + cClassIndex.
- 	bits := (bits bitShift: 4) + instSpec.
- 	bits := (bits bitShift: 6) + ((instSize+1)\\64).  "+1 since prim instSize field includes header"
- 	bits := (bits bitShift: 1). "This shift plus integer bit lets wordSize work like byteSize"
- 	^ bits!

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

Item was removed:
- ----- Method: TestCategoryEditor>>changesRemoveCategory: (in category 'accessing') -----
- changesRemoveCategory: category
- 	changes removeCategory: category!

Item was removed:
- ----- Method: ClassFormat class>>compiledMethodSpec (in category 'storage specifications') -----
- compiledMethodSpec
- 	^ 12!

Item was removed:
- ----- Method: ClassEditor>>edRequiresMigration (in category 'building') -----
- edRequiresMigration
- 	^ subject
- 		ifNotNil: [self format ~= subject format]
- 		ifNil: [false]!

Item was removed:
- ----- Method: ClassEditorProtocolTest>>test21BeWeak (in category 'tests') -----
- test21BeWeak
- 	editor typeOfClass: #weak.
- 	self assert: editor typeOfClass == #weak.
- 	self assert: editor isWords.
- 	self assert: editor isVariable.
- 	self assert: editor isPointers.
- 	self deny: editor isBits.
- !

Item was removed:
- ----- Method: SourceRepository>>storeMethod:forClass:category:stamped:prior: (in category 'creation') -----
- storeMethod: sourceString forClass: aClass category: catString stamped: stampString prior: sourcePointer
- 	| remote stream |
- 	self assureStartupStampLogged.
- 	stream := self changesStream.
- 	stream
- 		setToEnd;
- 		cr;
- 		nextPut: $!!;
- 		nextPutAll: aClass name;
- 		nextPutAll: ' methodsFor: ';
- 		print: catString;
- 		nextPutAll: ' stamp: ';
- 		print: stampString.
- 	sourcePointer ifNotNil: [stream nextPutAll: ' prior: '; print: sourcePointer].
- 	stream
- 		nextPut: $!!; cr.
- 	remote := RemoteString 
- 				newString: sourceString
- 				onFileNumber: self changesIndex 
- 				toFile: stream.
- 	stream space; nextPut: $!!.
- 		^ remote!

Item was removed:
- ----- Method: ClassEditorProtocolTest>>test22BeVariable (in category 'tests') -----
- test22BeVariable
- 	editor typeOfClass: #variable.
- 	self assert: editor typeOfClass == #variable.
- 	self assert: editor isWords.
- 	self assert: editor isVariable.
- 	self assert: editor isPointers.
- 	self deny: editor isWeak.
- 	self deny: editor isBits.
- !

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

Item was removed:
- ----- Method: ClassFormat class>>namedSpec (in category 'storage specifications') -----
- namedSpec
- 	^ 1!

Item was removed:
- ----- Method: ClassEditor>>setSubject:system: (in category 'initialize-release') -----
- setSubject: aClass system: aSystemEditor 
- 	subject := aClass.
- 	system := aSystemEditor. 
- 	subject ifNil: 
- 			[superEditor := aSystemEditor at: #Object.
- 			name := #Annonymous.
- 			type := #normal.
- 			instVarNames := Array new.
- 			classVarNames := Array new.
- 			sharedPools := Array new.
- 			methods := MethodDictionaryEditor for: self.
- 			self class edInitializeForNewClass]!

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

Item was removed:
- ----- Method: MetaclassEditorTest>>setUp (in category 'running') -----
- setUp
- 	editor := (ClassEditor on: EditorSubject) class!

Item was removed:
- ----- Method: SourceRepositoryTest>>test03StoreCommentClassStampedPrior (in category 'tests') -----
- test03StoreCommentClassStampedPrior
- 	| remote |
- 	remote := repository 
- 		storeComment: 'This is a comment.'
- 		forClass: self class
- 		stamped: 'cwp 12/11/2005 21:58'
- 		prior: 42.
- 	self assert: repository changesStream contents = 'xxx
- !!SourceRepositoryTest commentStamp: ''cwp 12/11/2005 21:58'' prior: 42!!
- This is a comment.!!'.
- 
- 	self assert: remote sourceFileNumber = 2.
- 	self assert: remote position = 74!

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

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

Item was removed:
- ----- Method: MetaclassEditor>>edBuild (in category 'building') -----
- edBuild
- 	| result class |
- 	class := self subject ifNil: [Metaclass] ifNotNil: [self 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.
- 	self decoratorsDo: [:ea | ea edBuildInto: product].
- 	^ result!

Item was removed:
- ----- Method: ClassFormat class>>noStateSpec (in category 'storage specifications') -----
- noStateSpec
- 	^ 0!

Item was removed:
- ----- Method: ClassEditorBuildTest>>test10MethodRemoved (in category 'tests') -----
- test10MethodRemoved
- 	
- 	| dict |
- 	editor removeSelector: #het.
- 	dict := editor methodDictionary.
- 	self assert: dict isEmpty!

Item was removed:
- ----- Method: ClassEditor>>subclassesOrEditors (in category 'reflecting') -----
- subclassesOrEditors
- "Answer all of my subclasses, as either classes or editors, whichever is easier"
- 
- 	^ system edSubclassesOrEditorsOf: self!

Item was removed:
- ----- Method: ClassFormat class>>named: (in category 'instance creation') -----
- named: size
- 	^ self
- 		size: size
- 		spec: self namedSpec
- 		index: 0!

Item was removed:
- ----- Method: ClassEditor>>removeSharedPool: (in category 'editing') -----
- removeSharedPool: aSharedPool
- 	"We use reject based on identity instead of copyWithout: here."
- 
- 	sharedPools ifNil: [sharedPools := subject sharedPools].
- 	sharedPools := sharedPools reject: [:each | each == aSharedPool]!

Item was removed:
- ----- Method: MetaclassEditorTest class>>isAbstract (in category 'as yet unclassified') -----
- isAbstract
- 	^ self name == #MetaclassEditorTest!

Item was removed:
- ----- Method: SystemEditorTest>>test16KeyAtIdentityValueFindEditors (in category 'tests') -----
- test16KeyAtIdentityValueFindEditors
- 	| classEditor |
- 	classEditor := editor at: #Object.
- 	self assert: (editor keyAtIdentityValue: classEditor ifAbsent: [nil]) == #Object!

Item was removed:
- ----- Method: EditorSubject>>het (in category 'phoenician') -----
- het
- 	^ 'first letter of the phoenician alphabet'!

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

Item was removed:
- ClassEditorTest subclass: #ClassEditorValidationTest
- 	instanceVariableNames: ''
- 	classVariableNames: ''
- 	poolDictionaries: ''
- 	category: 'SystemEditor-Tests'!

Item was removed:
- ----- Method: ClassEditor>>category (in category 'reflecting') -----
- category
- 	"If this isn't cached, SystemEditorBrowser is really slow. And it doesn't affect the correctness of the editor, so do it by default"
- 	^ category ifNil: [category := subject category]!

Item was removed:
- ----- Method: ClassEditor>>binding (in category 'reflecting') -----
- binding
- 	^ system bindingOf: self name!

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

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

Item was removed:
- ----- Method: MethodEditorTest>>sourcePointer (in category 'emulating') -----
- sourcePointer
- 	^ 42!

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

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

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

Item was removed:
- ----- Method: ClassEditor>>edPrepareMigration: (in category 'building') -----
- edPrepareMigration: txn
- 	self subject ifNil: [^ self].
- 	self edRequiresBuild 
- 		ifTrue: [self edPrepareInstanceMigration: txn]
- 		ifFalse: [super edPrepareMigration: txn]!

Item was removed:
- ----- 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 removed:
- ----- Method: ClassEditor>>classComment:stamp: (in category 'editing') -----
- classComment: aTextOrString stamp: aString
- 	self organization classComment: aTextOrString stamp: aString!

Item was removed:
- ----- Method: ClassExporter>>environment (in category 'public') -----
- environment
- 	^ environment!

Item was removed:
- ----- Method: ClassOrganizer>>edClassComment:stamp: (in category '*systemeditor-squeak') -----
- edClassComment: aString stamp: aStamp
- "Set the comment and stamp directly, with no checks.This works around a silly check in ClassOrganizer>>classComment:stamp: in Croquet. This check raises an error if the subject is either nil or a metaclass. The check does not exist in Squeak 3.8 and above"
- 	^ super classComment: aString stamp: aStamp!

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

Item was removed:
- ----- Method: ClassEditorProtocolTest>>test27Subclass (in category 'tests') -----
- test27Subclass
- 	| sub |
- 	sub := editor
- 			subclass: #EditorSubjectSubclass
- 			instanceVariableNames: ''
- 			classVariableNames: ''
- 			poolDictionaries: ''
- 			category: 'SystemEditor-Tests'.
- 	self assert: sub subject isNil.
- 	self assert: sub name = #EditorSubjectSubclass.
- 	self assert: sub instVarNames isEmpty.
- 	self assert: sub classVarNames isEmpty.
- 	self assert: sub sharedPools isEmpty.!

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

Item was removed:
- ----- Method: ClassEditorProtocolTest>>test38SharedPoolsString (in category 'tests') -----
- test38SharedPoolsString
- 
- 	self assert: editor sharedPoolsString = editor subject sharedPoolsString!

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

Item was removed:
- Object subclass: #EditorSubject
- 	instanceVariableNames: 'alpha beta'
- 	classVariableNames: 'Beth Aleph'
- 	poolDictionaries: 'EditorSubjectPool'
- 	category: 'SystemEditor-Tests'!
- EditorSubject class
- 	instanceVariableNames: 'omega'!

Item was removed:
- ----- Method: MetaclassEditorBuildTest>>test04ExistingMethods (in category 'tests') -----
- test04ExistingMethods
- 	
- 	| result |
- 	editor compile: 'pe ^ 2'.
- 	result := editor edBuild.
- 	self assert: (result compiledMethodAt: #ayin) == (editor subject compiledMethodAt: #ayin)!

Item was removed:
- InvalidSystemChange subclass: #IllegalVariableName
- 	instanceVariableNames: ''
- 	classVariableNames: ''
- 	poolDictionaries: ''
- 	category: 'SystemEditor-Squeak'!

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

Item was removed:
- ----- Method: ClassEditorValidationTest>>test07InstVarNamedSuper (in category 'tests') -----
- test07InstVarNamedSuper
- 
- 	editor addInstVarName: 'super'.
- 	self should: [editor validate] raise: IllegalVariableName.!

Item was removed:
- ----- Method: ClassFormat>>isVariable (in category 'testing') -----
- isVariable
- 	"Answer whether the receiver has indexable variables."
- 
- 	^ self instSpec >= 2!

Item was removed:
- ----- Method: MetaclassEditor>>system (in category 'accessing') -----
- system
- 	^ system ifNil: [system := editor system]!

Item was removed:
- ----- Method: MetaclassEditor>>product (in category 'building') -----
- product
- 	^ product ifNil: [product := editor product class]!

Item was removed:
- ----- Method: SystemEditor>>at:ifAbsent: (in category 'reflecting') -----
- at: aSymbol ifAbsent: aBlock
- 	| newEditor |
- 	(removals includes: aSymbol) ifTrue: [^ aBlock value].
- 	additions at: aSymbol ifPresent: [:editor | ^ editor].
- 	subject at: aSymbol ifPresent: [:obj |
- 		newEditor := AbstractEditor on: obj for: self ifNotHandled: [^ obj].
- 		^ newEditor edRegisterEditor].
- 	^ aBlock value!

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

Item was removed:
- ----- Method: ClassEditorProtocolTest>>test19BeBytes (in category 'tests') -----
- test19BeBytes
- 	editor typeOfClass: #bytes.
- 	self assert: editor typeOfClass == #bytes.
- 	self assert: editor isBytes.
- 	self assert: editor isBits.
- 	self assert: editor isVariable.
- 	self deny: editor isPointers.!

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

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

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

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

Item was removed:
- ----- Method: CategorizerEditor>>listAtCategoryNamed: (in category 'reflecting - accessing') -----
- listAtCategoryNamed: catName
- 
- 	| category list |
- 	category := catName asSymbol.
- 	(self categories includes: category) ifFalse: [^ nil].
- 	list := self subject ifNotNil: [self subject listAtCategoryNamed: category].
- 	list ifNil: [list := OrderedCollection new].
- 	list := list asOrderedCollection.
- 	self removedElements do: [:ea | list removeAll: ea].
- 	self changedElementsAndCategoriesDo: [:ea :cat |
- 		list removeAll: ea. cat = category ifTrue: [list add: ea]].
- 	^ list
- !

Item was removed:
- ----- Method: OrganizationEditor class>>for: (in category 'instance creation') -----
- for: aClassEditor
- 	^ self for: aClassEditor repository: SourceRepository default!

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

Item was removed:
- ----- Method: ClassEditor>>bindingOf: (in category 'reflecting') -----
- bindingOf: varName
- 	"Answer the binding of some variable resolved in the scope of the receiver"
- 	| aSymbol |
- 	aSymbol := varName asSymbol.
- 
- 	"First look in classVar dictionary."
- 	(self classVarNames includes: aSymbol)
- 		ifTrue: [^ subject ifNotNil: [subject classPool bindingOf: aSymbol]].
- 
- 	"Next look in shared pools."
- 	self sharedPools do: [:pool |
- 		(pool bindingOf: aSymbol) ifNotNilDo: [:binding | ^binding]].
- 
- 	"Next look in declared environment."
- 	(self environment bindingOf: aSymbol) ifNotNilDo: [:binding | ^binding].
- 
- 	"Finally look higher up the superclass chain and fail at the end."
- 	^ self superclassOrEditor bindingOf: aSymbol!

Item was removed:
- ----- Method: CategorizerEditor>>removeElement: (in category 'reflecting - accessing') -----
- removeElement: element
- 	self subclassResponsibility!

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

Item was removed:
- ----- Method: ClassEditorBuildTest>>test17NewMethodsAreClassified (in category 'tests') -----
- test17NewMethodsAreClassified
- 	
- 	| migration organizer |
- 	editor 
- 		compile: 'zayin ^ 2'
- 		classified: 'numbers'
- 		withStamp: 'cwp 5/30/2004 09:27'
- 		notifying: nil
- 		logSource: true.
- 	
- 	migration := MigrationTransaction new.
- 	editor edPrepareMigration: migration.
- 	organizer := migration destinationFor: editor subject organization.
- 	self assert: (organizer categoryOfElement: #zayin) = 'numbers'!

Item was removed:
- ----- Method: ClassEditorProtocolTest>>test30ClassVarsArentDuplicated (in category 'tests') -----
- test30ClassVarsArentDuplicated
- 	editor addClassVarName: 'Gimel'.
- 	editor addClassVarName: 'Gimel'.
- 	self assert: editor classVarNames = (editor subject classVarNames copyWith: 'Gimel')!

Item was removed:
- ----- Method: MethodDictionaryEditor>>remove: (in category 'editing') -----
- remove: aSymbol
- 	classEditor edInvalidateOrganization.
- 	additions removeKey: aSymbol ifAbsent: [].
- 	removals add: aSymbol!

Item was removed:
- ----- Method: MethodEditor>>selector (in category 'accessing') -----
- selector
- 	^ Parser new parseSelector: source!

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

Item was removed:
- ----- Method: SystemEditor>>at: (in category 'reflecting') -----
- at: aSymbol 
- 	^ self 
- 		at: aSymbol 
- 		ifAbsent: [self error: 'key not found']!

Item was removed:
- ----- Method: MethodDictionaryEditor>>removals (in category 'accessing') -----
- removals
- 	^ removals!

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

Item was removed:
- ----- Method: SystemEditor>>edSubclassesOrEditorsOf:do: (in category 'building') -----
- edSubclassesOrEditorsOf: anEditor do: aBlock
- "Evaluate aBlock for each subclasses of the given ClassEditor, as either an editor (if it has changed), or as a class (if it has not changed). Does not add any items to my additions list"
- 
- 	| subclasses |
- 	subclasses := anEditor subject
- 		ifNil: [Set new]
- 		ifNotNilDo: [ :class | class subclasses asSet].
- 	additions do: [ :ea |
- 		subclasses remove: ea subject ifAbsent: [].
- 		((ea isKindOf: ClassDescriptionEditor)
- 			and: [ea superclassOrEditor == anEditor])
- 				ifTrue: [aBlock value: ea]].
- 	removals do: [ :removedKey | subclasses remove: (subject at: removedKey) ifAbsent: []].
- 	subclasses do: aBlock!

Item was removed:
- ----- Method: ClassFormat class>>noState (in category 'instance creation') -----
- noState
- 	^ self size: 0 spec: self noStateSpec index: 0!

Item was removed:
- SharedPool subclass: #EditorSubjectPool
- 	instanceVariableNames: ''
- 	classVariableNames: ''
- 	poolDictionaries: ''
- 	category: 'SystemEditor-Tests'!

Item was removed:
- ----- 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 removed:
- ----- Method: SystemEditor>>keyAtIdentityValue:ifAbsent: (in category 'reflecting') -----
- keyAtIdentityValue: anObject ifAbsent: aBlock
- 	^ additions 
- 		keyAtIdentityValue: anObject
- 		ifAbsent: [subject 
- 					keyAtIdentityValue: anObject 
- 					ifAbsent: aBlock]!

Item was removed:
- ----- Method: MetaclassEditor>>basicRemoveSelector: (in category 'debugging') -----
- basicRemoveSelector: selector
- "For running do-its against my ClassEditor"
- 
- 	^ superclass basicRemoveSelector: selector!

Item was removed:
- ----- Method: MethodEditorTest>>test01FirstCompilationIsLogged (in category 'tests') -----
- test01FirstCompilationIsLogged
- 	| editor actual expected |
- 	editor := MethodEditor
- 				source: 'one ^ 1'
- 				classified: 'numbers'
- 				stamp: 'cwp 12/11/2005 21:58'
- 				notifying: nil
- 				logging: true.
- 	editor repository: SourceRepository newInternal.
- 	editor compileFrom: nil for: self class.
- 	actual := editor repository changesStream contents.
- 	expected := 'xxx
- !!MethodEditorTest methodsFor: ''numbers'' stamp: ''cwp 12/11/2005 21:58''!!
- one ^ 1!! !!'.
- 	self assert: actual = expected!

Item was removed:
- ----- Method: CategorizerEditor>>changedCategories (in category 'accessing changed elements') -----
- changedCategories
- "Answer the set of categories whose elements have changed"
- 
- 	^ (self changedElementsAndCategoriesCollect:
- 		[:anElement :aCategory | aCategory]) asSet
- !

Item was removed:
- ----- Method: MethodEditor>>compileFrom:for: (in category 'building') -----
- compileFrom: aCompiledMethod for: aClassEditor
- 	| result remote |
- 	result := self compileFor: aClassEditor.
- 	^ log 
- 		ifFalse: [result]
- 		ifTrue: 
- 			[remote := self logCompilationFrom: aCompiledMethod for: aClassEditor.
- 			result setSourcePosition: remote position inFile: remote sourceFileNumber]
- !

Item was removed:
- ----- Method: ClassEditorProtocolTest>>test25CompileClassifiedNotifying (in category 'tests') -----
- test25CompileClassifiedNotifying
- 	self deny: (editor includesSelector: #zayin).
- 	editor 
- 		compile: 'zayin ^ 1'
- 		classified: 'numbers'
- 		notifying: nil.
- 	self assert: (editor includesSelector: #zayin)!

Item was removed:
- ----- Method: MetaclassEditorProtocolTest>>test02AddInstVarName (in category 'tests') -----
- test02AddInstVarName
- 	editor addInstVarName: 'psi'.
- 	self assert: editor instVarNames = (editor subject instVarNames copyWith: 'psi')!

Item was removed:
- ----- Method: CategorizerEditor>>renameCategory:toBe: (in category 'reflecting - accessing') -----
- renameCategory: oldCatString toBe: newCatString
- 	| oldCategory newCategory originalCategory |
- 	newCategory := newCatString asSymbol.
- 	oldCategory := oldCatString asSymbol.
- 	originalCategory := self oldCategoryFor: oldCategory.
- 	(self categories includes: newCategory) ifTrue: [^ self].
- 	(self categories includes: oldCategory) ifFalse: [^ self].
- 	categories replaceAll: oldCategory with: newCategory.
- 	renamedCategories at: originalCategory put: newCategory.!

Item was removed:
- ----- Method: CategorizerEditor>>classify:under: (in category 'reflecting - accessing') -----
- classify: element under: heading 
- 	self classify: element under: heading suppressIfDefault: true!

Item was removed:
- ----- Method: PureBehaviorEditor>>decorateWith: (in category 'accessing decorators') -----
- decorateWith: aClass
- 	decorators ifNil: [decorators := IdentityDictionary new].
- 	^ decorators at: aClass ifAbsentPut: [aClass for: self]!

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

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

Item was removed:
- ----- Method: SystemEditor>>classOrEditorFor: (in category 'accessing') -----
- classOrEditorFor: aClass
- "Answers an editor if the class is being edited, or a class if it is not"
- 
- 	| editor |
- 	aClass edIsEditor ifTrue: [^ aClass].
- 	editor := additions at: aClass theNonMetaClass name ifAbsent: [^ aClass].
- 	^ aClass isMeta ifTrue: [editor class] ifFalse: [editor]!

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

Item was removed:
- ----- Method: OrganizationEditor>>writeComment (in category 'building') -----
- writeComment
- 	| previous subject |
- 	subject := self subject.
- 	previous := subject ifNotNil: [subject commentRemoteStr].
- 	remote := previous 
- 				ifNil: [repository 
- 						storeComment: comment
- 						forClass: classEditor
- 						stamped: stamp]
- 				ifNotNil: [repository 
- 							storeComment: comment
- 							forClass: classEditor
- 							stamped: stamp
- 							replacing: previous].!

Item was removed:
- ----- Method: SourceRepository>>assureStartupStampLogged (in category 'creation') -----
- assureStartupStampLogged
- 	SmalltalkImage current assureStartupStampLogged.!

Item was removed:
- TestCase subclass: #MethodEditorTest
- 	instanceVariableNames: ''
- 	classVariableNames: ''
- 	poolDictionaries: ''
- 	category: 'SystemEditor-Tests'!

Item was removed:
- ----- 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 removed:
- ----- Method: OrganizationEditorTest>>test05SetCommentStamp (in category 'tests') -----
- test05SetCommentStamp
- 	editor := OrganizationEditor for: EditorSubject.
- 	editor classComment: 'comment string' stamp: 'cwp 12/11/2005 21:58'.
- 	self assert: editor commentStamp = 'cwp 12/11/2005 21:58'.!

Item was removed:
- ----- Method: MetaclassEditor>>inheritsFrom: (in category 'debugging') -----
- inheritsFrom: aClass
- "This allows aClassEditor isKindOf: Object to work properly"
- 
- 	^ superclass inheritsFrom: aClass!

Item was removed:
- ----- Method: SystemEditorTest>>test02DefaultSubjectIsSmalltalk (in category 'tests') -----
- test02DefaultSubjectIsSmalltalk
- 	self assert: editor subject == Smalltalk!

Item was removed:
- ----- Method: OrganizationEditor>>classComment:stamp: (in category 'reflecting') -----
- classComment: aStringOrText stamp: aString
- 	comment := aStringOrText.
- 	stamp := aString.
- 	isDirty := true
- 	!

Item was removed:
- ----- Method: ClassEditorProtocolTest>>test02AddInstVarName (in category 'tests') -----
- test02AddInstVarName
- 	editor addInstVarName: 'gamma'.
- 	self assert: editor instVarNames = (editor subject instVarNames copyWith: 'gamma')!

Item was removed:
- ----- Method: CategorizerEditor>>oldCategoryFor: (in category 'as yet unclassified') -----
- oldCategoryFor: newCategory
- 	^ renamedCategories keyAtValue: newCategory ifAbsent: [newCategory]!

Item was removed:
- ----- Method: MethodEditor>>repository: (in category 'accessing') -----
- repository: anObject
- 	repository := anObject!

Item was removed:
- ----- Method: ClassEditor>>edRequiresBuild (in category 'building') -----
- edRequiresBuild
- 	self edRequiresRecompile ifTrue: [^ true].
- 	self edSuperclassHasChanged ifTrue: [^ true].
- 	self edNameHasChanged ifTrue: [^ true].
- 	self class edRequiresBuild ifTrue: [^ true].
- 	self decoratorsDo: [:ea | ea edRequiresBuild ifTrue: [^ true]].
- 	^ false!

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

Item was removed:
- ----- Method: OrganizationEditorTest>>test12ReadingCommentDoesntRequireBuild (in category 'tests') -----
- test12ReadingCommentDoesntRequireBuild
- 	editor := OrganizationEditor for: (ClassEditor on: self class).
- 	editor classComment.
- 	self deny: editor edRequiresBuild!

Item was removed:
- ----- Method: ClassExporter class>>on: (in category 'instance creation') -----
- on: anEnvironment
- 	^ self new setEnvironment: anEnvironment!

Item was removed:
- ----- Method: ClassEditor>>classPool (in category 'reflecting') -----
- classPool
- 	| pool |
- 	pool := subject ifNil: [Dictionary new] ifNotNil: [subject classPool copy].
- 	classVarNames ifNil: [^ pool].
- 	pool keys do: [:ea | (classVarNames includes: ea) ifFalse: [pool removeKey: ea]].
- 	classVarNames do: [:ea | (pool includesKey: ea) ifFalse: [pool at: ea put: nil]].
- 	^ pool!

Item was removed:
- ----- Method: EditorSubjectSubTest>>createClass (in category 'support') -----
- createClass
- 	^ self createClassNamed: #EditorSubjectSub2!

Item was removed:
- ----- Method: ClassEditorProtocolTest>>test42Comment (in category 'tests') -----
- test42Comment
- 	self assert: (editor comment beginsWith: 'Main comment stating the purpose')!

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

Item was removed:
- ----- Method: CategorizerEditor>>addCategory:before: (in category 'reflecting - accessing') -----
- addCategory: catString before: nextCategory
- 	"I don't support ordering"
- 	| newCategory |
- 	newCategory := catString asSymbol.
- 	(self categories includes: newCategory) ifTrue: [^ self].
- 	categories add: newCategory before: nextCategory!

Item was removed:
- ----- Method: ClassFormat class>>bytesSpec (in category 'storage specifications') -----
- bytesSpec
- 	^ 8!

Item was removed:
- ----- Method: ClassFormat class>>wordsSpec (in category 'storage specifications') -----
- wordsSpec
- 	^ 6!

Item was removed:
- ----- Method: MethodDictionaryEditor class>>empty (in category 'instance creation') -----
- empty
- 	^ self on: MethodDictionary new!

Item was removed:
- ----- Method: OrganizationEditor>>commentRemoteStr (in category 'SystemEditor-Editors') -----
- commentRemoteStr
- 	"If we are dirty the comment has been explicitly set and if
- 	it was set to something else than nil we lazily create the remote String."
- 
- 	(isDirty and: [comment notNil] and: [remote isNil]) ifTrue: [self writeComment].
- 	^ remote ifNil: [self subject ifNotNil: [self subject commentRemoteStr]]!

Item was removed:
- ----- Method: MethodDictionaryEditor>>additions (in category 'accessing') -----
- additions
- 	^ additions!

Item was removed:
- ----- Method: CategorizerEditor>>edPrepareMigration: (in category 'building') -----
- edPrepareMigration: txn
- 	self edRequiresBuild
- 		ifTrue: [txn addMigrator: (ObjectMigrator 
- 									origin: self subject 
- 									destination: self edBuild)]!

Item was removed:
- ----- Method: MethodEditorTest>>test03RecompilationIsLogged (in category 'tests') -----
- test03RecompilationIsLogged
- 	| editor actual expected |
- 	editor := MethodEditor
- 				source: 'one ^ 1'
- 				classified: 'numbers'
- 				stamp: 'cwp 12/11/2005 21:58'
- 				notifying: nil
- 				logging: true.
- 	editor repository: SourceRepository newInternal.
- 	editor compileFrom: self for: self class.
- 	actual := editor repository changesStream contents.
- 	expected := 'xxx
- !!MethodEditorTest methodsFor: ''numbers'' stamp: ''cwp 12/11/2005 21:58'' prior: 42!!
- one ^ 1!! !!'.
- 	self assert: actual = expected!

Item was removed:
- ----- Method: MetaclassEditor>>selectorAtMethod:setClass: (in category 'debugging') -----
- selectorAtMethod: method setClass: classResultBlock
- "For getting the class of a method prior to 3.9"
- 
- 	^ superclass selectorAtMethod: method setClass: classResultBlock!

Item was removed:
- ----- Method: ClassExporter>>forwardIdentities (in category 'private') -----
- forwardIdentities
- 	oldClasses := oldClasses asArray.
- 	newClasses := newClasses asArray.
- 	oldClasses  elementsForwardIdentityTo: newClasses.
- 	oldClasses := nil.
- 	newClasses := nil.!

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

Item was removed:
- ----- Method: SystemEditorTest>>denyClassesAreMigrated: (in category 'asserting') -----
- denyClassesAreMigrated: classes 
- 	self deny: (self migratedClasses includesAnyOf: classes)!

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

Item was removed:
- ----- Method: SourceRepositoryTest>>test01StoreCommentClassStampedReplacing (in category 'tests') -----
- test01StoreCommentClassStampedReplacing
- 	| remote |
- 	remote := repository 
- 		storeComment: 'This is a comment.'
- 		forClass: self class
- 		stamped: 'cwp 12/11/2005 21:58'
- 		replacing: (RemoteString newFileNumber: 1 position: 42).
- 	self assert: repository changesStream contents = 'xxx
- !!SourceRepositoryTest commentStamp: ''cwp 12/11/2005 21:58'' prior: 16777258!!
- This is a comment.!!'.
- 
- 	self assert: remote sourceFileNumber = 2.
- 	self assert: remote position = 80!

Item was removed:
- SystemOrganization addCategory: #'SystemEditor-Core'!
- SystemOrganization addCategory: #'SystemEditor-Squeak'!
- SystemOrganization addCategory: #'SystemEditor-Tests'!

Item was removed:
- ----- Method: ClassFormatTest>>testNamed (in category 'tests') -----
- testNamed
- 	| format |
- 	format := ClassFormat named: 3.
- 	self assert: format instSize = 3.
- 	self assert: format isFixed.
- 	self assert: format isPointers.
- 	self assert: format isWords.
- 	self deny: format isVariable.
- 	self deny: format isBits.
- 	self deny: format isBytes.
- 	self deny: format isWeak!

Item was removed:
- ----- Method: OrganizationEditor>>edBuild (in category 'building') -----
- edBuild
- 	| result |
- 	result := super edBuild.
- 	result
- 		edClassComment: self commentRemoteStr
- 		stamp: self commentStamp.
- 	^ result!

Item was removed:
- ----- Method: InstanceMigratorTest>>testMigratingCompiledMethod (in category 'tests') -----
- testMigratingCompiledMethod
- 	| migrator oldInstance newInstance |
- 	migrator := InstanceMigrator from: CompiledMethod to: CompiledMethod.
- 	oldInstance := self class compiledMethodAt: #testMigratingCompiledMethod.
- 	newInstance := migrator migrate: oldInstance.
- 	self assert: newInstance class == CompiledMethod.
- 	self assert: newInstance basicSize = oldInstance basicSize.
- 	self assert: newInstance header = oldInstance header.!

Item was removed:
- ----- Method: SystemEditor>>edSubclassesOf:do: (in category 'building') -----
- edSubclassesOf: anEditor do: aBlock
- "Answers all subclasses of the given ClassEditor, as editors"
- 
- 	self edSubclassesOrEditorsOf: anEditor do: [:ea | aBlock value: (self edEditorFor: ea)]!

Item was removed:
- TestCase subclass: #SystemEditorTest
- 	instanceVariableNames: 'editor'
- 	classVariableNames: ''
- 	poolDictionaries: ''
- 	category: 'SystemEditor-Tests'!

Item was removed:
- ----- Method: ClassFormat>>isFixed (in category 'testing') -----
- isFixed
- 	"Answer whether the receiver does not have a variable (indexable) part."
- 
- 	^self isVariable not!

Item was removed:
- ----- Method: SystemEditorTest>>test06AtDoesntCreateNewClass (in category 'tests') -----
- test06AtDoesntCreateNewClass
- 	self should: [editor at: #EditorSubject2] raise: Error
- 	!

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

Item was removed:
- ----- Method: MethodDictionaryEditor>>edPrepareMigration:for: (in category 'building') -----
- edPrepareMigration: txn for: aClassEditor
- 	txn addMigrator: (ObjectMigrator
- 		origin: self subject
- 		destination: (self buildFor: aClassEditor))!

Item was removed:
- ----- Method: ClassFormat>>isPointers (in category 'testing') -----
- isPointers
- 	"Answer whether the receiver contains just pointers (not bits)."
- 
- 	^self isBits not!

Item was removed:
- ----- Method: SourceRepositoryTest>>test04StoreMethodReplacing (in category 'tests') -----
- test04StoreMethodReplacing
- 	| remote actual expected |
- 	remote := repository 
- 				storeMethod: 'one ^ 1'
- 				forClass: self class
- 				category: 'numbers'
- 				stamped: 'cwp 12/11/2005 21:58'
- 				replacing: (RemoteString newFileNumber: 1 position: 42).
- 	actual := repository changesStream contents.
- 	expected := 'xxx
- !!SourceRepositoryTest methodsFor: ''numbers'' stamp: ''cwp 12/11/2005 21:58'' prior: 16777258!!
- one ^ 1!! !!'.
- 	self assert: actual = expected.
- 	self assert: remote sourceFileNumber = 2.
- 	self assert: remote position = 95!

Item was removed:
- ----- Method: ClassEditor>>subclassesOrEditorsDo: (in category 'reflecting') -----
- subclassesOrEditorsDo: aBlock
- "Evaluates aBlock for all of my subclasses, as either classes or editors, whichever is easier"
- 
- 	system edSubclassesOrEditorsOf: self do: aBlock!

Item was removed:
- ----- 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 removed:
- ----- Method: ClassEditorProtocolTest>>test18NewFormat (in category 'tests') -----
- test18NewFormat
- 	| superFormat editorFormat |
- 	editor typeOfClass: #variable.
- 	superFormat := ClassFormat fromBits: EditorSubject superclass format.
- 	editorFormat := superFormat indexedSubclass: editor instVarNames size.
- 	self assert: editor format = editorFormat bits!

Item was removed:
- ----- Method: SystemEditorTest>>test01SubjectCanBeSpecified (in category 'tests') -----
- test01SubjectCanBeSpecified
- 	editor := SystemEditor on: Smalltalk.
- 	self assert: editor subject == Smalltalk!

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

Item was removed:
- ----- Method: ClassEditorProtocolTest>>test20BeWords (in category 'tests') -----
- test20BeWords
- 	editor typeOfClass: #words.
- 	self assert: editor typeOfClass == #words.
- 	self assert: editor isWords.
- 	self assert: editor isBits.
- 	self assert: editor isVariable.
- 	self deny: editor isPointers.!

Item was removed:
- ----- Method: ClassEditorOntologyTest>>test01Creation (in category 'tests') -----
- test01Creation
- 	"This invariant allows editors and their subject classes to use
- 	exactly the same reflection protocol, so that the only modification
- 	required to allow tools to modify the system atomically is to send
- 	#commit when all modifications are complete."
- 
- 	self assert: editor subject == EditorSubject.
- 	self assert: editor class subject == EditorSubject class!

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

Item was removed:
- ----- Method: OrganizationEditorTest>>test10CategoryOfElement (in category 'tests') -----
- test10CategoryOfElement
- 	editor := OrganizationEditor for: (ClassEditor on: self class).
- 	self assert: (editor categoryOfElement: #test10CategoryOfElement) = #tests.!

Item was removed:
- ----- Method: ClassExporterTest>>setUp (in category 'running') -----
- setUp
- 	super setUp.
- 	exporter := ClassExporter on: Smalltalk.
- !

Item was removed:
- ----- Method: ClassEditorProtocolTest>>test41HasComment (in category 'tests') -----
- test41HasComment
- 
- 	self deny: editor hasComment!

Item was removed:
- ----- Method: InstanceMigratorTest>>testTwoClassTransaction (in category 'tests') -----
- testTwoClassTransaction
- 	| mutator classes inst1 inst2 |
- 	mutator := MigrationTransaction new.
- 
- 	classes := self createClassPair.
- 	inst1 := classes key new.
- 	mutator addMigrator: (InstanceMigrator from: classes key to: classes value).
- 
- 	classes := self createClassPair.
- 	inst2 := classes key new.
- 	mutator addMigrator: (InstanceMigrator from: classes key to: classes value).
- 
- 	mutator commit.
- 	self assert: inst1 isInstanceOfNewClass.
- 	self assert: inst2 isInstanceOfNewClass!

Item was removed:
- ----- 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 removed:
- ----- Method: OrganizationEditorTest>>assertRemoteString:inRepository:matches: (in category 'asserting') -----
- assertRemoteString: remote inRepository: repository matches: aString
- 	self assert: remote sourceFileNumber = 2.
- 	repository changesStream position: remote position.
- 	self assert: (repository changesStream next: aString size) = aString.
- 	repository changesStream next = $!!!

Item was removed:
- ----- Method: ClassFormat class>>indexedSpec (in category 'storage specifications') -----
- indexedSpec
- 	^ 2!

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

Item was removed:
- ----- Method: SystemEditor>>edRemove: (in category 'building') -----
- edRemove: aSymbol
- 	| object |
- 	object := subject at: aSymbol ifAbsent: [^ self].
- 	object isBehavior
- 		ifTrue: [object removeFromSystem]
- 		ifFalse: [subject removeKey: aSymbol]!

Item was removed:
- ----- Method: ClassEditorOntologyTest>>test09Organization (in category 'tests') -----
- test09Organization
- 
- 	self assert: editor organization subject == editor subject organization!

Item was removed:
- ----- Method: SystemEditorCommitTest>>setUp (in category 'running') -----
- setUp
- 	super setUp.
- 	editor := SystemEditor new.
- !

Item was removed:
- ----- Method: ClassEditor>>addClassVarName: (in category 'editing') -----
- addClassVarName: aSymbol
- 	classVarNames ifNil: [classVarNames := subject classVarNames].
- 	classVarNames := classVarNames copyWith: aSymbol asSymbol!

Item was removed:
- ----- 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 removed:
- ----- Method: MetaclassEditor>>new (in category 'initialization') -----
- new
- "Answers a new ClassEditor with myself as its class"
- 	^ editor := self basicNew!

Item was removed:
- ----- Method: ClassEditor>>rename: (in category 'editing') -----
- rename: aString
- 	| oldName newName |
- 	(newName := aString asSymbol) = (oldName := self name)
- 		ifTrue: [^ self].
- 	(self system includesKey: newName)
- 		ifTrue: [^ self error: newName , ' already exists'].
- 	self setName: newName.
- 	self category: self category. "set explicitly to trigger reCategorize"
- 	self system renameClass: self from: oldName!

Item was removed:
- ----- Method: ClassExporter>>setEnvironment: (in category 'initialize-release') -----
- setEnvironment: anEnvironment 
- 	environment := anEnvironment.
- 	classes := OrderedCollection new.
- 	oldClasses := OrderedCollection new.
- 	newClasses := OrderedCollection new.!

Item was removed:
- ----- Method: CategorizerEditor>>edBuild (in category 'building') -----
- edBuild
- 	| result processed newCat |
- 	result := self productClass defaultList: Array new.
- 	categories ifNotEmpty: [result categories: categories].
- 	self changedElementsAndCategoriesDo: [:ea :cat |
- 		result classify: ea under: cat].
- 	self subject ifNil: [^ result].
- 	processed := IdentitySet new 
- 		addAll: result elementArray;
- 		addAll: self removedElements;
- 		yourself.
- 	self subject categories do: [:oldCat |
- 		newCat := self newCategoryFor: oldCat.
- 		(subject listAtCategoryNamed: oldCat) do: [:ea |
- 			(processed includes: ea) ifFalse: [
- 				result classify: ea under: newCat]]].
- 	^ result!

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

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

Item was removed:
- ----- Method: ClassDescriptionEditor>>edInvalidateSuperclass (in category 'building') -----
- edInvalidateSuperclass
- "Note that I require a rebuild due to a superclass change"
- 	self superclass: self superclass!

Item was removed:
- ----- Method: ClassFormat>>validate (in category 'validating') -----
- validate
- "Raise  an error if I am an invalid format"
- 
- 	instSize > 254 ifTrue: [self error: 'Too many instance variables (', instSize printString,')'].
- 	(self isBits and: [instSize > 0]) ifTrue: [self error: 'Only pointer formats can have named variables'].
- 	!

Item was removed:
- ----- Method: ClassEditor>>subclassesDo: (in category 'reflecting') -----
- subclassesDo: aBlock
- 	^ system edSubclassesOf: self do: aBlock!

Item was removed:
- ----- Method: SystemEditor>>edSubclassesOrEditorsOf: (in category 'building') -----
- edSubclassesOrEditorsOf: anEditor
- "Answer all subclasses of the given ClassEditor, as either an editor (if it has changed), or as a class (if it has not changed). Does not add any items to my additions list"
- 
- 	| subclasses subeditors |
- 	subclasses := anEditor subject
- 		ifNil: [Set new]
- 		ifNotNilDo: [ :class | class subclasses asSet].
- 	subeditors := additions select: [ :ea |
- 		subclasses remove: ea subject ifAbsent: [].
- 		ea edIsBehavior and: [ea superclassOrEditor == anEditor]].
- 	removals do: [ :removedKey | subclasses remove: (subject at: removedKey) ifAbsent: []].
- 	^ subclasses asArray, subeditors asArray!

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

Item was removed:
- ----- Method: ClassEditorOntologyTest>>test11MetaOrganization (in category 'tests') -----
- test11MetaOrganization
- 
- 	self assert: editor class organization subject == editor class subject organization!

Item was removed:
- ----- Method: ClassEditorProtocolTest>>test14AddAndRemoveSelector (in category 'tests') -----
- test14AddAndRemoveSelector
- 	editor 
- 		compile: 'zayin ^ 1'
- 		classified: 'numbers'
- 		withStamp: 'cwp 5/30/2004 09:27'
- 		notifying: nil
- 		logSource: true.
- 	editor removeSelector: #zayin.
- 	self deny: (editor includesSelector: #zayin).
- 	!

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

Item was removed:
- ----- Method: RootMetaclassEditor>>bindingOf: (in category 'reflecting') -----
- bindingOf: varName
- 	^ nil!

Item was removed:
- ----- Method: SystemEditorTest>>test14AtIfAbsentDoesntWrapPools (in category 'tests') -----
- test14AtIfAbsentDoesntWrapPools
- 	self assert: (editor at: #Undeclared ifAbsent: [0]) == Undeclared!

Item was removed:
- ----- Method: CategorizerEditor>>hasChangedElements (in category 'accessing changed elements') -----
- hasChangedElements
- 	self changedElementsAndCategoriesDo: [:element :category | ^ true].
- 	^ false!

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

Item was removed:
- ----- Method: SystemEditorCommitTest>>test01MigratesInstances (in category 'tests') -----
- test01MigratesInstances
- 	| inst classEditor class |
- 	class := editor subject at: #EditorSubjectSub.
- 	inst := class new.
- 	classEditor := editor at: #EditorSubjectSub.
- 	classEditor addInstVarName: 'gamma'.
- 	editor commit.
- 	self assert: (inst class instVarNames includes: 'gamma')!

Item was removed:
- ----- Method: ClassExporterTest>>test04ClassKnowsItsEnvironment (in category 'tests') -----
- test04ClassKnowsItsEnvironment
- 	| class |
- 	class := self createClass.
- 	exporter addClass: class.
- 	exporter commit.
- 	self assert: class environment == exporter environment
- 	!

Item was removed:
- ----- Method: InstanceMigratorTest>>createClassPair (in category 'support') -----
- createClassPair
- 	| editor oldClass newClass |
- 	editor := ClassEditor on: EditorSubject.
- 	editor compile: 'isInstanceOfNewClass ^ false' classified: 'testing'.
- 	oldClass := editor edBuild.
- 	editor compile: 'isInstanceOfNewClass ^ true' classified: 'testing'.
- 	newClass := editor edBuild.
- 	^ oldClass -> newClass!

Item was removed:
- ----- Method: ClassEditorValidationTest>>test10InstVarNamedFalse (in category 'tests') -----
- test10InstVarNamedFalse
- 
- 	editor addInstVarName: 'false'.
- 	self should: [editor validate] raise: IllegalVariableName.!

Item was removed:
- ----- Method: OrganizationEditor>>edRequiresBuild (in category 'building') -----
- edRequiresBuild
- 	^ isDirty or: [super edRequiresBuild]!

Item was removed:
- ----- Method: ClassEditorValidationTest>>test09InstVarNamedTrue (in category 'tests') -----
- test09InstVarNamedTrue
- 
- 	editor addInstVarName: 'true'.
- 	self should: [editor validate] raise: IllegalVariableName.!

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

Item was removed:
- ----- Method: EditorSubject class>>aleph (in category 'accessing class vars') -----
- aleph
- 	^ Aleph !

Item was removed:
- ----- Method: ClassEditorOntologyTest>>test04IsKindOfClass (in category 'tests') -----
- test04IsKindOfClass
- 	"A class and its editor are polymorphic, but this kind of
- 	explicit test can tell the difference."
- 
- 	self deny: (editor class isKindOf: Class)!

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

Item was removed:
- ----- Method: MetaclassEditorBuildTest>>test02AddInstVar (in category 'tests') -----
- test02AddInstVar
- 	
- 	| result |
- 	editor addInstVarName: 'gamma'.
- 	result := editor edBuild.
- 	self deny: result == editor subject.
- 	self assert: result instVarNames = editor instVarNames.
- 	self assert: result format = editor format.
- !

Item was removed:
- ----- Method: SystemEditor>>edPrepareMigration: (in category 'building') -----
- edPrepareMigration: txn
- 
- 	showProgress
- 		ifFalse:	[additions do: [:ea | ea edPrepareMigration: txn]]
- 		ifTrue:	[additions do: [:ea | ea edPrepareMigration: txn] displayingProgress: 'Preparing Transaction...']!

Item was removed:
- ----- Method: ClassEditorProtocolTest>>test04ClassVarNames (in category 'tests') -----
- test04ClassVarNames
- 	self assert: editor classVarNames = editor subject classVarNames!

Item was removed:
- ----- Method: MethodDictionaryEditor>>add: (in category 'editing') -----
- add: aModifiedMethod
- 	classEditor edInvalidateOrganization.
- 	^ additions at: aModifiedMethod selector put: aModifiedMethod!

Item was removed:
- ----- Method: ClassFormat class>>named (in category 'instance creation') -----
- named
- 	^ self named: 0!

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

Item was removed:
- ----- Method: ClassFormatTest>>testIndexed (in category 'tests') -----
- testIndexed
- 	| format |
- 	format := ClassFormat indexed.
- 	self assert: format instSize = 0.
- 	self assert: format isPointers.
- 	self assert: format isWords.
- 	self assert: format isVariable.
- 	self deny: format isFixed.
- 	self deny: format isBits.
- 	self deny: format isBytes.
- 	self deny: format isWeak
- !

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

Item was removed:
- ----- Method: ClassEditorProtocolTest>>test12AddSelector (in category 'tests') -----
- test12AddSelector
- 	self deny: (editor includesSelector: #zayin).
- 	editor 
- 		compile: 'zayin ^ 1'
- 		classified: 'numbers'
- 		withStamp: 'cwp 5/30/2004 09:27'
- 		notifying: nil
- 		logSource: true.
- 	self assert: (editor includesSelector: #zayin)!

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

Item was removed:
- ----- Method: ClassFormatTest>>testIndexedSubclass (in category 'tests') -----
- testIndexedSubclass
- 	| superFormat subFormat |
- 	superFormat := ClassFormat named: 3.
- 	subFormat := superFormat indexedSubclass: 2.
- 	self assert: superFormat instSize = 3.
- 	self assert: subFormat instSize = 5.
- 	self assert: subFormat isVariable.
- 	self assert: subFormat isPointers.
- 	self assert: subFormat isWords.
- 	self deny: subFormat isFixed.
- 	self deny: subFormat isBits.
- 	self deny: subFormat isBytes.
- 	self deny: subFormat isWeak!

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

Item was removed:
- ----- Method: MethodDictionaryEditor>>selectorIsModified: (in category 'testing') -----
- selectorIsModified: aSelector
- 	^ (additions includesKey: aSelector) or: [removals includes: aSelector]!

Item was removed:
- ----- Method: TestCategoryEditor>>changesRemoveElement: (in category 'accessing') -----
- changesRemoveElement: element
- 	changes removeElement: element!

Item was removed:
- ----- Method: ClassFormatTest>>testNamedSubclass (in category 'tests') -----
- testNamedSubclass
- 	| superFormat subFormat |
- 	superFormat := ClassFormat named: 3.
- 	subFormat := superFormat namedSubclass: 2.
- 	self assert: superFormat instSize = 3.
- 	self assert: subFormat instSize = 5.
- 	self assert: subFormat isFixed.
- 	self assert: subFormat isPointers.
- 	self assert: subFormat isWords.
- 	self deny: subFormat isVariable.
- 	self deny: subFormat isBits.
- 	self deny: subFormat isBytes.
- 	self deny: subFormat isWeak!

Item was removed:
- ----- Method: ClassEditor>>on:for: (in category 'initialize-release') -----
- on: aClass for: aSystemEditor
- 	^ self setSubject: aClass system: aSystemEditor!

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

Item was removed:
- ----- Method: MethodDictionaryEditor>>subject (in category 'accessing') -----
- subject
- 	^ subject ifNil: [classEditor subject 
- 		ifNil: [subject := MethodDictionary new]
- 		ifNotNilDo: [:aClass | subject := aClass methodDictionary]]!

Item was removed:
- ----- Method: MetaclassEditorBuildTest>>test01NoChange (in category 'tests') -----
- test01NoChange
- 	"We always rebuild the metaclass, since the class needs to be an instance of it."
- 
- 	self deny: editor edBuild == editor subject.
- 	self deny: editor edRequiresRecompile!

Item was removed:
- ----- Method: ClassExporterTest>>test03ExistingReferencesAreMaintained (in category 'tests') -----
- test03ExistingReferencesAreMaintained
- 	| class reference |
- 	reference := Smalltalk at: #EditorSubjectSub.
- 	class := self createClassNamed: #EditorSubjectSub.
- 	exporter addClass: class.
- 	exporter commit.
- 	self assert: (Smalltalk at: #EditorSubjectSub) == reference.!

Item was removed:
- ----- Method: SystemEditorCommitTest>>test02CategorizesClasses (in category 'tests') -----
- test02CategorizesClasses
- 	| classEditor |
- 	classEditor := editor at: #EditorSubjectSub.
- 	classEditor category: #'SystemEditor-Info'.
- 	editor commit.
- 	self assert: (SystemOrganization categoryOfElement: #EditorSubjectSub) == #'SystemEditor-Info'!

Item was removed:
- ----- Method: OrganizationEditorTest>>test08NilCommentDoesntWriteToChangesFile (in category 'tests') -----
- test08NilCommentDoesntWriteToChangesFile
- 	| repository result |
- 	repository := SourceRepository newInternal.
- 	editor := OrganizationEditor for: (ClassEditor on: self class)
- 				repository: repository.
- 	editor classComment: nil stamp: nil.
- 	result := editor edBuild.
- 	self assert: result commentRemoteStr isNil.
- 	self assert: repository changesStream size = 3!

Item was removed:
- ----- Method: ClassEditorBuildTest>>test02AddInstVar (in category 'tests') -----
- test02AddInstVar
- 	
- 	| result |
- 	editor addInstVarName: 'gamma'.
- 	result := editor product.
- 	self deny: result == editor subject.
- 	self assert: result name = editor subject name.
- 	self assert: result instVarNames = editor instVarNames.
- 	self assert: result format = editor format.
- !

Item was removed:
- ----- Method: CategorizerEditor>>edRequiresBuild (in category 'building') -----
- edRequiresBuild
- 	^ self hasChangedElements or: [self removedElements notEmpty]!

Item was removed:
- ----- Method: ClassEditor>>comment (in category 'reflecting') -----
- comment
- 	| comment |
- 	comment := self organization classComment.
- 	^ comment isEmpty
- 		ifFalse: [comment]
- 		ifTrue: [self classCommentBlank]!

Item was removed:
- ----- Method: SourceRepositoryTest>>test02StoreCommentForClassStamped (in category 'tests') -----
- test02StoreCommentForClassStamped
- 	| remote |
- 	remote := repository 
- 		storeComment: 'This is a comment.'
- 		forClass: self class
- 		stamped: 'cwp 12/11/2005 21:58'.
- 
- 	self assert: repository changesStream contents = 'xxx
- !!SourceRepositoryTest commentStamp: ''cwp 12/11/2005 21:58'' prior: 0!!
- This is a comment.!!'.
- 
- 	self assert: remote sourceFileNumber = 2.
- 	self assert: remote position = 73!

Item was removed:
- ----- Method: ClassEditor>>ensureClassVarName: (in category 'editing') -----
- ensureClassVarName: aString 
- 	(self allClassVarNames includes: aString)
- 		ifFalse: [ self addClassVarName: aString].
- 		 !

Item was removed:
- ----- Method: EditorSubjectSubTest>>createClassNamed: (in category 'support') -----
- createClassNamed: aSymbol 
- 	| classEditor |
- 	classEditor := (ClassEditor on: EditorSubject) 
- 				subclass: aSymbol
- 				instanceVariableNames: 'gamma'
- 				classVariableNames: ''
- 				poolDictionaries: ''
- 				category: 'SystemEditor-Tests'.
- 	^classEditor product!

Item was removed:
- ----- Method: ClassExporterTest>>test05NewClassReplacesOld (in category 'tests') -----
- test05NewClassReplacesOld
- 	| class |
- 	class := self createClassNamed: #EditorSubjectSub.
- 	exporter addClass: class.
- 	exporter commit.
- 	self assert: ((Smalltalk at: #EditorSubjectSub) instVarNames includes: 'gamma')!

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

Item was removed:
- ----- Method: SystemEditor>>bindingOf: (in category 'reflecting') -----
- bindingOf: aSymbol
-  
- 	^ self associationAt: aSymbol ifAbsent: [ self error: 'could  not bind ', aSymbol ]!

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

Item was removed:
- ----- Method: SystemEditor>>editors (in category 'accessing') -----
- editors
- 	^ additions!

Item was removed:
- DictionaryEditor subclass: #SystemEditor
- 	instanceVariableNames: 'organization showProgress debug'
- 	classVariableNames: ''
- 	poolDictionaries: ''
- 	category: 'SystemEditor-Squeak'!

Item was removed:
- ----- Method: ClassEditor>>new (in category 'reflecting') -----
- new
- "Create an instance of myself. This instance is only intended for compiling DoIts that will evaluate in my scope. See SystemEditor >> doItHost"
- 
- 	superclass := self subject ifNil: [UndefinedObject].
- 	methodDict := MethodDictionary new.
- 	format := superclass format.
- 	^ self basicNew!

Item was removed:
- ----- Method: ClassEditorBuildTest>>test01NoChange (in category 'tests') -----
- test01NoChange
- 	"Since there was no change, we don't have to rebuild the class at all."
- 
- 	| migration |
- 	migration := MigrationTransaction new.
- 	editor edPrepareMigration: migration.
- 	self assert: migration isEmpty!

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

Item was removed:
- ----- Method: OrganizationEditor>>changedElementsAndCategoriesDo: (in category 'accessing') -----
- changedElementsAndCategoriesDo: aBlock
- 	classEditor methods additions keysAndValuesDo: [:key :editor |
- 		aBlock value: key value: editor category]!

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

Item was removed:
- ----- Method: CategorizerEditor>>changesInCategory: (in category 'accessing changed elements') -----
- changesInCategory: category
- "Answers a list of new or recategorized elements in category"
- 
- 	^ self changedElementsAndCategoriesSelect:
- 			[:anElement :aCategory | category = aCategory]
- 		thenCollect: [:anElement :aCategory | anElement]!

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

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

Item was removed:
- ----- Method: MetaclassEditor>>bindingOf: (in category 'reflecting') -----
- bindingOf: varName
- 	^ editor bindingOf: varName!

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

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

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

Item was removed:
- ----- Method: SystemEditor>>hasBindingThatBeginsWith: (in category 'reflecting') -----
- hasBindingThatBeginsWith: aString
- 	"Answer true if the receiver has a key that begins with aString, false otherwise"
- 	
- 	additions keysDo:[:each | 
- 		((each beginsWith: aString)
- 			and: [(removals includes: each) not]) ifTrue:[^true]].
- 	subject keysDo:[:each | 
- 		((each beginsWith: aString)
- 			and: [(removals includes: each) not]) ifTrue:[^true]].
- 	^false!

Item was removed:
- ----- Method: SystemEditor class>>on: (in category 'instance creation') -----
- on: anEnvironment
- 	^ self basicNew setSubject: anEnvironment!

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

Item was removed:
- ----- 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 removed:
- ----- Method: OrganizationEditorTest>>basicFileStream (in category 'remote string') -----
- basicFileStream
- 	^ stream := WriteStream on: (String new: 20)!

Item was removed:
- ----- Method: OrganizationEditor>>productClass (in category 'building') -----
- productClass
- 	^ ClassOrganizer!

Item was removed:
- ----- Method: ClassEditorValidationTest>>test12InstVarDefinedInSuperclass (in category 'tests') -----
- test12InstVarDefinedInSuperclass
- 
- 	| subeditor |
- 	subeditor := editor
- 				subclass: #EditorSubjectSub
- 				instanceVariableNames: 'alpha'
- 				classVariableNames: ''
- 				poolDictionaries: ''
- 				category: 'Testing'.
- 	self should: [subeditor validate] raise: IllegalVariableName.!

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

Item was removed:
- ----- Method: SystemEditorTest>>test08DoesntRebuildSubclassesUnnecessarily (in category 'tests') -----
- test08DoesntRebuildSubclassesUnnecessarily
- 	| superclass |
- 	superclass := editor at: #ClassEditorTest.
- 	superclass compile: 'het ^ #one' classified: 'testing'.
- 	self denyClassesAreMigrated: ClassEditorTest subclasses.!

Item was removed:
- ----- Method: ClassDescriptionEditor>>edRequiresRecompile (in category 'building') -----
- edRequiresRecompile
- 	instVarNames ifNotNil: [^ true].
- 	self decoratorsDo: [:ea | ea edRequiresRecompile ifTrue: [^ true]].
- 	^ false!

Item was removed:
- ----- Method: ClassEditorBuildTest>>test16CommentNotChanged (in category 'tests') -----
- test16CommentNotChanged
- 	
- 	| migration |
- 	editor comment.
- 
- 	migration := MigrationTransaction new.
- 	editor edPrepareMigration: migration.
- 	self assert: migration migrators isEmpty.!

Item was removed:
- ----- Method: ClassEditorTest>>setUp (in category 'running') -----
- setUp
- 	editor := ClassEditor on: EditorSubject!

Item was removed:
- ----- Method: MetaclassEditor>>sharedPools (in category 'debugging') -----
- sharedPools
- 
- 	^ superclass sharedPools!

Item was removed:
- ----- Method: EditorSubject class>>ayin (in category 'methods for editing') -----
- ayin
- 	^ 22!

Item was removed:
- ----- Method: MethodEditor>>category (in category 'accessing') -----
- category
- 	^ category!

Item was removed:
- ----- Method: ClassEditorTest class>>isAbstract (in category 'testing') -----
- isAbstract
- 	^ self name == #ClassEditorTest!

Item was removed:
- ----- Method: MetaclassEditor>>subject (in category 'accessing') -----
- subject
- 	subject ifNotNil: [^ subject].
- 	editor subject ifNil: [^ nil].
- 	^ subject := editor subject class!

Item was removed:
- ----- Method: OrganizationEditorTest>>test06BuildCopiesCategories (in category 'tests') -----
- test06BuildCopiesCategories
- 	| actual expected |
- 	editor := OrganizationEditor for: (ClassEditor on: self class).
- 	actual := editor edBuild.
- 	expected := self class organization.
- 	self deny: actual == expected.
- 	self assert: actual printString = expected printString!

Item was removed:
- ----- Method: ClassEditorProtocolTest>>test15RemoveNewSelector (in category 'tests') -----
- test15RemoveNewSelector
- 	editor removeSelector: #zayin.
- 	self deny: (editor includesSelector: #zayin)!

Item was removed:
- ----- Method: MetaclassEditorProtocolTest>>test09CompiledMethodAt (in category 'tests') -----
- test09CompiledMethodAt
- 	"Compiled methods are immutable, so we don't wrap them for editing."
- 
- 	self assert: (editor compiledMethodAt: #ayin) == (editor subject compiledMethodAt: #ayin)!

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

Item was removed:
- ----- Method: SystemEditor>>edRecategorize (in category 'building') -----
- edRecategorize
- 	additions do: 
- 		[:ea | 
- 		ea edCategory ifNotNilDo:
- 			[:cat | 
- 			SystemOrganization 
- 				classify: ea name
- 				under: cat]]!

Item was removed:
- ----- Method: ClassEditorProtocolTest>>test06RemoveClassVarName (in category 'tests') -----
- test06RemoveClassVarName
- 	editor removeClassVarName: 'Beth'.
- 	self assert: editor classVarNames = (editor subject classVarNames copyWithout: 'Beth')!

Item was removed:
- ----- Method: SystemEditorTest>>setUp (in category 'running') -----
- setUp
- 	editor := SystemEditor new.
- !

Item was removed:
- ----- Method: CategorizerEditor>>changedElementsAndCategoriesDo: (in category 'accessing changed elements') -----
- changedElementsAndCategoriesDo: aBlock
- "Evaluates aBlock for each added or recategorized elements, and its category"
- 
- 	self subclassResponsibility!

Item was removed:
- ----- Method: SourceRepository>>storeMethod:forClass:category:stamped:replacing: (in category 'creation') -----
- storeMethod: sourceString forClass: aClass category: catString 
- stamped: stampString replacing: aRemoteString
- 	^ self
- 		storeMethod: sourceString 
- 		forClass: aClass 
- 		category: catString 
- 		stamped: stampString
- 		prior: aRemoteString sourcePointer.!

Item was removed:
- ----- Method: ClassDescriptionEditor>>allSuperclassesDo: (in category 'reflecting') -----
- allSuperclassesDo: aBlock 
- "Evaluate aBlock for each of my receiver superclasses."
- 
- 	self superclass withAllSuperclassesDo: aBlock!

Item was removed:
- AbstractEditor subclass: #CategorizerEditor
- 	instanceVariableNames: 'subject renamedCategories categories'
- 	classVariableNames: ''
- 	poolDictionaries: ''
- 	category: 'SystemEditor-Squeak'!
- 
- !CategorizerEditor commentStamp: '<historical>' prior: 0!
- An abstract superclass for editors of Categorizers. Implements the public interface of a Categorizer. I maintain the list of added, removed, or reordered categories, but it is up to subclasses to remember which elements were added, removed, or recategorized.
- 
- subject (Categorizer) - The Categorizer I am editing
- categories (OrderedCollection) - The ordered list of categories
- renamedCategories (Dictionary) - A dictionary mapping old category names to new names!

Item was removed:
- ----- Method: PureBehaviorEditor>>edPrepareMigration: (in category 'building') -----
- edPrepareMigration: txn
- 	self subject ifNil: [^ self].
- 	self decoratorsDo: [:ea | ea edPrepareMigration: txn].
- 	methods ifNotNil: [methods edPrepareMigration: txn for: self].
- 	organization ifNotNil: [organization edPrepareMigration: txn].
- !

Item was removed:
- ----- Method: ClassFormatTest>>testWeak (in category 'tests') -----
- testWeak
- 	| format |
- 	format := ClassFormat weak.
- 	self assert: format instSize = 0.
- 	self assert: format isVariable.
- 	self assert: format isPointers.
- 	self assert: format isWords.
- 	self assert: format isWeak.
- 	self deny: format isFixed.
- 	self deny: format isBits.
- 	self deny: format isBytes.
- !

Item was removed:
- ----- Method: ClassEditor>>subclasses (in category 'reflecting') -----
- subclasses
- 	^ system edSubclassesOf: self!

Item was removed:
- ----- Method: ClassFormat>>isWords (in category 'testing') -----
- isWords
- 	"Answer whether the receiver has 32-bit instance variables."
- 
- 	^ self isBytes not!

Item was removed:
- ----- Method: ClassEditor>>edName:superclassEditor:type:instVarString:classVarString:poolImports:category: (in category 'building') -----
- edName: aSymbol superclassEditor: anEditor type: typeOfClass instVarString: instString classVarString: classString poolImports: poolString category: catString 
- 	| scanner |
- 	scanner := Scanner new.
- 	name := aSymbol.
- 	self superclass: anEditor.
- 	type := typeOfClass.
- 	category := catString.
- 	instVarNames := scanner scanFieldNames: instString.
- 	classVarNames := scanner scanFieldNames: classString.
- 	sharedPools := (scanner scanFieldNames: poolString) 
- 				collect: [:ea | system edResolve: ea asSymbol]!

Item was removed:
- ----- Method: PureBehaviorEditor>>realClass (in category 'accessing') -----
- realClass
- "Since the metaobject protocol gets pretty messed up in some of my subclasses, answer what class this really is an instance of"
- 
- 	^ self class!

Item was removed:
- ----- Method: ClassEditorBuildTest>>test03Superclass (in category 'tests') -----
- test03Superclass
- 	
- 	| result |
- 	editor superclass: self class.
- 	result := editor product.
- 	self deny: result == editor subject.
- 	self assert: result superclass == self class.!

Item was removed:
- ----- Method: SourceRepository>>sourcesStream (in category 'accessing') -----
- sourcesStream
- 	^ files at: self sourcesIndex!

Item was removed:
- ----- Method: CategoryEditorTest>>setUp (in category 'as yet unclassified') -----
- setUp
- 	super setUp.
- 	categorizer := TestCategoryEditor on: categorizer!

Item was removed:
- ----- Method: CategorizerEditor>>productClass (in category 'building') -----
- productClass
- 	^ Categorizer!

Item was removed:
- ----- Method: MethodDictionaryEditor>>at: (in category 'reflecting') -----
- at: aSymbol
- 	^ self at: aSymbol ifAbsent: [self error: 'Method not found']!

Item was removed:
- ----- Method: SourceRepository class>>newInternal (in category 'instance creation') -----
- newInternal
- 	^ self forSourceFiles: (Array 
- 							with: self createFakeFileStream
- 							with: self createFakeFileStream).!

Item was removed:
- ----- Method: ClassFormat>>instSize (in category 'accessing') -----
- instSize
- 	^ instSize!

Item was removed:
- ----- Method: SystemEditor>>classNamed: (in category 'reflecting') -----
- classNamed: className 
- 	"className is either a class name or a class name followed by '
- 	class'. Answer the class or metaclass it names"
- 	| meta baseName baseClass |
- 	(className endsWith: ' class')
- 		ifTrue: [meta := true.
- 			baseName := className copyFrom: 1 to: className size - 6]
- 		ifFalse: [meta := false.
- 			baseName := className].
- 	baseClass := self
- 				at: baseName asSymbol
- 				ifAbsent: [^ nil].
- 	meta
- 		ifTrue: [^ baseClass class]
- 		ifFalse: [^ baseClass]!

Item was removed:
- ----- Method: ClassEditor class>>rearrangeVarNames:oldNames: (in category 'util') -----
- rearrangeVarNames: associations oldNames: oldVars
- 	"Rearrange vars. The associations are name -> pos and cover the subset
- 	of vars that should be moved. The old ones just fill in the holes."
- 
- 	| newVars |
- 	newVars := Array new: oldVars size.
- 	associations do: [:assoc |
- 		newVars at: assoc value put: assoc key].
- 	oldVars do: [:oldVar |
- 		(newVars includes: oldVar) ifFalse: [
- 			newVars at: (newVars indexOf: nil) put: oldVar]].
- 	^newVars!

Item was removed:
- ----- Method: MetaclassEditorBuildTest>>test06MethodAdded (in category 'tests') -----
- test06MethodAdded
- 	
- 	| dict |
- 	editor 
- 		compile: 'pe ^ -2'
- 		classified: 'letters'
- 		withStamp: 'cwp 5/30/2004 09:27'
- 		notifying: nil
- 		logSource: true.
- 	dict := editor methodDictionary.
- 	self assert: (dict at: #pe) isCompiledMethod.
- !

Item was removed:
- ----- Method: SystemEditorTest>>test10ValidatesBeforeCommitting (in category 'tests') -----
- test10ValidatesBeforeCommitting
- 	| classEditor |
- 	classEditor := editor at: #EditorSubject.
- 	classEditor typeOfClass: #bytes.
- 	classEditor addInstVarName: 'test'.
- 	self 
- 		should: [editor commit]
- 		raise: InvalidClassFormat!

Item was removed:
- ----- Method: TestCategoryEditor>>changesInCategory: (in category 'accessing') -----
- changesInCategory: category
- 	^ changes listAtCategoryNamed: category!

Item was removed:
- ----- Method: CategorizerEditor>>classifyAll:under: (in category 'reflecting - accessing') -----
- classifyAll: aCollection under: heading
- 
- 	aCollection do:
- 		[:element | self classify: element under: heading]!

Item was removed:
- ----- Method: ClassEditorProtocolTest>>test26CompileClassified (in category 'tests') -----
- test26CompileClassified
- 	self deny: (editor includesSelector: #zayin).
- 	editor 
- 		compile: 'zayin ^ 1'
- 		classified: 'numbers'.
- 	self assert: (editor includesSelector: #zayin)!

Item was removed:
- ----- Method: ClassEditor>>removeFromSystem (in category 'editing') -----
- removeFromSystem
- 	system edRemoveClassNamed: self name!

Item was removed:
- ----- Method: SystemEditor>>edClassAt:ifAbsent: (in category 'building') -----
- edClassAt: aSymbol ifAbsent: aBlock
- 	^ subject at: aSymbol ifAbsent: aBlock!

Item was removed:
- ----- Method: ClassEditorProtocolTest>>test16TypeOfClass (in category 'tests') -----
- test16TypeOfClass
- 	editor typeOfClass = #normal!

Item was removed:
- ----- Method: ClassExporterTest>>test02ClassIsAddedToSuperclass (in category 'tests') -----
- test02ClassIsAddedToSuperclass
- 	| class |
- 	class := self createClass.
- 	exporter addClass: class.
- 	exporter commit.
- 	self assert: (class superclass subclasses includes: class)
- 	!

Item was removed:
- ----- Method: OrganizationEditorTest>>test02ClassComment (in category 'tests') -----
- test02ClassComment
- 	editor := OrganizationEditor for: (ClassEditor on: self class).
- 	self assert: editor classComment asString = 'This comment must be present for the tests to pass.'!

Item was removed:
- ----- Method: CategorizerEditor>>removeCategory: (in category 'reflecting - accessing') -----
- removeCategory: catString
- 	| category |
- 	category := catString asSymbol.
- 	(self categories includes: category) ifFalse: [^ self].
- 	(self listAtCategoryNamed: category)
- 		ifNotEmpty: [^self error: 'cannot remove non-empty category'].
- 	categories remove: category ifAbsent: [].
- 	renamedCategories keysAndValuesRemove: [:key :value | value == category].
- !

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

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

Item was removed:
- ----- Method: MethodEditor>>logCompilationFrom:for: (in category 'building') -----
- logCompilationFrom: aCompiledMethod for: aClassEditor
- 	^ aCompiledMethod
- 		ifNil: [self repository 
- 				storeMethod: source
- 				forClass: aClassEditor
- 				category: category
- 				stamped: stamp]
- 		ifNotNil: [self repository
- 					storeMethod: source
- 					forClass: aClassEditor
- 					category: category
- 					stamped: stamp
- 					replacing: aCompiledMethod]!

Item was removed:
- ----- Method: ClassEditorOntologyTest>>test03ClassReferences (in category 'tests') -----
- test03ClassReferences
- 
- 	"The instance is a strange beast. Its class is created on the fly, and is
- 	both an instance of MetaclassEditor and a subclass of ClassEditor. 
- 	See #testCreation." 
- 	self assert: editor class class == MetaclassEditor.
- 	self assert: (editor class instVarNamed: 'superclass') == ClassEditor.
- 
- 
- 	"editor is an instance of a light-weight class, so we don't register it
- 	with its superclass. In fact, the only thing that keeps it from being
- 	garbage collected is the class pointer from editor."
- 	self deny: (ClassEditor subclasses includes: editor class).
- 
- !

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

Item was removed:
- ----- Method: ClassEditorProtocolTest>>test09RemoveSharedPool (in category 'tests') -----
- test09RemoveSharedPool
- 	editor removeSharedPool: EditorSubjectPool.
- 	self assert: editor sharedPools = (editor subject sharedPools copyWithout: EditorSubjectPool)!

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

Item was removed:
- ----- Method: ClassEditorValidationTest>>test11InstVarNamedNil (in category 'tests') -----
- test11InstVarNamedNil
- 
- 	editor addInstVarName: 'nil'.
- 	self should: [editor validate] raise: IllegalVariableName.!

Item was removed:
- ----- Method: ClassFormat>>isBytes (in category 'testing') -----
- isBytes
- 	"Answer whether the receiver has 8-bit instance variables."
- 
- 	^ self instSpec >= 8!

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

Item was removed:
- ----- Method: PureBehaviorEditor>>bindingOf: (in category 'reflecting') -----
- bindingOf: varName
- 	^ self environment bindingOf: varName!

Item was removed:
- ClassEditor subclass: #RootClassEditor
- 	instanceVariableNames: ''
- 	classVariableNames: ''
- 	poolDictionaries: ''
- 	category: 'SystemEditor-Squeak'!
- 
- !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 removed:
- ----- Method: ClassDescriptionEditor>>withAllSuperclassesDo: (in category 'reflecting') -----
- withAllSuperclassesDo: aBlock 
- "Evaluate aBlock for each of my receiver superclasses."
- 
- 	aBlock value: self.
- 	self allSuperclassesDo: aBlock!

Item was removed:
- ----- Method: ClassEditorProtocolTest>>test13RemoveSelector (in category 'tests') -----
- test13RemoveSelector
- 	editor removeSelector: #het.
- 	self deny: (editor includesSelector: #het)!

Item was removed:
- ----- Method: OrganizationEditorTest>>test01SubjectCanBeSpecified (in category 'tests') -----
- test01SubjectCanBeSpecified
- 	editor := OrganizationEditor for: (ClassEditor on: EditorSubject).
- 	self assert: editor subject == EditorSubject organization!

Item was removed:
- ----- Method: CategorizerEditor>>setSubject: (in category 'initialize-release') -----
- setSubject: aCategorizer
- 	subject := aCategorizer.
- 	renamedCategories := Dictionary new.
- 	categories := OrderedCollection new.!

Item was removed:
- ----- Method: ClassEditor>>hasComment (in category 'reflecting') -----
- hasComment
- 	| comment |
- 	comment := self organization classComment.
- 	^ comment notNil and: [comment isEmpty not]!

Item was removed:
- ----- Method: OrganizationEditorTest>>test03CommentStamp (in category 'tests') -----
- test03CommentStamp
- 	editor := OrganizationEditor for: (ClassEditor on: self class).
- 	self assert: editor commentStamp = OrganizationEditorTest organization commentStamp!

Item was removed:
- ----- Method: InstanceMigratorTest>>testOneClassTransaction (in category 'tests') -----
- testOneClassTransaction
- 	| mutator classes inst |
- 	classes := self createClassPair.
- 	inst := classes key new.
- 	mutator := MigrationTransaction new.
- 	mutator addMigrator: (InstanceMigrator from: classes key to: classes value).
- 	mutator commit.
- 	self assert: inst isInstanceOfNewClass!

Item was removed:
- ----- Method: ClassExporter>>addClass: (in category 'public') -----
- addClass: aClass
- 	classes add: aClass!

Item was removed:
- ----- Method: ClassFormat>>cClassIndex (in category 'accessing') -----
- cClassIndex
- 	^ cClassIndex!

Item was removed:
- ----- Method: MetaclassEditorProtocolTest>>test07RemoveSelector (in category 'tests') -----
- test07RemoveSelector
- 	editor removeSelector: #ayin.
- 	self deny: (editor includesSelector: #ayin)!

Item was removed:
- ClassDescriptionEditor subclass: #MetaclassEditor
- 	instanceVariableNames: 'editor'
- 	classVariableNames: ''
- 	poolDictionaries: ''
- 	category: 'SystemEditor-Squeak'!

Item was removed:
- ----- Method: SystemEditorTest>>test04ClassEditorsAreCached (in category 'tests') -----
- test04ClassEditorsAreCached
- 	| first second |
- 	first := editor at: #EditorSubject.
- 	second := editor at: #EditorSubject.
- 	self assert: first == second!

Item was removed:
- ----- Method: SourceRepository>>changesIndex (in category 'accessing') -----
- changesIndex
- 	^ 2!

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

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

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

Item was removed:
- ----- Method: SystemEditor>>at:ifPresent: (in category 'reflecting') -----
- at: key ifPresent: aBlock
- 	"Lookup the given key in the receiver. If it is present, answer the value of evaluating the given block with the value associated with the key. Otherwise, answer nil."
- 
- 	| v |
- 	v := self at: key ifAbsent: [^ nil].
- 	^ aBlock value: v
- !

Item was removed:
- ----- Method: ClassEditorBuildTest>>test05RemoveClassVar (in category 'tests') -----
- test05RemoveClassVar
- 	
- 	| result |
- 	editor removeClassVarName: 'Beth'.
- 	result := editor product.
- 	self deny: result == editor subject.
- 	self assert: result classVarNames = editor classVarNames.!

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

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

Item was removed:
- ----- Method: MetaclassEditor>>addSelectorSilently:withMethod: (in category 'debugging') -----
- addSelectorSilently: selector withMethod: compiledMethod
- "For running do-its against my ClassEditor"
- 
- 	^ superclass addSelectorSilently: selector withMethod: compiledMethod!

Item was removed:
- ----- Method: ClassEditor>>edSuperclassHasChanged (in category 'building') -----
- edSuperclassHasChanged
- 	^ superEditor ~~ nil!

Item was removed:
- ----- Method: ClassEditorOntologyTest>>test02Printing (in category 'tests') -----
- test02Printing
- 	"This makes debugging easier."
- 	
- 	self assert: editor printString = 'a ClassEditor on: EditorSubject'.
- 	self assert: editor class printString = 'a MetaclassEditor on: EditorSubject'.!

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

Item was removed:
- ----- Method: ClassFormat class>>size:type:index: (in category 'instance creation') -----
- size: instSize type: aSymbol index: cClassIndex
- 	^ self size: instSize spec: (self specFromType: aSymbol size: instSize) index: cClassIndex!

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

Item was removed:
- ----- Method: ClassFormat>>instSpec (in category 'accessing') -----
- instSpec
- 	^ instSpec!

Item was removed:
- ----- Method: SystemEditor>>edExpandEditors (in category 'building') -----
- edExpandEditors
- 	| queue editor remembered |
- 	remembered := IdentitySet new.
- 	queue := additions values asOrderedCollection.
- 	[queue isEmpty] whileFalse: [editor := queue removeFirst.
- 		(remembered includes: editor) ifFalse: [
- 			remembered add: editor.
- 			editor edDependentsDo: [:ea | queue add: ea]]]!

Item was removed:
- ----- Method: CategorizerEditor>>classify:under:suppressIfDefault: (in category 'reflecting - accessing') -----
- classify: element under: heading suppressIfDefault: aBoolean
- 	| category |
- 	((heading = Categorizer nullCategory) or: [heading == nil])
- 		ifTrue: [category := Categorizer default]
- 		ifFalse: [category := heading asSymbol].
- 	self addCategory: category.
- 	((self categories includes: Categorizer default)
- 		and: [(self listAtCategoryNamed: Categorizer default) size = 0])
- 			ifTrue: [self removeCategory: Categorizer default].
- !

Item was removed:
- ----- Method: ClassEditorProtocolTest>>test39Category (in category 'tests') -----
- test39Category
- 
- 	self assert: editor category = editor subject category!

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

Item was removed:
- ----- Method: SourceRepository class>>default (in category 'instance creation') -----
- default
- 	^ self forSourceFiles: SourceFiles!

Item was removed:
- ----- Method: ClassFormatTest>>testWords (in category 'tests') -----
- testWords
- 	| format |
- 	format := ClassFormat words.
- 	self assert: format instSize = 0.
- 	self assert: format isVariable.
- 	self assert: format isBits.
- 	self assert: format isWords.
- 	self deny: format isFixed.
- 	self deny: format isPointers.
- 	self deny: format isBytes.
- 	self deny: format isWeak
- !

Item was removed:
- ----- Method: ClassEditorProtocolTest>>test31AllInstVarNames (in category 'tests') -----
- test31AllInstVarNames
- 	
- 	| subeditor |
- 	editor addInstVarName: 'gamma'.
- 	subeditor := ClassEditor forNewClassNamed: #EditorSubjectSub.
- 	subeditor superclass: editor.
- 	subeditor addInstVarName: 'delta'.
- 	self assert: subeditor allInstVarNames = (editor subject instVarNames, #('gamma' 'delta')).
- 
- !

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

Item was removed:
- ----- Method: PureBehaviorEditor>>product (in category 'building') -----
- product
- 	^ product ifNil: [product := self edRequiresBuild ifTrue: [self edBuild] ifFalse: [subject]]!

Item was removed:
- Notification subclass: #InvalidSystemChange
- 	instanceVariableNames: ''
- 	classVariableNames: ''
- 	poolDictionaries: ''
- 	category: 'SystemEditor-Squeak'!

Item was removed:
- ----- Method: CategorizerEditor>>elementArray (in category 'reflecting - private') -----
- elementArray
- 	^ self categories gather: [:category | self listAtCategoryNamed: category]!

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

Item was removed:
- ----- Method: SystemEditor>>removals (in category 'accessing') -----
- removals
- 	^ removals!

Item was removed:
- ----- Method: SystemEditor>>edRemoveClassNamed: (in category 'editing') -----
- edRemoveClassNamed: aSymbol
- 	additions removeKey: aSymbol ifAbsent: [].
- 	removals add: aSymbol!

Item was removed:
- EditorSubjectSubTest subclass: #ClassExporterTest
- 	instanceVariableNames: 'exporter'
- 	classVariableNames: ''
- 	poolDictionaries: ''
- 	category: 'SystemEditor-Tests'!

Item was removed:
- ----- Method: PureBehaviorEditor>>classCommentBlank (in category 'reflecting') -----
- classCommentBlank
- 	^ 'Main comment stating the purpose of this class and relevant relationship to other classes.
- 
- Possible useful expressions for doIt or printIt.
- 
- Structure:
-  instVar1		type -- comment about the purpose of instVar1
-  instVar2		type -- comment about the purpose of instVar2
- 
- Any further useful comments about the general approach of this implementation.'!

Item was removed:
- ----- Method: MethodDictionaryEditor class>>for: (in category 'instance creation') -----
- for: aClassEditor 
- 	^ self new setClassEditor: aClassEditor!

Item was removed:
- ----- Method: PureBehaviorEditor>>edRequiresBuild (in category 'building') -----
- edRequiresBuild
- "Answer true if this editor needs building; false otherwise"
- 	^ self subject isNil!

Item was removed:
- MetaclassEditor subclass: #RootMetaclassEditor
- 	instanceVariableNames: ''
- 	classVariableNames: ''
- 	poolDictionaries: ''
- 	category: 'SystemEditor-Squeak'!

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

Item was removed:
- ----- Method: EditorSubjectSubTest>>tearDown (in category 'running') -----
- tearDown
- 	(Smalltalk at: #EditorSubject)
- 		allSubclasses do: [:ea | ea removeFromSystem]!

Item was removed:
- ----- Method: SourceRepository>>storeComment:forClass:stamped: (in category 'creation') -----
- storeComment: commentString forClass: aClass stamped: stampString
- 	^ self storeComment: commentString forClass: aClass stamped: stampString prior: 0!

Item was removed:
- ----- Method: ClassFormat>>withInstSize: (in category 'converting') -----
- withInstSize: aSmallInteger
- 	self isPointers ifFalse: [self error: 'Only pointer formats can have named variables'].
- 	^ self class size: aSmallInteger spec: self instSpec index: self cClassIndex!

Item was removed:
- ----- Method: MetaclassEditor>>instVarNames (in category 'debugging') -----
- 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: [superclass instVarNames]
- 		ifFalse: [super instVarNames]!

Item was removed:
- ----- Method: CategorizerEditor>>listAtCategoryNumber: (in category 'reflecting - accessing') -----
- listAtCategoryNumber: anInteger
- 	^ self listAtCategoryNamed: (self categories at: anInteger)!

Item was removed:
- ----- Method: MethodEditor class>>source:classified:stamp:notifying:logging: (in category 'as yet unclassified') -----
- source: source classified: catString stamp: stamp notifying: requestor logging: aBoolean
- 	^ self new
- 		setSource: source
- 		classified: catString
- 		stamp: stamp
- 		notifying: requestor
- 		log: aBoolean!

Item was removed:
- ----- Method: MetaclassEditorBuildTest>>test07MethodRecompilation (in category 'tests') -----
- test07MethodRecompilation
- 	
- 	| dict |
- 	editor addInstVarName: 'psi'.
- 	dict := editor methodDictionary.
- 	self deny: (dict at: #ayin) == (editor subject compiledMethodAt: #ayin).
- !

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

Item was removed:
- ----- Method: SourceRepository class>>createFakeFileStream (in category 'accessing') -----
- createFakeFileStream
- 	| stream |
- 	stream := ReadWriteStream on: (String new: 100).
- 	stream nextPutAll: 'xxx'.
- 	stream position: 1.
- 	^ stream!

Item was removed:
- ----- Method: ClassFormat class>>weak (in category 'instance creation') -----
- weak
- 	^ self size: 0 spec: self weakSpec index: 0!

Item was removed:
- ----- Method: ClassFormatTest>>testNoState (in category 'tests') -----
- testNoState
- 	| format |
- 	format := ClassFormat noState.
- 	self assert: format instSize = 0.
- 	self assert: format isFixed.
- 	self assert: format isPointers.
- 	self assert: format isWords.
- 	self deny: format isVariable.
- 	self deny: format isBits.
- 	self deny: format isBytes.
- 	self deny: format isWeak!

Item was removed:
- ----- Method: ClassEditor>>edPrepareInstanceMigration: (in category 'building') -----
- edPrepareInstanceMigration: txn
- 	txn addMigrator: (InstanceMigrator from: self subject to: self product)!

Item was removed:
- ----- Method: SystemEditor class>>new (in category 'instance creation') -----
- new
- 	^ self on: Smalltalk!

Item was removed:
- ----- Method: PureBehaviorEditor>>compiledMethodAt: (in category 'editing') -----
- compiledMethodAt: aSelector
- 
- 	^ self compiledMethodAt: aSelector ifAbsent: [ self error: 'key not found' ]!

Item was removed:
- ----- Method: ClassFormatTest>>testBytes (in category 'tests') -----
- testBytes
- 	| format |
- 	format := ClassFormat bytes.
- 	self assert: format instSize = 0.
- 	self assert: format isVariable.
- 	self assert: format isBits.
- 	self assert: format isBytes.
- 	self deny: format isFixed.
- 	self deny: format isPointers.
- 	self deny: format isWords.
- 	self deny: format isWeak
- !

Item was removed:
- ----- Method: ClassEditor>>edDependentsDo: (in category 'building') -----
- edDependentsDo: aBlock
- 	super edDependentsDo: aBlock.
- 	self edDependentSubclassesDo: aBlock.
- 	self edDependentSuperclassesDo: aBlock.!

Item was removed:
- ----- Method: ClassEditorProtocolTest>>test35IsBehavior (in category 'tests') -----
- test35IsBehavior
- 
- 	self assert: editor isBehavior!

Item was removed:
- ----- Method: ClassEditorValidationTest>>test06InstVarNamedSelf (in category 'tests') -----
- test06InstVarNamedSelf
- 
- 	editor addInstVarName: 'self'.
- 	self should: [editor validate] raise: IllegalVariableName.!

Item was removed:
- ----- Method: ClassFormat class>>fromBits: (in category 'instance creation') -----
- fromBits: bits
- 	^ self
- 		size: (((bits bitShift: -10) bitAnd: 192) + ((bits bitShift: -1) bitAnd: 63) - 1)
- 		spec: ((bits bitShift: -7) bitAnd: 15)
- 		index: ((bits bitShift: -11) bitAnd: 31)!

Item was removed:
- ----- Method: SystemEditor>>setSubject: (in category 'initialize-release') -----
- setSubject: anEnvironment 
- 	subject := anEnvironment.
- 	additions := IdentityDictionary new.
- 	removals := Set new.!

Item was removed:
- ----- Method: ClassEditorProtocolTest>>test34Subclasses (in category 'tests') -----
- test34Subclasses
- 
- 	| supereditor |
- 	supereditor := (editor system at: #Object)
- 					subclass: #EditorSubjectSuper 
- 					instanceVariableNames: ''
- 					classVariableNames: ''
- 					poolDictionaries: ''
- 					category: 'Testing'.
- 	editor superclass: supereditor.
- 	self assert: supereditor subclasses = (Array with: editor)!

Item was removed:
- ----- Method: PureBehaviorEditor>>decompilerClass (in category 'reflecting') -----
- decompilerClass
- 	^ self subject 
- 		ifNil: [Decompiler]
- 		ifNotNil: [self subject decompilerClass]!

Item was removed:
- ----- Method: SystemEditorTest>>test07ReshapesSubclasses (in category 'tests') -----
- test07ReshapesSubclasses
- 	| superclass |
- 	superclass := editor at: #ClassEditorTest.
- 	superclass addInstVarName: 'gamma'.
- 	self assertClassesAreMigrated: ClassEditorTest subclasses!

Item was removed:
- ----- Method: ClassFormat class>>namedAndIndexedSpec (in category 'storage specifications') -----
- namedAndIndexedSpec
- 	^ 3!

Item was removed:
- ----- Method: ClassEditor>>instVarAt:put: (in category 'debugging') -----
- 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 removed:
- ----- Method: MetaclassEditor>>instSize (in category 'debugging') -----
- instSize
- 	"Override the implemenation in Behavior, so that when inspecting the
- 	ClassEditor, it will look like a regular Class"
- 
- 	^ self isDebuggingAsEditor
- 		ifTrue: [superclass instSize]
- 		ifFalse: [super instSize]!

Item was removed:
- ClassEditorTest subclass: #ClassEditorProtocolTest
- 	instanceVariableNames: ''
- 	classVariableNames: ''
- 	poolDictionaries: ''
- 	category: 'SystemEditor-Tests'!

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

Item was removed:
- ----- Method: SystemEditor>>edRegisterEditor: (in category 'building') -----
- edRegisterEditor: anEditor 
- 	additions at: anEditor name put: anEditor!

Item was removed:
- ----- Method: MetaclassEditorBuildTest>>test09NoSubject (in category 'tests') -----
- test09NoSubject
- 	
- 	| result |
- 	editor := (ClassEditor forNewClassNamed: #EditorSubect2) class.
- 	result := editor edBuild.
- 	self assert: result isMeta!

Item was removed:
- ----- Method: MethodEditor>>compileFor: (in category 'building') -----
- compileFor: aClassEditor
- [
- 	| node method |
- 	node := aClassEditor product compilerClass new
- 				compile: source
- 				in: aClassEditor product
- 				notifying: requestor
- 				ifFail: nil.
- 	node encoder requestor: self.
- 	method := node generate: #(0 0 0 0).
- 	(method respondsTo: #selector:) "set selector on 3.9 and above"
- 		ifTrue: [method selector: node selector].
- 	^ method
- ] on: SyntaxErrorNotification do: [:ex |
- 	"In 3.10, the class category needs to be set"
- 	ex instVarNamed: #category put: aClassEditor category.
- 	"Let the user fix and install the fixed code into the class's old or temporary MethodDictionary"
- 	ex outer.
- 	"Now fetch and use that code instead"
- 	source := aClassEditor product sourceCodeAt: self selector ifAbsent: [^ nil].
- 	^ aClassEditor product compiledMethodAt: self selector
- ]!

Item was removed:
- ----- Method: RootClassEditor>>withAllSuperclassesDo: (in category 'reflecting') -----
- withAllSuperclassesDo: aBlock
- 	^ self!

Item was removed:
- ----- 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 removed:
- ----- Method: ClassEditor>>removeClassVarName: (in category 'editing') -----
- removeClassVarName: aString 
- 	classVarNames ifNil: [classVarNames := subject classVarNames].
- 	classVarNames := classVarNames copyWithout: aString!

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

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

Item was removed:
- ----- Method: CategorizerEditor>>changedElementsAndCategoriesCollect: (in category 'accessing changed elements') -----
- changedElementsAndCategoriesCollect: aBlock
- "Evaluates aBlock for each added or recategorized elements, and its category. Answers an OrderedCollection of the results"
- 
- 	| newCollection |
- 	newCollection := OrderedCollection new.
- 	self changedElementsAndCategoriesDo: [:anElement :aCategory |
- 		newCollection add: (aBlock value: anElement value: aCategory)].
- 	^ newCollection!

Item was removed:
- ----- Method: SystemEditor>>commitWithProgress (in category 'building') -----
- commitWithProgress
- 
- 	showProgress := true.
- 	self commit.
- 	showProgress := false.!

Item was removed:
- ----- Method: SourceRepositoryTest>>setUp (in category 'running') -----
- setUp
- 	repository := SourceRepository newInternal!

Item was removed:
- ----- Method: OrganizationEditor class>>on: (in category 'instance creation') -----
- on: anOrganizer
- 	^ self for: anOrganizer subject!

Item was removed:
- ----- Method: TestCategoryEditor>>classifyChange:under:suppressIfDefault: (in category 'accessing') -----
- classifyChange: element under: category suppressIfDefault: aBoolean
- 	changes classify: element under: category suppressIfDefault: aBoolean!

Item was removed:
- ----- Method: SystemEditorTest>>test15KeyAtIdentityValueFindPools (in category 'tests') -----
- test15KeyAtIdentityValueFindPools
- 	self assert: (editor keyAtIdentityValue: Undeclared ifAbsent: [nil]) = #Undeclared!

Item was removed:
- ----- Method: SystemOrganizationEditor>>changedElementsAndCategoriesDo: (in category 'accessing') -----
- changedElementsAndCategoriesDo: aBlock
- 	system editors keysAndValuesDo: [:key :editor |
- 		aBlock value: key value: editor category]!

Item was removed:
- ----- Method: OrganizationEditorTest>>sourceFileNumber (in category 'remote string') -----
- sourceFileNumber
- 	^ 2!

Item was removed:
- ----- Method: SourceRepository>>changesStream (in category 'accessing') -----
- changesStream
- 	^ files at: self changesIndex!

Item was removed:
- ----- Method: ClassEditor>>superclass: (in category 'editing') -----
- superclass: aClassOrEditor 
- 	super superclass: aClassOrEditor.
- 	self class superclass: aClassOrEditor class!

Item was removed:
- ----- Method: OrganizationEditor class>>for:repository: (in category 'instance creation') -----
- for: aClassEditor repository: aSourceRepository
- 	^ self new setClassEditor: aClassEditor repository: aSourceRepository!

Item was removed:
- ----- Method: ClassEditorProtocolTest>>test03RemoveClassVarName (in category 'tests') -----
- test03RemoveClassVarName
- 	editor removeClassVarName: 'Beth'.
- 	self assert: editor classVarNames = (editor subject classVarNames copyWithout: 'Beth')!

Item was removed:
- ----- Method: OrganizationEditorTest>>repository (in category 'construction') -----
- repository
- 	self shouldBeImplemented!

Item was removed:
- ----- Method: ClassEditorBuildTest>>test15CommentChanged (in category 'tests') -----
- test15CommentChanged
- 	
- 	| migration |
- 	editor classComment: 'A new comment' stamp: 'cwp 12/18/2005 15:47'.
- 
- 	migration := MigrationTransaction new.
- 	editor edPrepareMigration: migration.
- 	self assert: migration migrators size = 1.
- 	self assert: (migration migrators first origin isKindOf: ClassOrganizer)!

Item was removed:
- TestCase subclass: #InstanceMigratorTest
- 	instanceVariableNames: ''
- 	classVariableNames: ''
- 	poolDictionaries: ''
- 	category: 'SystemEditor-Tests'!

Item was removed:
- ----- Method: ClassFormat>>isBits (in category 'testing') -----
- isBits
- 	"Answer whether the receiver contains just bits (not pointers)."
- 
- 	^ self instSpec >= 6!

Item was removed:
- ----- Method: OrganizationEditorTest>>setUp (in category 'running') -----
- setUp
- 	editor := OrganizationEditor for: EditorSubject!

Item was removed:
- ----- Method: MetaclassEditor>>canUnderstand: (in category 'debugging') -----
- canUnderstand: selector
- 
- 	^ superclass canUnderstand: selector!

Item was removed:
- ----- Method: ClassEditorProtocolTest>>test32FormatWithEditedSuperclass (in category 'tests') -----
- test32FormatWithEditedSuperclass
- 
- 	| format supereditor |
- 	supereditor := (editor system at: #Object)
- 					subclass: #EditorSubjectSub 
- 					instanceVariableNames: 'gamma'
- 					classVariableNames: ''
- 					poolDictionaries: ''
- 					category: 'Testing'.
- 	editor superclass: supereditor.
- 	format := ClassFormat fromBits: editor format.
- 	self assert: format instSize = (supereditor instSize + editor instVarNames size)!

Item was removed:
- ----- Method: SourceRepository>>hash (in category 'comparing') -----
- hash
- 	^ self sourcesStream identityHash bitXor: self changesStream identityHash!

Item was removed:
- ----- Method: ClassEditorProtocolTest>>test28InstSize (in category 'tests') -----
- test28InstSize
- 	| sub |
- 	sub := editor
- 			subclass: #EditorSubjectSubclass
- 			instanceVariableNames: 'gamma'
- 			classVariableNames: ''
- 			poolDictionaries: ''
- 			category: 'SystemEditor-Tests'.
- 	self assert: sub instSize = 3!

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

Item was removed:
- ----- Method: MethodEditor>>interactive (in category 'accessing') -----
- interactive
- 	^ false!

Item was removed:
- ----- Method: SystemEditorTest>>test09RecompilesSubclasses (in category 'tests') -----
- test09RecompilesSubclasses
- 	"This test isn't quite right. It should actually compare compiled methods."
- 
- 	| superclass |
- 	superclass := editor at: #ClassEditorTest.
- 	superclass removeInstVarName: 'alpha'.
- 	self assertClassesAreMigrated: ClassEditorTest subclasses!

Item was removed:
- ----- Method: PureBehaviorEditor class>>reservedNames (in category 'accessing') -----
- reservedNames
- 	^ ReservedNames!

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

Item was removed:
- ----- Method: ClassExporter>>replace: (in category 'private') -----
- replace: aClass
- 	oldClasses add: (environment at: aClass name).
- 	newClasses add: aClass!

Item was removed:
- ----- Method: SystemEditor>>edResolve: (in category 'building') -----
- edResolve: aSymbol
- 	^ subject at: aSymbol!

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

Item was removed:
- ----- Method: ClassFormat class>>bytes (in category 'instance creation') -----
- bytes
- 	^ self size: 0 spec: self bytesSpec index: 0!

Item was removed:
- ----- Method: MethodEditor>>repository (in category 'accessing') -----
- repository
- 	^ repository ifNil: [repository := SourceRepository default]!

Item was removed:
- ----- Method: ClassFormat class>>weakSpec (in category 'storage specifications') -----
- weakSpec
- 	^ 4!

Item was removed:
- ----- Method: SourceRepository>>storeMethod:forClass:category:stamped: (in category 'creation') -----
- storeMethod: sourceString forClass: aClass category: catString stamped: stampString 
- 	^ self storeMethod: sourceString forClass: aClass category: catString stamped: stampString prior: nil!

Item was removed:
- Object subclass: #ClassFormat
- 	instanceVariableNames: 'instSize instSpec cClassIndex'
- 	classVariableNames: ''
- 	poolDictionaries: ''
- 	category: 'SystemEditor-Squeak'!
- 
- !ClassFormat commentStamp: 'mtf 7/7/2008 23:18' prior: 0!
- I am an expert on the way the Squeak VM encodes class formats. My instance variable, 'bits', is identical in format to the 'format' instance variable of Behavior. I have methods for interpreting those bits. The class format integer is 18 bits in length. The instSize field is split into two parts for backwards compatibility.
- 
- <2 bits=instSize//64> <5 bits=cClass> <4 bits=instSpec> <6 bits=instSize\\64> <1 bit=0>
- 
- - instSize: the number of named instance variables
- - cClass: the index into the compact class table
- - instSpec: values indicating how instances are organized
- 	0 - no state
- 	1 - named instance variables only
- 	2 - variable number of object pointers
- 	3 - named instance variables, variable number of object pointers
- 	4 - variable number of weak object pointers
- 	6 - variable number of words
- 	8 - variable number of bytes
- 	12 - compiled method format: variable number of object pointers, variable number of bytes!

Item was removed:
- ----- Method: CategorizerEditor>>categories: (in category 'reflecting - accessing') -----
- categories: anArray
- 
- 	categories := anArray!

Item was removed:
- CategorizerEditor subclass: #SystemOrganizationEditor
- 	instanceVariableNames: 'system'
- 	classVariableNames: ''
- 	poolDictionaries: ''
- 	category: 'SystemEditor-Squeak'!

Item was removed:
- ----- Method: ClassDescriptionEditor>>edSuperclass (in category 'building') -----
- edSuperclass
- "Answer my product's superclass, building it if necessary"
- 
- 	| classOrEditor |
- 	classOrEditor :=  self superclassOrEditor.
- 	^ classOrEditor edIsEditor
- 		ifTrue: [classOrEditor product]
- 		ifFalse: [classOrEditor]!

Item was removed:
- ----- Method: ClassEditorValidationTest>>test04TooManyInstVars (in category 'tests') -----
- test04TooManyInstVars
- 	1 to: 255 do: [:i | editor addInstVarName: i asString].
- 	self should: [editor validate] raise: InvalidClassFormat!

Item was removed:
- ----- Method: ClassFormatTest>>testNamedWithInstSize (in category 'tests') -----
- testNamedWithInstSize
- 	| old new |
- 	old := ClassFormat named: 3.
- 	new := old withInstSize: 5.
- 	self assert: new instSize = 5.
- 	self assert: new instSpec = old instSpec.
- 	self assert: new cClassIndex = old cClassIndex!

Item was removed:
- ----- Method: ClassEditor>>edPrepareExport: (in category 'building') -----
- edPrepareExport: exporter 
- 	^exporter addClass: self product!

Item was removed:
- ----- Method: ClassEditorValidationTest>>test05MultiplyDefinedInstVars (in category 'tests') -----
- test05MultiplyDefinedInstVars
- 	"See ClassEditorProtocolTest>>test29InstVarsArentDuplicated"
- 
- 	editor
- 		addInstVarName: 'gamma';
- 		addInstVarName: 'gamma'.
- 	self assert: editor edIsValid!

Item was removed:
- ----- Method: SystemEditorTest>>test18RemovedClassesArentPresent (in category 'tests') -----
- test18RemovedClassesArentPresent
- 	| classEditor |
- 	classEditor := editor at: #EditorSubject.
- 	classEditor removeFromSystem.
- 	self should: [editor at: #EditorSubject] raise: Error.!

Item was removed:
- ----- Method: OrganizationEditor>>removedElements (in category 'accessing') -----
- removedElements
- 	^ classEditor methods removals!

Item was removed:
- ----- Method: ClassFormat>>setSize:spec:index: (in category 'initializing') -----
- setSize: size spec: spec index: index
- 	instSize := size.
- 	instSpec := spec.
- 	cClassIndex := index.!

Item was removed:
- ----- Method: SourceRepository>>sourcesIndex (in category 'accessing') -----
- sourcesIndex
- 	^ 1!

Item was removed:
- ----- Method: CategoryEditorTest>>tearDown (in category 'as yet unclassified') -----
- tearDown
- 	self assert: categorizer subject printString =
- '(''as yet unclassified'' d e)
- (''abc'' a b c)
- (''unreal'')
- '!

Item was removed:
- EditorSubjectSubTest subclass: #SystemEditorCommitTest
- 	instanceVariableNames: 'editor'
- 	classVariableNames: ''
- 	poolDictionaries: ''
- 	category: 'SystemEditor-Tests'!

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

Item was removed:
- ----- Method: EditorSubject class>>aleph: (in category 'accessing class vars') -----
- aleph: anObject
- 	Aleph := anObject!

Item was removed:
- ----- Method: TestCategoryEditor>>changesAddCategory:before: (in category 'accessing') -----
- changesAddCategory: newCategory before: nextCategory
- 	"I don't support ordering"
- 	changes addCategory: newCategory!

Item was removed:
- ----- Method: ClassEditor>>edCategory (in category 'building') -----
- edCategory
- 	^ category!

Item was removed:
- ----- Method: ClassEditor>>edRequiresRecompile (in category 'building') -----
- edRequiresRecompile
- 	classVarNames ifNotNil: [^ true].
- 	sharedPools ifNotNil: [^ true].
- 	^ super edRequiresRecompile!

Item was removed:
- ----- Method: ClassEditorProtocolTest>>test05AddClassVarName (in category 'tests') -----
- test05AddClassVarName
- 	editor addClassVarName: #Gimel.
- 	self assert: editor classVarNames = (editor subject classVarNames copyWith: #Gimel)!

Item was removed:
- ----- Method: ClassEditorValidationTest>>test13InstVarDefinedInSubclass (in category 'tests') -----
- test13InstVarDefinedInSubclass
- 
- 	editor
- 		subclass: #EditorSubjectSub
- 		instanceVariableNames: 'gamma'
- 		classVariableNames: ''
- 		poolDictionaries: ''
- 		category: 'Testing'.
- 	editor addInstVarName: 'gamma'.
- 	self should: [editor validate] raise: IllegalVariableName.!

Item was removed:
- ----- Method: SystemEditorTest>>test17RemovedClassesAreAbsent (in category 'tests') -----
- test17RemovedClassesAreAbsent
- 	| classEditor |
- 	classEditor := editor at: #EditorSubject.
- 	classEditor removeFromSystem.
- 	self assert: (editor at: #EditorSubject ifAbsent: [nil]) isNil!

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

Item was removed:
- ----- Method: ClassEditor>>edNameHasChanged (in category 'building') -----
- edNameHasChanged
- 	name ifNil: [^ false].
- 	^ name ~~ self subject name!

Item was removed:
- ----- Method: ClassDescriptionEditor>>superclassOrEditor (in category 'accessing') -----
- superclassOrEditor
- "Answer my superclass as an editor if it is being edited, or as a class if it is not. Does not add anything to my SystemEditor"
- 
- 	superEditor ifNotNil: [^ superEditor].
- 	self subject superclass ifNil: [^ self realClass classRootEditor on: nil for: self environment].
- 	^ self environment classOrEditorFor: self subject superclass!

Item was removed:
- ----- Method: ClassEditorBuildTest>>test07AddSharedPool (in category 'tests') -----
- test07AddSharedPool
- 	
- 	| result pool |
- 	pool := Dictionary new.
- 	editor addSharedPool: pool.
- 	result := editor product.
- 	self deny: result == editor subject.
- 	self assert: (result sharedPools includes: pool).
- 	self deny: (editor subject sharedPools includes: pool).!

Item was removed:
- TestCase subclass: #SourceRepositoryTest
- 	instanceVariableNames: 'repository'
- 	classVariableNames: ''
- 	poolDictionaries: ''
- 	category: 'SystemEditor-Tests'!

Item was removed:
- ----- Method: PureBehaviorEditor>>printOn: (in category 'printing') -----
- printOn: aStream
- 
- 	| title |
- 	title := self realClass name.
- 	aStream
- 		nextPutAll: (title first isVowel ifTrue: ['an '] ifFalse: ['a ']);
- 		nextPutAll: title;
- 		nextPutAll: ' on: ';
- 		print: self subject !

Item was removed:
- ----- Method: ClassEditor>>subclass:instanceVariableNames:classVariableNames:poolDictionaries:category: (in category 'editing') -----
- subclass: aSymbol instanceVariableNames: instString classVariableNames: classString poolDictionaries: poolString category: categoryString 
- 	^ ((system 
- 		at: aSymbol
- 		ifAbsent: [ ClassEditor on: nil for: system])
- 			edName: aSymbol
- 			superclassEditor: self
- 			type: #normal
- 			instVarString: instString
- 			classVarString: classString
- 			poolImports: poolString
- 			category: categoryString) edRegisterEditor!

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

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

Item was removed:
- ----- Method: SourceRepository>>storeComment:forClass:stamped:prior: (in category 'creation') -----
- storeComment: commentString forClass: aClass stamped: stampString prior: aSourcePointer
- 	| remote stream |
- 	self assureStartupStampLogged.
- 	stream := self changesStream.
- 	stream
- 		setToEnd;
- 		cr;
- 		nextPut: $!!;
- 		nextPutAll: aClass name;
- 		nextPutAll: ' commentStamp: ';
- 		print: stampString;
- 		nextPutAll: ' prior: ';
- 		print: aSourcePointer;
- 		nextPut: $!!;
- 		cr.
- 	remote := RemoteString 
- 				newString: commentString
- 				onFileNumber: self changesIndex 
- 				toFile: stream.
- 		^ remote!

Item was removed:
- ----- Method: ClassEditorBuildTest>>test04AddClassVar (in category 'tests') -----
- test04AddClassVar
- 	
- 	| result |
- 	editor addClassVarName: 'Gimel'.
- 	result := editor product.
- 	self deny: result == editor subject.
- 	self assert: result classVarNames = editor classVarNames.
- !

Item was removed:
- ----- Method: SystemEditor>>edResolve:ifAbsent: (in category 'building') -----
- edResolve: aSymbol ifAbsent: aBlock
- 	^ subject at: aSymbol ifAbsent: aBlock!

Item was removed:
- ----- Method: TestCategoryEditor class>>on: (in category 'as yet unclassified') -----
- on: aCategorizer
- 	^ self new setSubject: aCategorizer!

Item was removed:
- ----- Method: ClassFormat>>typeOfClass (in category 'accessing') -----
- typeOfClass
- 	"Answer a symbol uniquely describing the type of the receiver"
- 	self instSpec = self class compiledMethodSpec ifTrue:[^#compiledMethod]. "Very special!!"
- 	self isBytes ifTrue:[^#bytes].
- 	(self isWords and:[self isPointers not]) ifTrue:[^#words].
- 	self isWeak ifTrue:[^#weak].
- 	self isVariable ifTrue:[^#variable].
- 	^#normal.!

Item was removed:
- ----- Method: ClassFormat class>>specFromType:size: (in category 'storage specifications') -----
- specFromType: aSymbol size: size
- 	^ aSymbol caseOf: {
- 		[#normal] -> [size > 0 ifTrue: [self namedSpec] ifFalse: [self noStateSpec]].
- 		[#variable] -> [self indexedSpec: size].
- 		[#bytes] -> [self bytesSpec].
- 		[#words] -> [self wordsSpec].
- 		[#weak] -> [self weakSpec].
- 		[#compiledMethod] -> [self compiledMethodSpec].
- 	} otherwise: [self error: 'Unknown class type: ', aSymbol]
- 	!

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

Item was removed:
- ----- Method: CategorizerEditor>>removedElements (in category 'accessing changed elements') -----
- removedElements
- "Answers a list of elements that have been removed"
- 
- 	^ Array new!

Item was removed:
- ----- Method: CategorizerEditor>>addCategory: (in category 'reflecting - accessing') -----
- addCategory: newCategory
- 	^ self addCategory: newCategory before: nil!

Item was removed:
- ----- Method: CategorizerEditor>>categories (in category 'reflecting - accessing') -----
- categories
- 
- 	^ categories!

Item was removed:
- ----- Method: ClassEditorBuildTest>>test14SuperclassEditedInstVars (in category 'tests') -----
- test14SuperclassEditedInstVars
- 	
- 	| result subeditor |
- 	editor addInstVarName: 'gamma'.
- 	subeditor := ClassEditor forNewClassNamed: #EditorSubjectSub.
- 	subeditor superclass: editor.
- 	subeditor addInstVarName: 'delta'.
- 	result := subeditor product.
- 	self assert: result allInstVarNames = (editor subject instVarNames, #('gamma' 'delta')).
- 
- !

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

Item was removed:
- ----- Method: MethodEditor>>timeStamp (in category 'accessing') -----
- timeStamp
- 	^ stamp!

Item was removed:
- ----- Method: SystemOrganizationEditor>>setSystem: (in category 'as yet unclassified') -----
- setSystem: anEnvironment
- 	system := anEnvironment!

Item was removed:
- ----- Method: OrganizationEditorTest>>test11RemovingCommentCausesBuild (in category 'tests') -----
- test11RemovingCommentCausesBuild
- 	| repository |
- 	repository := SourceRepository newInternal.
- 	editor := OrganizationEditor for: (ClassEditor on: self class)
- 				repository: repository.
- 	editor classComment: nil stamp: nil.
- 	self assert: editor edRequiresBuild!

Item was removed:
- ----- Method: SourceRepository>>storeComment:forClass:category:stamped:replacing: (in category 'creation') -----
- storeComment: aByteString forClass: aClass category: aByteString3 stamped: aByteString4 replacing: aRemoteString 
- 	self shouldBeImplemented!

Item was removed:
- ----- Method: ClassEditorProtocolTest>>test33InstSizeWithEditedSuperclass (in category 'tests') -----
- test33InstSizeWithEditedSuperclass
- 
- 	| supereditor |
- 	supereditor := (editor system at: #Object)
- 					subclass: #EditorSubjectSub 
- 					instanceVariableNames: 'gamma'
- 					classVariableNames: ''
- 					poolDictionaries: ''
- 					category: 'Testing'.
- 	editor superclass: supereditor.
- 	self assert: editor instSize = (supereditor instSize + editor instVarNames size)!

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

Item was removed:
- ----- 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"
- 
- 	^ self environment debug!

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

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

Item was removed:
- ----- Method: OrganizationEditor>>setClassEditor:repository: (in category 'initialize-release') -----
- setClassEditor: aClassEditor repository: aSourceRepository
- 	isDirty := false.
- 	classEditor := aClassEditor.
- 	repository := aSourceRepository.
- 	self setSubject: nil.!

Item was removed:
- ----- 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 removed:
- ----- Method: SourceRepository class>>forSourceFiles: (in category 'instance creation') -----
- forSourceFiles: anArray
- 	^ self new setSourceFiles: anArray!

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

Item was removed:
- ----- Method: ClassFormat>>error: (in category 'errors') -----
- error: aString
- 	InvalidClassFormat signal: aString!

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

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

Item was removed:
- ----- Method: MethodDictionaryEditor>>at:ifAbsent: (in category 'reflecting') -----
- at: aSymbol ifAbsent: absentBlock
- 	(removals includes: aSymbol) ifTrue: [^ absentBlock value].
- 	additions at: aSymbol ifPresent: [:editor | ^ editor].
- 	self subject at: aSymbol ifPresent: [:aCompiledMethod | ^ self add: (MethodEditor
- 		source: (classEditor subject sourceCodeAt: aSymbol)
- 		classified: (classEditor organization subject categoryOfElement: aSymbol)
- 		stamp: aCompiledMethod timeStamp
- 		notifying: nil
- 		logging: true )].
- 	^ absentBlock value!

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

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

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

Item was removed:
- ----- Method: MetaclassEditorBuildTest>>test03Superclass (in category 'tests') -----
- test03Superclass
- 	
- 	| result |
- 	editor superclass: self class class.
- 	result := editor edBuild.
- 	self deny: result == editor subject.
- 	self assert: result superclass == self class class.!

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

Item was removed:
- PureBehaviorEditor subclass: #ClassDescriptionEditor
- 	instanceVariableNames: 'superEditor type instVarNames'
- 	classVariableNames: ''
- 	poolDictionaries: ''
- 	category: 'SystemEditor-Squeak'!
- 
- !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 removed:
- ----- Method: PureBehaviorEditor>>binding (in category 'reflecting') -----
- binding
- 	^ nil -> self!

Item was removed:
- ----- Method: SystemEditorCommitTest>>test03RemovesClasses (in category 'tests') -----
- test03RemovesClasses
- 	| classEditor |
- 	classEditor := editor at: #EditorSubjectSub.
- 	classEditor removeFromSystem.
- 	editor commit.
- 	self deny: (Smalltalk hasClassNamed: #EditorSubjectSub)!

Item was removed:
- ----- Method: ClassFormat>>indexedSubclass: (in category 'converting') -----
- indexedSubclass: nInstVars
- 	| newSize |
- 	self isPointers ifFalse: [self error: 'Can''t make a pointer subclass.'].
- 	newSize := self instSize + nInstVars.
- 	newSize > 254 ifTrue: [self error: 'Too many instance variables'].
- 	
- 	^ self class indexed: newSize!

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

Item was removed:
- ----- Method: SourceRepository>>storeComment:forClass:stamped:replacing: (in category 'creation') -----
- storeComment: commentString forClass: aClass stamped: stampString replacing: aRemoteString
- 	^ self 
- 		storeComment: commentString
- 		forClass: aClass
- 		stamped: stampString
- 		prior: aRemoteString sourcePointer!

Item was removed:
- ----- Method: MetaclassEditorProtocolTest>>test06RemoveNewSelector (in category 'tests') -----
- test06RemoveNewSelector
- 	editor removeSelector: #pe.
- 	self deny: (editor includesSelector: #pe)!

Item was removed:
- ----- Method: OrganizationEditorTest>>position (in category 'remote string') -----
- position
- 	^ 42!

Item was removed:
- ----- Method: OrganizationEditor>>classComment (in category 'SystemEditor-Editors') -----
- classComment
- 	^comment ifNil: [self subject ifNotNil: [self subject classComment]]!

Item was removed:
- ----- Method: CategorizerEditor>>newCategoryFor: (in category 'as yet unclassified') -----
- newCategoryFor: oldCategory
- 	^ renamedCategories at: oldCategory ifAbsent: [oldCategory]!

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

Item was removed:
- ----- Method: SystemEditor>>renameClass:from: (in category 'reflecting') -----
- renameClass: aClassEditor from: aSymbol 
- 	self edRemoveClassNamed: aSymbol.
- 	aClassEditor edRegisterEditor!

Item was removed:
- ----- Method: TestCategoryEditor>>removedElements (in category 'private') -----
- removedElements
- 	^ removedElements !

Item was removed:
- ----- Method: ClassFormatTest>>testBitsWithInstSize (in category 'tests') -----
- testBitsWithInstSize
- 	| format |
- 	format := ClassFormat bytes.
- 	self should: [format withInstSize: 2] raise: InvalidClassFormat!

Item was removed:
- ----- Method: ClassEditor>>realClass (in category 'accessing') -----
- realClass
- "Answer the true class, which is the superclass of my MetaclassEditor"
- 
- 	^ self class instVarAt: 1!

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

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

Item was removed:
- ClassEditorTest subclass: #ClassEditorOntologyTest
- 	instanceVariableNames: ''
- 	classVariableNames: ''
- 	poolDictionaries: ''
- 	category: 'SystemEditor-Tests'!

Item was removed:
- ----- 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 removed:
- ----- Method: MetaclassEditorProtocolTest>>test01InstVarNames (in category 'tests') -----
- test01InstVarNames
- 	self assert: editor instVarNames = editor subject instVarNames!

Item was removed:
- ----- Method: PureBehaviorEditor>>propertyAt:ifPresent: (in category 'accessing properties') -----
- propertyAt: key ifPresent: aBlock
- 
- 	self propertyAt: key ifAbsent: [^ nil].
- 	^ aBlock value!

Item was removed:
- ----- Method: ClassEditor>>instVarAt: (in category 'debugging') -----
- 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 removed:
- ----- Method: ClassEditorProtocolTest>>test44SourceCodeAt (in category 'tests') -----
- test44SourceCodeAt
- 	self assert: (editor sourceCodeAt: #het) = (editor subject sourceCodeAt: #het)!

Item was removed:
- ----- Method: ClassEditorProtocolTest>>test36InstanceVariablesString (in category 'tests') -----
- test36InstanceVariablesString
- 
- 	self assert: editor instanceVariablesString = editor subject instanceVariablesString!

Item was removed:
- ----- Method: ClassEditorProtocolTest>>test43SetClassComment (in category 'tests') -----
- test43SetClassComment
- 	editor classComment: 'class comment' stamp: 'cwp 12/11/2005 22:00'.
- 	editor comment = 'class comment'!

Item was removed:
- ----- Method: OrganizationEditor>>commentStamp (in category 'reflecting') -----
- commentStamp
- 	^stamp ifNil: [self subject ifNotNil: [self subject commentStamp]]!

Item was removed:
- ----- Method: SystemEditor>>doItHost (in category 'accessing') -----
- doItHost
- "Answer an object which lets methods evaluated against it execute in my context:
- 
- Compiler evaluate: 'Array' for: SystemEditor new doItHost logged: false
- "
- 
- 	^ (self at: #UndefinedObject) new!

Item was removed:
- ----- Method: ClassEditorProtocolTest>>test17Format (in category 'tests') -----
- test17Format
- 
- 	| format |
- 	format := ClassFormat fromBits: editor format.
- 	self assert: format instSize = editor subject instSize.
- 	self assert: format instSpec = editor subject instSpec.
- 	self assert: format isBits = editor subject isBits.
- 	self assert: format isBytes = editor subject isBytes.
- 	self assert: format isFixed = editor subject isFixed.
- 	self assert: format isPointers = editor subject isPointers.
- 	self assert: format isVariable = editor subject isVariable.
- 	self assert: format isWeak = editor subject isWeak.
- 	self assert: format isWords = editor subject isWords.!

Item was removed:
- ----- Method: SystemEditor>>edSubclassesOf: (in category 'building') -----
- edSubclassesOf: anEditor
- "Answers all subclasses of the given ClassEditor, as editors"
- 
- 	^ (self edSubclassesOrEditorsOf: anEditor) collect: [:ea | self edEditorFor: ea]!

Item was removed:
- ----- Method: SystemEditor>>edEditorFor: (in category 'building') -----
- edEditorFor: aClass
- 	| name editor |
- 	aClass edIsEditor ifTrue: [^ aClass].
- 	name := aClass theNonMetaClass name.
- 	editor := self at: name.
- 	^ aClass isMeta ifFalse: [editor] ifTrue: [editor class].!

Item was removed:
- ----- Method: ClassEditor>>sharedPoolsString (in category 'reflecting') -----
- sharedPoolsString
- 	^ String streamContents: [ :stream |
- 		self sharedPools 
- 			do: [ :each |
- 				stream nextPutAll: (system 
- 								keyAtIdentityValue: each 
- 								ifAbsent: ['private'])]
- 			separatedBy: [stream space]]!

Item was removed:
- ----- Method: ClassEditorProtocolTest>>test40SetCategory (in category 'tests') -----
- test40SetCategory
- 
- 	editor category: #'Test-Category'.
- 	self assert: editor category = #'Test-Category'!

Item was removed:
- TestCase subclass: #OrganizationEditorTest
- 	instanceVariableNames: 'editor stream'
- 	classVariableNames: ''
- 	poolDictionaries: ''
- 	category: 'SystemEditor-Tests'!
- 
- !OrganizationEditorTest commentStamp: 'cwp 12/18/2005 15:47' prior: 0!
- This comment must be present for the tests to pass.!

Item was removed:
- ----- Method: CategorizerEditor>>categoryOfChange: (in category 'accessing changed elements') -----
- categoryOfChange: element
- "Answers the category of a new or recategorized element"
- 
- 	self changedElementsAndCategoriesDo: [:anElement :aCategory |
- 		element = anElement ifTrue: [^ aCategory]].
- 	^ nil!

Item was removed:
- ----- Method: ClassEditorProtocolTest>>test01InstVarNames (in category 'tests') -----
- test01InstVarNames
- 	self assert: editor instVarNames = editor subject instVarNames!

Item was removed:
- ----- Method: PureBehaviorEditor>>parserClass (in category 'reflecting') -----
- parserClass
- 	^ self subject 
- 		ifNil: [Parser]
- 		ifNotNil: [self subject parserClass]!

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

Item was removed:
- ----- Method: ClassFormat class>>indexedSpec: (in category 'storage specifications') -----
- indexedSpec: size
- 	^ size = 0 ifTrue: [self indexedSpec] ifFalse: [self namedAndIndexedSpec]!

Item was removed:
- ----- Method: ClassEditor>>edRequiresSubclassRebuild (in category 'building') -----
- edRequiresSubclassRebuild
- 	^ self class edRequiresSubclassRebuild 
- 		or: [self edRequiresMigration]
- 		or: [self edRequiresRecompile]!

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

Item was removed:
- ----- Method: ClassEditor>>rearrangeSharedPoolVarNames: (in category 'editing') -----
- rearrangeSharedPoolVarNames: associations
- 	"The associations are name -> pos and cover the subset
- 	of vars that should be moved. The old just fill in the holes.
- 	NOTE: This method uses identityIncludes:, otherwise it fails on empty Dictionaries."
- 
- 	| newPools |
- 	newPools := Array new: sharedPools size.
- 	associations do: [:assoc |
- 		newPools at: assoc value put: (
- 			system edResolve: assoc key asSymbol
- 				ifAbsent: [self error: 'Can not resolve pool ', assoc key])].
- 	sharedPools do: [:oldPool |
- 		(newPools identityIncludes: oldPool) ifFalse: [
- 			newPools at: (newPools indexOf: nil) put: oldPool]].
- 	sharedPools := newPools!

Item was removed:
- ----- Method: SystemOrganizationEditor>>subject (in category 'accessing') -----
- subject
- 	^ subject ifNil: [self setSubject: system subject organization. subject]!

Item was removed:
- ----- Method: SourceRepository>>= (in category 'comparing') -----
- = other
- 	self class == other class ifFalse: [^ false].
- 	self sourcesStream == other sourcesStream ifFalse: [^ false].
- 	self changesStream == other changesStream ifFalse: [^ false].
- 	^ true!

Item was removed:
- ----- Method: MetaclassEditor>>allInstVarNames (in category 'debugging') -----
- allInstVarNames
- 	 "specialized in order to enable debugger to show as self"
- 	^ self isDebuggingAsEditor
- 		ifTrue: [superclass allInstVarNames]
- 		ifFalse: [super allInstVarNames]!

Item was removed:
- ----- Method: ClassEditorProtocolTest>>test11ClassVarNamesInterned (in category 'tests') -----
- test11ClassVarNamesInterned
- 	editor addClassVarName: 'Gimel'.
- 	self assert: (editor classVarNames anySatisfy: [:ea | ea == #Gimel])!

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

Item was removed:
- ----- Method: ClassExporter>>commit (in category 'public') -----
- commit
- 	[classes do: [:ea | self export: ea].
- 	self forwardIdentities]
- 		valueUnpreemptively
- !

Item was removed:
- ----- Method: CategorizerEditor>>printOn: (in category 'reflecting - printing') -----
- printOn: aStream
- 	self categories do: [:category |
- 		aStream nextPutAll: '('''; nextPutAll: category; nextPut: $'.
- 		(self listAtCategoryNamed: category) do: [:element |
- 			aStream space; nextPutAll: element].
- 		aStream nextPut: $); cr]!

Item was removed:
- ----- Method: ClassExporter>>export: (in category 'private') -----
- export: aClass
- 	(environment includesKey: aClass name)
- 		ifTrue: [self replace: aClass]
- 		ifFalse: [environment at: aClass name put: aClass]!

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

Item was removed:
- ----- Method: ClassFormatTest>>testNamedAndIndexed (in category 'tests') -----
- testNamedAndIndexed
- 	| format |
- 	format := ClassFormat indexed: 3.
- 	self assert: format instSize = 3.
- 	self assert: format isPointers.
- 	self assert: format isWords.
- 	self assert: format isVariable.
- 	self deny: format isFixed.
- 	self deny: format isBits.
- 	self deny: format isBytes.
- 	self deny: format isWeak
- !

Item was removed:
- ----- Method: ClassFormat class>>size:spec:index: (in category 'instance creation') -----
- size: instSize spec: instSpec index: cClassIndex
- 	^ self new setSize: instSize spec: instSpec index: cClassIndex!

Item was removed:
- ----- Method: ClassFormatTest>>testNoStateSubclass (in category 'tests') -----
- testNoStateSubclass
- 	| format superformat |
- 	superformat := ClassFormat noState.
- 	format := superformat namedSubclass: 0.
- 	self assert: format instSize = 0.
- 	self assert: format isFixed.
- 	self assert: format isPointers.
- 	self assert: format isWords.
- 	self deny: format isVariable.
- 	self deny: format isBits.
- 	self deny: format isBytes.
- 	self deny: format isWeak.
- 	self assert: superformat bits == format bits!

Item was removed:
- ----- Method: ClassDescriptionEditor>>methodDictionary (in category '*SystemEditor-Tests') -----
- 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: ClassFormat>>isWeak (in category 'testing') -----
- isWeak
- 	"Answer whether the receiver has contains weak references."
- 	^ self instSpec = 4!

Item was removed:
- ----- Method: SourceRepository>>setSourceFiles: (in category 'initialize-release') -----
- setSourceFiles: anArray
- 	files := anArray!

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

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

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

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

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

Item was removed:
- ----- Method: TestCategoryEditor>>changesRenameCategory:toBe: (in category 'accessing') -----
- changesRenameCategory: oldCategory toBe: newCategory
- 	changes renameCategory: oldCategory toBe: newCategory!

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

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

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

Item was removed:
- ----- Method: CategorizerEditor>>categoryOfElement: (in category 'reflecting - accessing') -----
- categoryOfElement: element
- 	(self removedElements includes: element) ifTrue: [^ nil].
- 	(self categoryOfChange: element) ifNotNilDo: [:cat | ^ cat].
- 	self subject ifNil: [^ nil].
- 	^ self newCategoryFor: (self subject categoryOfElement: element)
- !

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

Item was removed:
- ----- Method: SystemEditor>>edCommitRemovals (in category 'building') -----
- edCommitRemovals
- 	removals do: [:ea | self edRemove: ea]!

Item was removed:
- ----- Method: ClassEditorValidationTest>>test02BitsWithVariablesIsInvalid (in category 'tests') -----
- test02BitsWithVariablesIsInvalid
- 	editor typeOfClass: #bytes.
- 	self should: [editor validate] raise: InvalidClassFormat!

Item was removed:
- ----- Method: PureBehaviorEditor>>validate (in category 'validating') -----
- validate
- 	self decoratorsDo: [:ea | ea validate]!

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

Item was removed:
- ----- Method: TestCategoryEditor>>categoryOfChange: (in category 'accessing') -----
- categoryOfChange: element
- 	^ changes categoryOfElement: element!

Item was removed:
- TestCase subclass: #ClassEditorTest
- 	instanceVariableNames: 'editor'
- 	classVariableNames: ''
- 	poolDictionaries: ''
- 	category: 'SystemEditor-Tests'!

Item was removed:
- ----- Method: ClassEditorProtocolTest>>test23BeNormal (in category 'tests') -----
- test23BeNormal
- 	editor typeOfClass: #normal.
- 	self assert: editor typeOfClass == #normal.
- 	self assert: editor isPointers.
- 	self deny: editor isWords.
- 	self deny: editor isVariable.
- 	self deny: editor isWeak.
- 	self deny: editor isBits.
- !

Item was removed:
- ----- Method: MetaclassEditorProtocolTest>>test03RemoveInstVarName (in category 'tests') -----
- test03RemoveInstVarName
- 	editor removeInstVarName: 'omega'.
- 	self assert: editor instVarNames = (editor subject instVarNames copyWithout: 'omega')!

Item was removed:
- MetaclassEditorTest subclass: #MetaclassEditorProtocolTest
- 	instanceVariableNames: ''
- 	classVariableNames: ''
- 	poolDictionaries: ''
- 	category: 'SystemEditor-Tests'!

Item was removed:
- ----- Method: ClassEditorValidationTest>>test08InstVarNamedThisContext (in category 'tests') -----
- test08InstVarNamedThisContext
- 
- 	editor addInstVarName: 'thisContext'.
- 	self should: [editor validate] raise: IllegalVariableName.!

Item was removed:
- ----- Method: SystemEditorTest>>assertClassesAreMigrated: (in category 'asserting') -----
- assertClassesAreMigrated: classes 
- 	self assert: (self migratedClasses includesAllOf: classes)!

Item was removed:
- ----- Method: MethodDictionaryEditor>>includesSelector: (in category 'testing') -----
- includesSelector: aSymbol 
- 	(additions includesKey: aSymbol) ifTrue: [^ true].
- 	(removals includes: aSymbol) ifTrue: [^false].
- 	(self subject includesKey: aSymbol) ifTrue: [^ true].
- 	^ false!

Item was removed:
- ----- Method: CategorizerEditor>>changedElementsAndCategoriesSelect:thenCollect: (in category 'accessing changed elements') -----
- changedElementsAndCategoriesSelect: selectBlock thenCollect: collectBlock
- "Evaluates collectBlock for each added or recategorized element and its category for which selectBlock answers true. Answers an OrderedCollection of the results"
- 
- 	| newCollection |
- 	newCollection := OrderedCollection new.
- 	self changedElementsAndCategoriesDo: [:anElement :aCategory |
- 		(selectBlock value: anElement value: aCategory) ifTrue: [newCollection
- 			add: (collectBlock value: anElement value: aCategory)]].
- 	^ newCollection!

Item was removed:
- ----- Method: MethodDictionaryEditor>>buildFor: (in category 'editing') -----
- buildFor: aClassEditor
- 	| result old |
- 	result := MethodDictionary new.
- 	self subject keysAndValuesDo:
- 		[:selector :cm |
- 		(self selectorIsModified: selector)
- 			ifFalse: [result at: selector put: (self recompile: selector from: cm for: aClassEditor)]].
- 	additions keysAndValuesDo: 
- 		[:selector :mm | 
- 		old := self subject at: selector ifAbsent: [nil]. 
- 		result at: selector put: (mm compileFrom: old for: aClassEditor)].
- 	^ result
- !

Item was removed:
- ----- Method: OrganizationEditorTest>>test09EmptyCommentWrittenToChangesFile (in category 'tests') -----
- test09EmptyCommentWrittenToChangesFile
- 	| remote repository result |
- 	repository := SourceRepository newInternal.
- 	editor := OrganizationEditor for: (ClassEditor on: self class)
- 				repository: repository.
- 	editor classComment: '' stamp: 'cwp 12/11/2005 21:58'.
- 	result := editor edBuild.
- 	remote := result commentRemoteStr.
- 	self assertRemoteString: remote inRepository: repository matches: ''!

Item was removed:
- ----- Method: ClassEditorBuildTest>>test12MethodRecompilation (in category 'tests') -----
- test12MethodRecompilation
- 	
- 	| dict |
- 	editor addInstVarName: 'gamma'.
- 	dict := editor methodDictionary.
- 	self deny: (dict at: #het) == (editor subject compiledMethodAt: #het).
- !

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

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

Item was removed:
- ----- Method: TestCategoryEditor>>setSubject: (in category 'initialize-release') -----
- setSubject: aCategorizer
- 	super setSubject: aCategorizer.
- 	changes := Categorizer defaultList: Array new.
- 	removedElements := Set new!

Item was removed:
- ----- Method: SystemOrganizationEditor>>removedElements (in category 'accessing') -----
- removedElements
- 	^ system removals!

Item was removed:
- ----- 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 removed:
- ----- Method: PureBehaviorEditor>>edIsBehavior (in category 'testing') -----
- edIsBehavior
- "Answers true if I am an editor for a Behavior"
- 	^ false!

Item was removed:
- ----- Method: OrganizationEditorTest>>test04SetComment (in category 'tests') -----
- test04SetComment
- 	editor := OrganizationEditor for: EditorSubject.
- 	editor classComment: 'comment string' stamp: 'cwp 12/11/2005 21:58'.
- 	self assert: editor classComment = 'comment string'!

Item was removed:
- ----- Method: ClassFormat class>>indexed: (in category 'instance creation') -----
- indexed: size
- 	^ self 
- 		size: size
- 		spec: (self indexedSpec: size)
- 		index: 0!

Item was removed:
- ----- Method: SystemEditor>>edPrepareExport: (in category 'building') -----
- edPrepareExport: exporter
- 
- 	showProgress
- 		ifFalse:	[additions do: [:ea | ea edPrepareExport: exporter]]
- 		ifTrue:	[additions do: [:ea | ea edPrepareExport: exporter] displayingProgress: 'Preparing Classes...']!

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

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

Item was removed:
- ----- Method: ClassEditorProtocolTest>>test24CompileClassifiedWithStampNotifying (in category 'tests') -----
- test24CompileClassifiedWithStampNotifying
- 	self deny: (editor includesSelector: #zayin).
- 	editor 
- 		compile: 'zayin ^ 1'
- 		classified: 'numbers'
- 		withStamp: 'cwp 5/30/2004 09:27'
- 		notifying: nil.
- 	self assert: (editor includesSelector: #zayin)!

Item was removed:
- ----- Method: ClassEditorBuildTest>>test09ExistingMethods (in category 'tests') -----
- test09ExistingMethods
- 	
- 	| result |
- 	editor compile: 'waw ^ 3' classified: 'phoenician'.
- 	result := editor product.
- 	self assert: (result compiledMethodAt: #het) == (editor subject compiledMethodAt: #het)!

Item was removed:
- ----- Method: MetaclassEditor>>initialize (in category 'initialization') -----
- initialize
- "initialize myself so that I can create instances"
- 
- 	superclass := self class classClassEditor.
- 	methodDict := MethodDictionary new.
- 	format := superclass format.!

Item was removed:
- ----- Method: MetaclassEditorProtocolTest>>test05AddSelector (in category 'tests') -----
- test05AddSelector
- 	self deny: (editor includesSelector: #zayin).
- 	editor 
- 		compile: 'zayin ^ 1'
- 		classified: 'numbers'
- 		withStamp: 'cwp 5/30/2004 09:27'
- 		notifying: nil
- 		logSource: true.
- 	self assert: (editor includesSelector: #zayin)!

Item was removed:
- ----- Method: SystemEditor>>associationAt:ifAbsent: (in category 'reflecting') -----
- associationAt: aSymbol ifAbsent: aBlock
-  
- 	self at: aSymbol ifAbsent: [^ aBlock value]. "first create any editors necessary"
- 	^ additions associationAt: aSymbol
- 		ifAbsent: [subject associationAt: aSymbol]!

Item was removed:
- ----- Method: ClassEditorBuildTest>>test08RemoveSharedPool (in category 'tests') -----
- test08RemoveSharedPool
- 	
- 	| result |
- 	editor removeSharedPool: EditorSubjectPool.
- 	result := editor product.
- 	self deny: result == editor subject.
- 	self deny: (result sharedPools includes: EditorSubjectPool).
- 	self assert: (editor subject sharedPools includes: EditorSubjectPool).!

Item was removed:
- ----- Method: CategorizerEditor>>allMethodSelectors (in category 'reflecting - accessing') -----
- allMethodSelectors
- 	"give a list of all method selectors."
- 
- 	^ self elementArray copy sort!

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

Item was removed:
- ----- Method: ClassEditorOntologyTest>>test06Format (in category 'tests') -----
- test06Format
- 	"Despite having an instance variable called 'format' 
- 	MetaclassEditors should answer the format of the 
- 	subject's metaclass, not the format of ClassEditor class."
- 
- 	self assert: editor class format = EditorSubject class format!

Item was removed:
- ----- Method: PureBehaviorEditor>>edDependentsDo: (in category 'building') -----
- edDependentsDo: aBlock
- "Find any editors that should be modified because of me, inform them if necessary, then send them to aBlock"
- 	self decoratorsDo: [:ea | ea edDependentsDo: aBlock]!

Item was removed:
- ----- Method: ClassEditorBuildTest>>test06PreserveClassVar (in category 'tests') -----
- test06PreserveClassVar
- 	
- 	| result object |
- 	object := Object new.
- 	editor removeClassVarName: 'Beth'.
- 	editor subject aleph: object.
- 	result := editor product.
- 	self deny: result == editor subject.
- 	self assert: result aleph == object!

Item was removed:
- ----- Method: ClassEditorOntologyTest>>test07MetaSuperclass (in category 'tests') -----
- test07MetaSuperclass
- 	"MetaclassEditor's ivar called 'superclass' should point to ClassEditor,
- 	but the method #superclass return an editor on the superclass of the
- 	editor's subject."
- 
- 	self assert: editor class superclass subject == EditorSubject class superclass!

Item was removed:
- ----- Method: ClassEditorProtocolTest>>test37ClassVariablesString (in category 'tests') -----
- test37ClassVariablesString
- 
- 	self assert: editor classVariablesString = editor subject classVariablesString!

Item was removed:
- Object subclass: #SourceRepository
- 	instanceVariableNames: 'files'
- 	classVariableNames: ''
- 	poolDictionaries: ''
- 	category: 'SystemEditor-Squeak'!
- 
- !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 removed:
- ----- Method: ClassEditorBuildTest>>test13NoSubject (in category 'tests') -----
- test13NoSubject
- 	
- 	| result |
- 	editor := ClassEditor forNewClassNamed: #EditorSubject2.
- 	result := editor product.
- 	self assert: result name = #EditorSubject2!

Item was removed:
- ----- 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 removed:
- ----- Method: RootMetaclassEditor>>withAllSuperclassesDo: (in category 'reflecting') -----
- withAllSuperclassesDo: aBlock
- 	^ self!

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

Item was removed:
- ----- Method: MetaclassEditor class>>classRootEditor (in category 'instance creation') -----
- classRootEditor
- "Answer the class of editors for the root of my heiarchy"
- 
- 	^ RootMetaclassEditor!

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

Item was removed:
- ----- Method: CategorizerEditor>>changedElements (in category 'accessing changed elements') -----
- changedElements
- "Answers the list of elements that have been added or recategorized"
- 
- 	^ self changedElementsAndCategoriesCollect: [:anElement :aCategory | anElement]!

Item was removed:
- ----- Method: ClassFormat class>>indexed (in category 'instance creation') -----
- indexed
- 	^ self indexed: 0!

Item was removed:
- ----- 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 subclassesOrEditors do: [ :class | (class instVarNames includes: ea) ifTrue: [ IllegalVariableName signal ] ] ]!

Item was removed:
- ----- Method: ClassEditorBuildTest>>test11MethodAdded (in category 'tests') -----
- test11MethodAdded
- 	
- 	| dict selector |
- 	selector := editor 
- 				compile: 'zayin ^ 2'
- 				classified: 'numbers'
- 				withStamp: 'cwp 5/30/2004 09:27'
- 				notifying: nil
- 				logSource: true.
- 	dict := editor methodDictionary.
- 	self deny: editor edRequiresBuild.
- 	self assert: (dict at: #zayin) isCompiledMethod.
- 	self assert: selector == #zayin
- !



More information about the Packages mailing list