[squeak-dev] The Trunk: EToys-dtl.315.mcz

commits at source.squeak.org commits at source.squeak.org
Fri Dec 1 00:38:18 UTC 2017


David T. Lewis uploaded a new version of EToys to project The Trunk:
http://source.squeak.org/trunk/EToys-dtl.315.mcz

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

Name: EToys-dtl.315
Author: dtl
Time: 29 November 2017, 9:45:42.436285 pm
UUID: 877a21b3-739f-4c05-8bec-bb5a153d1dbe
Ancestors: EToys-dtl.314

SyntaxMorph requires asMorphicSyntaxIn: and related methods from the ParseNode hierarchy. This update adds the missing methods imported from the Etoys development image.

SyntaxMorph class>>testAll exposes some problems in these earlier ParseNode methods, and this probably reflects updates that will be required to match the various compiler improvements in Squeak since the original SyntaxMorph implementation.

=============== Diff against EToys-dtl.314 ===============

Item was added:
+ ----- Method: AssignmentNode>>asMorphicSyntaxIn: (in category '*Etoys-tiles') -----
+ asMorphicSyntaxIn: parent
+ 
+ 	^parent assignmentNode: self variable: variable value: value!

Item was added:
+ ----- Method: BlockNode>>asMorphicCollectSyntaxIn: (in category '*Etoys-tiles') -----
+ asMorphicCollectSyntaxIn: parent
+ 
+ 	^parent 
+ 		blockNodeCollect: self 
+ 		arguments: arguments 
+ 		statements: statements!

Item was added:
+ ----- Method: BlockNode>>asMorphicSyntaxIn: (in category '*Etoys-tiles') -----
+ asMorphicSyntaxIn: parent
+ 
+ 	^parent 
+ 		blockNode: self 
+ 		arguments: arguments 
+ 		statements: statements!

Item was added:
+ ----- Method: BraceNode>>asMorphicSyntaxIn: (in category '*Etoys-tiles') -----
+ asMorphicSyntaxIn: parent
+ 
+ 	| row |
+ 
+ 	row _ (parent addRow: #brace on: self) layoutInset: 1.
+ 	row addMorphBack: (StringMorph new contents: 
+ 		(String streamContents: [:aStream | self printOn: aStream indent: 0])).
+ 	^row
+ !

Item was added:
+ ----- Method: CascadeNode>>asMorphicSyntaxIn: (in category '*Etoys-tiles') -----
+ asMorphicSyntaxIn: parent
+ 
+ 	^parent
+ 		cascadeNode: self 
+ 		receiver: receiver 
+ 		messages: messages
+ !

Item was added:
+ ----- Method: LiteralNode>>asMorphicSyntaxIn: (in category '*Etoys-tiles') -----
+ asMorphicSyntaxIn: parent
+ 
+ 	| row |
+ 
+ 	row _ parent addRow: #literal on: self.
+ 	(key isVariableBinding) ifFalse: [
+ 		row layoutInset: 1.
+ 		^ row addMorphBack: (row addString: key storeString special: false)].
+ 	key key isNil ifTrue: [
+ 		^ row addTextRow: ('###',key value soleInstance name)
+ 	] ifFalse: [
+ 		^ row addTextRow: ('##', key key)
+ 	].	!

Item was added:
+ ----- Method: MessageNode>>asMorphicSyntaxIn: (in category '*Etoys-tiles') -----
+ asMorphicSyntaxIn: parent
+ 
+ 	^parent 
+ 		vanillaMessageNode: self 
+ 		receiver: receiver 
+ 		selector: selector 
+ 		arguments: arguments
+ !

Item was added:
+ ----- Method: MessageNode>>morphFromKeywords:arguments:on:indent: (in category '*Etoys-tiles') -----
+ morphFromKeywords: key arguments: args on: parent indent: ignored
+ 
+ 	^parent
+ 		messageNode: self 
+ 		receiver: receiver 
+ 		selector: selector 
+ 		keywords: key 
+ 		arguments: args
+ !

Item was added:
+ ----- Method: MethodNode>>asMorphicSyntaxIn: (in category '*Etoys-tiles') -----
+ asMorphicSyntaxIn: parent
+ 	
+ 	^parent
+ 		methodNodeInner: self 
+ 		selectorOrFalse: selectorOrFalse 
+ 		precedence: precedence 
+ 		arguments: arguments 
+ 		temporaries: temporaries 
+ 		primitive: primitive 
+ 		block: block
+ !

Item was added:
+ ----- Method: MethodNode>>asMorphicSyntaxUsing: (in category '*Etoys-tiles') -----
+ asMorphicSyntaxUsing: aClass
+ 	
+ 	^ Cursor wait showWhile: [
+ 		(aClass methodNodeOuter: self) finalAppearanceTweaks]
+ 		!

Item was added:
+ ----- Method: MorphicProject>>setWorld: (in category '*Etoys-Worlds') -----
+ setWorld: aWorld
+ 	world := aWorld.
+ 	Smalltalk globals at: #World
+ 		ifPresent: [ :w | Smalltalk globals at: #World put: world ].
+ !

Item was added:
+ ----- Method: ParseNode>>asMorphicSyntaxIn: (in category '*Etoys-tiles') -----
+ asMorphicSyntaxIn: parent
+ 
+ 	| morph |
+ 	"Default for missing implementations"
+ 
+ 	morph _ parent addColumn: #error on: self.
+ 	morph addTextRow: self class printString.
+ 	^morph
+ 	
+ 
+ !

Item was added:
+ ----- Method: ReturnNode>>asMorphicSyntaxIn: (in category '*Etoys-tiles') -----
+ asMorphicSyntaxIn: parent
+ 
+ 	^parent returnNode: self expression: expr
+ !

Item was added:
+ ----- Method: TempVariableNode>>asMorphicSyntaxIn: (in category '*Etoys-tiles') -----
+ asMorphicSyntaxIn: parent
+ 
+ 	^ parent addToken: self name type: #tempVariable on: self!

Item was added:
+ ----- Method: VariableNode>>asMorphicSyntaxIn: (in category '*Etoys-tiles') -----
+ asMorphicSyntaxIn: parent
+ 
+ 	^ parent addToken: self name
+ 			type: #variable 
+ 			on: self clone	"don't hand out the prototype!! See VariableNode>>initialize"
+ !

Item was added:
+ ----- Method: VariableNode>>currentValueIn: (in category '*Etoys-tiles') -----
+ currentValueIn: aContext
+ 
+ 	aContext ifNil: [^nil].
+ 	^((self variableGetterBlockIn: aContext) ifNil: [^nil]) value printString
+ 	
+ 
+ !

Item was added:
+ ----- Method: VariableNode>>variableGetterBlockIn: (in category '*Etoys-tiles') -----
+ variableGetterBlockIn: aContext
+ 
+ 	| temps index ivars |
+ 
+ 	(self type = 4 and: [self key isVariableBinding]) ifTrue: [
+ 		^[self key value]
+ 	].
+ 	aContext ifNil: [^nil].
+ 	self isSelfPseudoVariable ifTrue: [^[aContext receiver]].
+ 	self type = 1 ifTrue: [
+ 		ivars _ aContext receiver class allInstVarNames.
+ 		index _ ivars indexOf: self name ifAbsent: [^nil].
+ 		^[aContext receiver instVarAt: index]
+ 	].
+ 	self type = 2 ifTrue: [
+ 		temps _ aContext tempNames.
+ 		index _ temps indexOf: self name ifAbsent: [^nil].
+ 		^[aContext tempAt: index]
+ 	].
+ 	^nil
+ !



More information about the Squeak-dev mailing list