[Vm-dev] VM Maker: VMMaker.oscog-eem.2873.mcz

commits at source.squeak.org commits at source.squeak.org
Tue Nov 10 00:54:38 UTC 2020


Eliot Miranda uploaded a new version of VMMaker to project VM Maker:
http://source.squeak.org/VMMaker/VMMaker.oscog-eem.2873.mcz

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

Name: VMMaker.oscog-eem.2873
Author: eem
Time: 9 November 2020, 4:54:28.78066 pm
UUID: 0d03b37a-cec9-44cc-b9b8-abace901cd20
Ancestors: VMMaker.oscog-eem.2872

COGMTVM: The Slang change to super sends won't work.  Use a clumsier approach.

=============== Diff against VMMaker.oscog-eem.2872 ===============

Item was changed:
  ----- Method: CoInterpreterMT>>restoreVMStateFor:threadIndexAndFlags: (in category 'vm scheduling') -----
  restoreVMStateFor: vmThread threadIndexAndFlags: threadIndexAndFlags
  	"We've been preempted; we must restore state and update the threadId
  	 in our process, and may have to put the active process to sleep."
  	| sched activeProc myProc |
  	sched := self schedulerPointer.
  	activeProc := objectMemory fetchPointer: ActiveProcessIndex ofObject: sched.
  	(threadIndexAndFlags anyMask: OwnVMForeignThreadFlag)
  		ifTrue:
  			[self assert: foreignCallbackProcessSlot == ForeignCallbackProcess.
  			 myProc := objectMemory splObj: foreignCallbackProcessSlot.
  			self assert: myProc ~= objectMemory nilObject.
  			objectMemory splObj: foreignCallbackProcessSlot put: objectMemory nilObject]
  		ifFalse: [myProc := cogThreadManager popAWOLProcess: vmThread].
  	self assert: activeProc ~= myProc.
  	(activeProc ~= objectMemory nilObject
  	 and: [(objectMemory fetchPointer: MyListIndex ofObject: activeProc) = objectMemory nilObject]) ifTrue:
  		[self putToSleep: activeProc yieldingIf: preemptionYields].
  	self assert: (objectMemory fetchPointer: MyListIndex ofObject: myProc) = (objectMemory splObj: ProcessInExternalCodeTag).
  	objectMemory
  		storePointer: ActiveProcessIndex ofObject: sched withValue: myProc;
  		storePointerUnchecked: MyListIndex ofObject: myProc withValue: objectMemory nilObject.
  	"Only unaffine if the process was affined at this level and did not become bound in the interim."
  	((threadIndexAndFlags anyMask: ProcessUnaffinedOnDisown)
  	 and: [(self isBoundProcess: myProc) not]) ifTrue:
  		[self setOwnerIndexOfProcess: myProc to: 0 bind: false].
  	self initPrimCall.
+ 	self cCode:
+ 			[self externalSetStackPageAndPointersForSuspendedContextOfProcess: myProc]
+ 		inSmalltalk:
+ 			["Bypass the no-offset stack depth check in the simulator's externalSetStackPageAndPointersForSuspendedContextOfProcess:"
+ 			 super externalSetStackPageAndPointersForSuspendedContextOfProcess: myProc.
+ 			 "We're in ownVM:, hence in a primitive, hence need to include the argument count"
+ 			 (self isMachineCodeFrame: framePointer) ifTrue:
+ 				[self maybeCheckStackDepth: vmThread argumentCount
+ 					sp: stackPointer
+ 					pc: instructionPointer]].
- 	"Bypass the no-offset stack depth check in the simulator's externalSetStackPageAndPointersForSuspendedContextOfProcess:"
- 	super externalSetStackPageAndPointersForSuspendedContextOfProcess: myProc.
- 	"We're in ownVM:, hence in a primitive, hence need to include the argument count"
- 	(self isMachineCodeFrame: framePointer) ifTrue:
- 		[self maybeCheckStackDepth: vmThread argumentCount
- 			sp: stackPointer
- 			pc: instructionPointer].
  	"If this primitive is called from machine code maintain the invariant that the return pc
  	 of an interpreter callee calling a machine code caller is ceReturnToInterpreterPC."
  	(vmThread inMachineCode
  	 and: [instructionPointer >= objectMemory startOfMemory]) ifTrue:
  		[self iframeSavedIP: framePointer put: instructionPointer.
  		 instructionPointer := cogit ceReturnToInterpreterPC].
  	newMethod := vmThread newMethodOrNull.
  	argumentCount := vmThread argumentCount.
  	primitiveFunctionPointer := vmThread primitiveFunctionPointer.
  	vmThread newMethodOrNull: nil.
  	self cCode: '' inSmalltalk:
  		[| range |
  		 range := self cStackRangeForThreadIndex: vmThread index.
  		 self assert: ((range includes: vmThread cStackPointer) and: [range includes: vmThread cFramePointer])].
  	self setCFramePointer: vmThread cFramePointer setCStackPointer: vmThread cStackPointer.
  	self assert: newMethod notNil
  !

