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

squeak-dev-noreply at lists.squeakfoundation.org squeak-dev-noreply at lists.squeakfoundation.org
Tue Oct 14 06:31:06 UTC 2008


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

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

Name: SystemEditor-mtf.136
Author: mtf
Time: 13 October 2008, 11:31:58 pm
UUID: bf506d66-56e2-4ecb-95b4-7163a69ad730
Ancestors: SystemEditor-mtf.135

Some more reflection to support compiling and running code in the context of a SystemEditor. See SystemEditor >> doItHost. This was implemented in order to interpret trait composition strings

=============== Diff against SystemEditor-mtf.135 ===============

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

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

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

Item was changed:
  ----- 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)
- 	(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 added:
+ ----- 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 superclassOrEditor == anEditor ifTrue: [aBlock value: ea]].
+ 	removals do: [ :removedKey | subclasses remove: (subject at: removedKey) ifAbsent: []].
+ 	subclasses do: aBlock!

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

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

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

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

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

Item was added:
+ ----- 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 added:
+ ----- Method: ClassDescriptionEditor>>withAllSuperclassesDo: (in category 'reflecting') -----
+ withAllSuperclassesDo: aBlock 
+ "Evaluate aBlock for each of my receiver superclasses."
+ 
+ 	aBlock value: self.
+ 	self allSuperclassesDo: aBlock!

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

Item was changed:
  ----- 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]!
- 	self isDebuggingAsEditor ifTrue: [^ super instVarNames].
- 	^ instVarNames ifNil: [self subject instVarNames]!

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

Item was changed:
  ----- 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]!
- 	self isDebuggingAsEditor ifTrue: [^ super instSize].
- 	^ self instVarNames size + self superclassOrEditor instSize!

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

Item was changed:
  ----- 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 subject superclass ifNil: [^ self class classRootEditor on: nil for: self environment].
  	^ self environment classOrEditorFor: self subject superclass!

Item was added:
+ ----- 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 added:
+ ----- Method: PureBehaviorEditor>>binding (in category 'reflecting') -----
+ binding
+ 	^ nil -> self!

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

Item was added:
+ ----- 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 changed:
  ----- Method: PureBehaviorEditor>>parserClass (in category 'reflecting') -----
  parserClass
+ 	^ self subject 
+ 		ifNil: [Parser]
+ 		ifNotNil: [self subject parserClass]!
- 	^ self class parserClass!

Item was changed:
  ----- 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]!
- 	
- 	self isDebuggingAsEditor ifTrue: [^ super allInstVarNames].
- 	^ self edSuperclass
- 		ifNil: [self instVarNames copy]
- 		ifNotNil: [self edSuperclass allInstVarNames, self instVarNames]!

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

Item was changed:
  ----- 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.!
- 	format := self class classClassEditor format.!

Item was added:
+ ----- Method: RootMetaclassEditor>>withAllSuperclassesDo: (in category 'reflecting') -----
+ withAllSuperclassesDo: aBlock
+ 	^ self!

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

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

Item was removed:
- ----- Method: ClassEditor>>printOn: (in category 'printing') -----
- printOn: aStream
- 	aStream 
- 		nextPutAll: 'a ClassEditor on: ';
- 		nextPutAll: subject name!

Item was removed:
- ----- Method: MetaclassEditor>>basicNew (in category 'initialization') -----
- 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: RootMetaclassEditor>>allSuperclasses (in category 'reflecting') -----
- allSuperclasses
- 	^ OrderedCollection new!



More information about the Packages mailing list