Item was changed:
  ----- Method: MessageNode>>asTranslatorNodeIn: (in category '*VMMaker-C translation') -----
  asTranslatorNodeIn: aTMethod
  	"Answer a TParseNode subclass equivalent of me"
  	"selector is sometimes a Symbol, sometimes a SelectorNode!!
  	 On top of this, numArgs is needed due to the (truly grody) use of
  	 arguments as a place to store the extra expressions needed to generate
  	 code for in-line to:by:do:, etc.  see below, where it is used.
  
  	 Expand super nodes in place. Elide sends of halt so that halts can be
  	 sprinkled through the simulator but will be eliminated from the generated C."
  	| rcvrOrNil sel args ifNotNilBlock |
  	rcvrOrNil := receiver ifNotNil: [receiver asTranslatorNodeIn: aTMethod].
  	(rcvrOrNil notNil
  	and: [rcvrOrNil isVariable
+ 	and: [rcvrOrNil name = 'super']]) ifTrue:
- 	and: [rcvrOrNil name = 'super'
- 	and: [aTMethod selector == selector key]]]) ifTrue:
  		[^aTMethod superExpansionNodeFor: selector key args: arguments].
  	sel := selector isSymbol ifTrue: [selector] ifFalse: [selector key].
  	sel == #halt ifTrue: [^rcvrOrNil].
  	(sel == #cCode:inSmalltalk: "extracting here rather than in translation allows inlining in the block."
  	  or: [sel == #cCode:]) ifTrue:
  		[arguments first isBlockNode ifTrue:
  			[| block |
  			 ^(block := arguments first asTranslatorNodeIn: aTMethod) statements size = 1
  				ifTrue: [block statements first]
  				ifFalse: [block]].
  		 (arguments first isLiteralNode
  		 and: [arguments first key isString
  		 and: [arguments first key isEmpty]]) ifTrue:
  			[^arguments first asTranslatorNodeIn: aTMethod]].
  	args := arguments
  				select: [:arg| arg notNil]
  				thenCollect: [:arg| arg asTranslatorNodeIn: aTMethod].
  	(sel = #to:by:do: and: [arguments size = 7 and: [(arguments at: 7) notNil]]) ifTrue:
  		["Restore limit expr that got moved by transformToDo:"
  		 args := {(arguments at: 7) value asTranslatorNodeIn: aTMethod. 
  				  args second.
  				  args third. "add the limit var as a hidden extra argument; we may need it later"
  				  TVariableNode new setName: arguments first key}].
  	(sel == #ifTrue:ifFalse: and: [arguments first isJust: NodeNil]) ifTrue:
  		[sel := #ifFalse:. args := {args last}].
  	(sel == #ifTrue:ifFalse: and: [arguments last isJust: NodeNil]) ifTrue:
  		[sel := #ifTrue:. args := {args first}].
  	(sel == #ifFalse:ifTrue: and: [arguments first isJust: NodeNil]) ifTrue:
  		[sel := #ifTrue:. args := {args last}].
  	(sel == #ifFalse:ifTrue: and: [arguments last isJust: NodeNil]) ifTrue:
  		[sel := #ifTrue:. args := {args first}].
  	((sel == #ifFalse: or: [sel == #or:])
  	 and: [arguments size = 2 and: [(arguments at: 2) notNil]]) ifTrue:
  		["Restore argument block that got moved by transformOr: or transformIfFalse:"
  		 args := {(arguments at: 2) asTranslatorNodeIn: aTMethod}].
  	(args size > sel numArgs and: [sel ~~ #to:by:do:]) ifTrue: "to:by:do: has iLimiT hidden in last arg"
  		["prune the extra blocks left by ifTrue:, ifFalse:, and: & or:"
  		 self assert: args size - sel numArgs = 1.
  		 self assert: (args last isStmtList
  					  and: [args last statements size = 1
  					  and: [(args last statements first isVariable
  							or: [args last statements first isConstant])
  					  and: [#('nil' true false) includes: args last statements first nameOrValue]]]).
  		 args := args first: sel numArgs].
  	"For the benefit of later passes, e.g. value: inlining,
  	 transform e ifNotNil: [:v| ...] into  v := e. v ifNotNil: [...],
  	 which in fact means transforming (v := e) ifTrue: [:v|...] into v := e. v ifTrue: [...]."
  	((sel == #ifTrue: or: [sel == #ifFalse: or: [sel == #ifTrue:ifFalse: or: [sel == #ifFalse:ifTrue:]]])
  	 and: [receiver notNil
  	 and: [receiver isAssignmentEqualsEqualsNil
  	 and: [(ifNotNilBlock := args detect: [:arg| arg isStmtList and: [arg args size = 1]] ifNone: []) notNil]]]) ifTrue:
  		[ifNotNilBlock setArguments: #().
  		 ^TStmtListNode new
  			setArguments: #()
  			statements:
  				{	receiver receiver asTranslatorNodeIn: aTMethod.
  					TSendNode new
  						setSelector: sel
  						receiver: (TSendNode new
  									setSelector: #==
  									receiver: (receiver receiver variable asTranslatorNodeIn: aTMethod)
  									arguments: {receiver arguments first asTranslatorNodeIn: aTMethod})
  						arguments: args }].
  	((CCodeGenerator isVarargsSelector: sel)
  	 and: [args last isCollection
  	 and: [args last isSequenceable]]) ifTrue:
  		[args := args allButLast, args last].
  	^TSendNode new
  		setSelector: sel
  		receiver: rcvrOrNil
  		arguments: args!



More information about the Vm-dev mailing list