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

commits at source.squeak.org commits at source.squeak.org
Mon Dec 16 06:28:36 UTC 2019


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

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

Name: VMMaker.oscog-eem.2615
Author: eem
Time: 15 December 2019, 10:28:19.693105 pm
UUID: b8e6e486-cd05-49d3-a689-7fdc05fc6176
Ancestors: VMMaker.oscog-eem.2614

Cogit: refactor stack overflow checking into the compileStackOverflowCheck: routine. Provide CogAbstractInstruction>>hasCmpRSPReg tio allow a backend to stipulate that the stack check occurs in reverse (CmpR: SPReg R: TempReg, as opposed to CmpR: TempReg R: SPReg).

Simulation:
Cogit: Eliminate all the inMemoryCFrame/StackPointerAddress code.  It breaks simulation with xchg rax,rsp, which will stomp on rax (TempReg) that passes the class oop in a directed super send.
CogAbstractInstruction>>printStateOn: must only look up integer operands, not e.g. labels.
Plugins: Fix an integer overflow bug in BalloonArray>>bitsOf: (C silently truncates; so should bitsOf:).

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

Item was changed:
  ----- Method: BalloonArray>>bitsOf: (in category 'memory access') -----
  bitsOf: value
  	"Convert pos and neg ints and floats to 32-bit representations expected by C"
- 
  	value isInteger ifTrue:
+ 		[^(value >= 0
+ 			ifTrue: [value]
+ 			ifFalse: [value + 16r80000000 + 16r80000000])  bitAnd: 16rFFFFFFFF].
- 		[value >= 0 ifTrue: [^ value].
- 		^ value + 16r80000000 + 16r80000000].
  	value isFloat ifTrue:
+ 		[^value asIEEE32BitWord].
- 		[^ value asIEEE32BitWord].
  	self error: 'unexpected value for 32 bits'.
+ 	^0!
- 	^ 0!

Item was changed:
  ----- Method: CoInterpreter>>cFramePointerAddress (in category 'cog jit support') -----
  cFramePointerAddress
  	<api>
+ 	^self
+ 		cCode: [self addressOf: CFramePointer]
+ 		inSmalltalk: [cogit simulatedReadWriteVariableAddress: #getCFramePointer in: self]!
- 	^self cCode: [self addressOf: CFramePointer] inSmalltalk: [self error: 'Use Cogit''s version  when simulating']!

Item was changed:
  ----- Method: CoInterpreter>>cStackPointerAddress (in category 'cog jit support') -----
  cStackPointerAddress
  	<api>
+ 	^self
+ 		cCode: [self addressOf: CStackPointer]
+ 		inSmalltalk: [cogit simulatedReadWriteVariableAddress: #getCStackPointer in: self]!
- 	^self cCode: [self addressOf: CStackPointer] inSmalltalk: [self error: 'Use Cogit''s version  when simulating']!

Item was changed:
  ----- Method: CoInterpreter>>setCFramePointer:setCStackPointer: (in category 'callback support') -----
  setCFramePointer: cFramePointer setCStackPointer: cStackPointer
  	<inline: #always>
  	CStackPointer := cStackPointer.
+ 	CFramePointer := cFramePointer!
- 	CFramePointer := cFramePointer.
- 	self cCode: [] inSmalltalk:
- 		[objectMemory
- 			longAt: self inMemoryCFramePointerAddress
- 				put: cFramePointer;
- 			longAt: self inMemoryCStackPointerAddress
- 				put: cStackPointer]!

Item was removed:
- ----- Method: CogARMCompiler>>genLoadCStackPointer (in category 'smalltalk calling convention') -----
- genLoadCStackPointer
- 	"Load the stack pointer register with that of the C stack, effecting
- 	 a switch to the C stack.  Used when machine code calls into the
- 	 CoInterpreter run-time (e.g. to invoke interpreter primitives)."
- 	cogit MoveAw: cogit cStackPointerAddress R: SPReg.
- 	^0!

Item was changed:
  ----- Method: CogAbstractInstruction>>genLoadCStackPointer (in category 'smalltalk calling convention') -----
  genLoadCStackPointer
  	"Load the stack pointer register with that of the C stack, effecting
  	 a switch to the C stack.  Used when machine code calls into the
  	 CoInterpreter run-time (e.g. to invoke interpreter primitives)."
+ 	cogit MoveAw: cogit cStackPointerAddress R: SPReg.
+ 	^0!
- 	self subclassResponsibility!

Item was added:
+ ----- Method: CogAbstractInstruction>>hasCmpRSPReg (in category 'testing') -----
+ hasCmpRSPReg
+ 	"Answer if the receiver can do CmpR: anyRegExceptSP R: SPReg.
+ 	 If the answerr is false the Cogit assumes that the receiver can do CmpR: SPReg R: anyRegExceptSP.
+ 	 The back end has to do one or the other, by hook or by crook."
+ 	^true!

Item was changed:
  ----- Method: CogAbstractInstruction>>printStateOn: (in category 'printing') -----
  printStateOn: aStream
  	| opcodeName orneryOperands format |
  	<doNotGenerate> "Smalltalk-side only"
  	opcode ifNil:
  		[^self].
  	aStream space; nextPut: $(; nextPutAll: (opcodeName := self class nameForOpcode: opcode).
  	orneryOperands := operands isCObjectAccessor
  							ifTrue: [operands object]
  							ifFalse: [operands].
  	format := ((CogRTLOpcodes classPool includesKey: opcodeName)
  				ifTrue: [CogRTLOpcodes]
  				ifFalse: [self class]) printFormatForOpcodeName: opcodeName.
  	orneryOperands withIndexDo:
  		[:operand :index|
  		operand ifNotNil:
  			[aStream space.
  			 index >= (orneryOperands identityIndexOf: nil ifAbsent: [orneryOperands size + 1]) ifTrue:
  				[aStream print: index - 1; nextPut: $:].
  			 (format notNil and: ['rf' includes: (format at: index ifAbsent: $-)])
  				ifTrue: [aStream nextPutAll: ((format at: index) = $r
  												ifTrue: [self nameForRegister: operand]
  												ifFalse: [self nameForFPRegister: operand])]
  				ifFalse:
  					[| operandNameOrNil |
+ 					 operandNameOrNil := operand isInteger ifTrue:
+ 												[(cogit coInterpreter lookupAddress: operand) ifNil:
+ 													[objectMemory lookupAddress: operand]].
- 					 operandNameOrNil := (cogit coInterpreter lookupAddress: operand) ifNil: [objectMemory lookupAddress: operand].
  					 operandNameOrNil ifNotNil: [aStream nextPut: ${].
  					 aStream print: operand.
  					 (operand isInteger and: [operand > 16 and: [opcode ~= Label]]) ifTrue:
  						[objectMemory wordSize = 8
  							ifTrue:
  								[(operand allMask: 1 << 63) ifTrue:
  									[aStream nextPut: $/; print: operand signedIntFromLong64]]
  							ifFalse:
  								[(operand allMask: 1 << 31) ifTrue:
  									[aStream nextPut: $/; print: operand signedIntFromLong]].
  						 aStream nextPut: $/.
  						 operand printOn: aStream base: 16.
  						 operandNameOrNil ifNotNil:
  							[aStream nextPut: $=; nextPutAll: operandNameOrNil; nextPut: $}]]]]].
  	machineCodeSize ifNotNil:
  		[(machineCodeSize between: 1 and: machineCode size) ifTrue:
  			[0 to: machineCodeSize - 1 by: self codeGranularity do:
  				[:i|
  				 aStream space.
  				 (self machineCodeAt: i)
  					ifNil: [aStream nextPut: $.]
  					ifNotNil:
  						[:mc|
  						mc isInteger
  							ifTrue: [mc printOn: aStream base: 16]
  							ifFalse: [mc printOn: aStream]]]]].
  	address ifNotNil:
  		[aStream space; nextPut: $@.
  		 address printOn: aStream base: 16].
  	aStream nextPut: $)!

Item was removed:
- ----- Method: CogIA32Compiler>>genLoadCStackPointer (in category 'smalltalk calling convention') -----
- genLoadCStackPointer
- 	"Load the stack pointer register with that of the C stack, effecting
- 	 a switch to the C stack.  Used when machine code calls into the
- 	 CoInterpreter run-time (e.g. to invoke interpreter primitives)."
- 	cogit MoveAw: cogit cStackPointerAddress R: SPReg.
- 	^0!

Item was removed:
- ----- Method: CogMIPSELCompiler>>genLoadCStackPointer (in category 'smalltalk calling convention') -----
- genLoadCStackPointer
- 	"Load the stack pointer register with that of the C stack, effecting
- 	 a switch to the C stack.  Used when machine code calls into the
- 	 CoInterpreter run-time (e.g. to invoke interpreter primitives)."
- 	cogit MoveAw: cogit cStackPointerAddress R: SPReg.
- 	^0!

Item was removed:
- ----- Method: CogVMSimulator>>inMemoryCFramePointerAddress (in category 'rump c stack') -----
- inMemoryCFramePointerAddress
- 	^self rumpCStackAddress - 16!

Item was removed:
- ----- Method: CogVMSimulator>>inMemoryCStackPointerAddress (in category 'initialization') -----
- inMemoryCStackPointerAddress
- 	^self rumpCStackAddress - 8!

Item was removed:
- ----- Method: CogX64Compiler>>genLoadCStackPointer (in category 'smalltalk calling convention') -----
- genLoadCStackPointer
- 	"Load the stack pointer register with that of the C stack, effecting
- 	 a switch to the C stack.  Used when machine code calls into the
- 	 CoInterpreter run-time (e.g. to invoke interpreter primitives)."
- 	cogit MoveAw: cogit cStackPointerAddress R: SPReg.
- 	^0!

Item was changed:
  ----- Method: Cogit>>cFramePointerAddress (in category 'trampoline support') -----
  cFramePointerAddress
- 	"Real VM's version is in CoInterpreter"
  	<doNotGenerate>
+ 	^coInterpreter cFramePointerAddress!
- 	^(backEnd wantsNearAddressFor: #CFramePointer)
- 		ifTrue: [self simulatedReadWriteVariableAddress: #getCFramePointer in: coInterpreter]
- 		ifFalse: [coInterpreter inMemoryCFramePointerAddress]!

Item was changed:
  ----- Method: Cogit>>cStackPointerAddress (in category 'trampoline support') -----
  cStackPointerAddress
- 	"Real VM's version is in CoInterpreter"
  	<doNotGenerate>
+ 	^coInterpreter cStackPointerAddress!
- 	^(backEnd wantsNearAddressFor: #CStackPointer)
- 		ifTrue: [self simulatedReadWriteVariableAddress: #getCStackPointer in: coInterpreter]
- 		ifFalse: [coInterpreter inMemoryCStackPointerAddress]!

Item was added:
+ ----- Method: Cogit>>compileStackOverflowCheck: (in category 'compile abstract instructions') -----
+ compileStackOverflowCheck: canContextSwitch
+ 	"Compile the compare of stackLimit against the stack pointer, jumping to the stackOverflowCall if
+ 	 the stack pointer is below the limit.  Answer a bytecode annotated label that follows the sequence.
+ 
+ 	 The stack check functions both as a genuine stack limit check to prevent calls overflowing stack pages,
+ 	 and as an event/context-switch break out.  To cause an event check (including a check for a required
+ 	 context switch), stackLimit is set to the highest possible value, and hence all stack limit checks will
+ 	 fail.  A path in the stack overflow abort then arranges to call event checking if it has been requested.
+ 
+ 	 Certain block activations (e.g. valueNoContextSwitch:) must not context switch, and in that
+ 	 case, SendNumArgs is set to zero to communicate to the stack overflow abort that it should
+ 	 not perform event/context-switch (yet).
+ 
+ 	 A further complication is that certain back ends (currently ARMv8) can only do
+ 	 CmpR: SPReg R: TempReg and not CmpR: TempReg R: SPReg"
+ 
+ 	| jumpSkip label |
+ 	<inline: false>
+ 	self MoveAw: coInterpreter stackLimitAddress R: TempReg.
+ 	backEnd hasCmpRSPReg
+ 		ifTrue:
+ 			[self CmpR: TempReg R: SPReg. "N.B. FLAGS := SPReg - TempReg"
+ 			"If we can't context switch for this method, use a slightly
+ 			 slower overflow check that clears SendNumArgsReg."
+ 			canContextSwitch
+ 				ifTrue:
+ 					[self JumpBelow: stackOverflowCall.
+ 					 label := self Label]
+ 				ifFalse:
+ 					[jumpSkip := self JumpAboveOrEqual: 0.
+ 					 self MoveCq: 0 R: SendNumArgsReg.
+ 					 self Jump: stackOverflowCall.
+ 					 jumpSkip jmpTarget: (label := self Label)]]
+ 		ifFalse:
+ 			[self CmpR: SPReg R: TempReg. "N.B. FLAGS := TempReg - SPReg"
+ 			"If we can't context switch for this method, use a slightly
+ 			 slower overflow check that clears SendNumArgsReg."
+ 			canContextSwitch
+ 				ifTrue:
+ 					[self JumpAboveOrEqual: stackOverflowCall.
+ 					 label := self Label]
+ 				ifFalse:
+ 					[jumpSkip := self JumpBelow: 0.
+ 					 self MoveCq: 0 R: SendNumArgsReg.
+ 					 self Jump: stackOverflowCall.
+ 					 jumpSkip jmpTarget: (label := self Label)]].
+ 	self annotateBytecode: label.
+ 	^label!

Item was removed:
- ----- Method: CurrentImageCoInterpreterFacade>>inMemoryCFramePointerAddress (in category 'accessing') -----
- inMemoryCFramePointerAddress
- 	^self addressForLabel: #CFramePointer!

Item was removed:
- ----- Method: CurrentImageCoInterpreterFacade>>inMemoryCStackPointerAddress (in category 'accessing') -----
- inMemoryCStackPointerAddress
- 	^self addressForLabel: #CStackPointer!

Item was changed:
  ----- Method: SimpleStackBasedCogit>>compileBlockFrameBuild: (in category 'compile abstract instructions') -----
  compileBlockFrameBuild: blockStart
  	"Build a frame for a block activation.  See CoInterpreter class>>initializeFrameIndices.
  	 		closure (in ReceiverResultReg)
  			arg0
  			...
  			argN
  			caller's saved ip/this stackPage (for a base frame)
  	fp->	saved fp
  			method
  			context (uninitialized?)
  			receiver
  			first temp
  			...
  	sp->	Nth temp
  	Avoid use of SendNumArgsReg which is the flag determining whether
  	context switch is allowed on stack-overflow."
  	<var: #blockStart type: #'BlockStart *'>
  	<inline: false>
  	self annotateBytecode: self Label.
  	backEnd hasLinkRegister ifTrue:
  		[self PushR: LinkReg].
  	self PushR: FPReg.
  	self MoveR: SPReg R: FPReg.
  	"Think of ClassReg as ClosureReg"
  	self MoveR: ReceiverResultReg R: ClassReg.
  	"The block method field must have its MFMethodFlagIsBlockFlag bit set.
  	 We arrange this using a labelOffset.  A hack, but it works."
  	blockStart fakeHeader
  		addDependent: (self annotateAbsolutePCRef:
  			(self PushCw: blockStart fakeHeader asInteger)); "method"
  		setLabelOffset: MFMethodFlagIsBlockFlag.
  	self annotate: (self PushCw: objectMemory nilObject) "context"
  		objRef: objectMemory nilObject.
  	"Fetch home receiver from outer context. closure is on stack and initially in ReceiverResultReg.
  	 It is safe to use Arg0Reg because reg args are pushed by the value primitives if there are any.".
  	blockStart hasInstVarRef
  		ifTrue: "Use ReceiverResultReg for Context to agree with store check trampoline"
  			[objectRepresentation
  				genLoadSlot: ClosureOuterContextIndex
  					sourceReg: ClassReg
  						destReg: ReceiverResultReg;
  				genLoadSlot: ReceiverIndex
  					sourceReg: ReceiverResultReg
  						destReg: Arg0Reg.
  			objectRepresentation
  				genEnsureOopInRegNotForwarded: Arg0Reg scratchReg: TempReg updatingSlot: ReceiverIndex in: ReceiverResultReg.
  			self MoveR: Arg0Reg R: ReceiverResultReg]
  		ifFalse:
  			[objectRepresentation
  				genLoadSlot: ClosureOuterContextIndex
  					sourceReg: ClassReg
  						destReg: Arg0Reg;
  				genLoadSlot: ReceiverIndex
  					sourceReg: Arg0Reg
  						destReg: ReceiverResultReg].
  	self PushR: ReceiverResultReg. "home receiver"
  	"Push copied values; bytecode initializes temporaries"
  	0 to: blockStart numCopied - 1 do:
  		[:i|
  		objectRepresentation
  			genLoadSlot: i + ClosureFirstCopiedValueIndex
  			sourceReg: ClassReg
  			destReg: TempReg.
  		self PushR: TempReg].
+ 	blockStart stackCheckLabel:
+ 		(self compileStackOverflowCheck: true)!
- 	self MoveAw: coInterpreter stackLimitAddress R: TempReg.
- 	self CmpR: TempReg R: SPReg. "N.B. FLAGS := SPReg - TempReg"
- 	self JumpBelow: stackOverflowCall.
- 	blockStart stackCheckLabel: (self annotateBytecode: self Label)!

Item was changed:
  ----- Method: SimpleStackBasedCogit>>compileFrameBuild (in category 'compile abstract instructions') -----
  compileFrameBuild
  	"Build a frame for a CogMethod activation.  See CoInterpreter class>>initializeFrameIndices.
  	 		receiver (in ReceiverResultReg)
  			arg0
  			...
  			argN
  			caller's saved ip/this stackPage (for a base frame)
  	fp->	saved fp
  			method
  			context (uninitialized?)
  			receiver
  			first temp
  			...
  	sp->	Nth temp
  	If there is a primitive and an error code the Nth temp is the error code.
  	Ensure SendNumArgsReg is set early on (incidentally to nilObj) because
  	it is the flag determining whether context switch is allowed on stack-overflow."
- 	| jumpSkip |
  	<inline: false>
- 	<var: #jumpSkip type: #'AbstractInstruction *'>
  	needsFrame ifFalse: [^self].
  	backEnd hasLinkRegister ifTrue: [self PushR: LinkReg].
  	self PushR: FPReg.
  	self MoveR: SPReg R: FPReg.
  	methodLabel addDependent: (self annotateAbsolutePCRef:
  		(self PushCw: methodLabel asInteger)). "method"
  	self genMoveNilR: SendNumArgsReg.
  	self PushR: SendNumArgsReg. "context"
  	self PushR: ReceiverResultReg.
  	methodOrBlockNumArgs + 1 to: (coInterpreter temporaryCountOfMethodHeader: methodHeader) do:
  		[:i|
  		self PushR: SendNumArgsReg].
  	(self methodUsesPrimitiveErrorCode: methodObj header: methodHeader) ifTrue:
  		[self compileGetErrorCode].
+ 	stackCheckLabel := self compileStackOverflowCheck: (coInterpreter
+ 															canContextSwitchIfActivating: methodObj
+ 															header: methodHeader).
- 	self MoveAw: coInterpreter stackLimitAddress R: TempReg.
- 	self CmpR: TempReg R: SPReg. "N.B. FLAGS := SPReg - TempReg"
- 	"If we can't context switch for this method, use a slightly
- 	 slower overflow check that clears SendNumArgsReg."
- 	(coInterpreter canContextSwitchIfActivating: methodObj header: methodHeader)
- 		ifTrue:
- 			[self JumpBelow: stackOverflowCall.
- 			 stackCheckLabel := self Label]
- 		ifFalse:
- 			[jumpSkip := self JumpAboveOrEqual: 0.
- 			 self MoveCq: 0 R: SendNumArgsReg.
- 			 self Jump: stackOverflowCall.
- 			 jumpSkip jmpTarget: (stackCheckLabel := self Label)].
- 	self annotateBytecode: stackCheckLabel.
  	NewspeakVM ifTrue:
  		[numIRCs > 0 ifTrue:
  		 	[self PrefetchAw: theIRCs]]!

Item was changed:
  ----- Method: SimpleStackBasedCogit>>compileFullBlockMethodFrameBuild: (in category 'compile abstract instructions') -----
  compileFullBlockMethodFrameBuild: numCopied
  	"Build a frame for a block activation.  See CoInterpreter class>>initializeFrameIndices.
  	 		closure (in ReceiverResultReg)
  			arg0
  			...
  			argN
  			caller's saved ip/this stackPage (for a base frame)
  	fp->	saved fp
  			method
  			context (uninitialized?)
  			receiver
  			first temp
  			...
  	sp->	Nth temp
  	Avoid use of SendNumArgsReg which is the flag determining whether
  	context switch is allowed on stack-overflow."
  	<inline: false>
  	needsFrame ifFalse: [^self].
  	backEnd hasLinkRegister ifTrue: [self PushR: LinkReg].
  	self PushR: FPReg.
  	self MoveR: SPReg R: FPReg.
  	"Think of ClassReg as ClosureReg"
  	self MoveR: ReceiverResultReg R: ClassReg.
  	"The block method field must have its MFMethodFlagIsBlockFlag bit set.
  	 We arrange this using a labelOffset.  A hack, but it works."
  	methodLabel addDependent: (self annotateAbsolutePCRef:
  			(self PushCw: methodLabel asInteger));
  			setLabelOffset: MFMethodFlagIsBlockFlag.. "method"
  	self genMoveNilR: SendNumArgsReg.
  	self PushR: SendNumArgsReg. "context"
  	"Closure is on stack and initially in ReceiverResultReg.
  	 It is safe to use Arg0Reg because reg args are pushed by the value primitives if there are any.".
  
  	self flag: #TODO. "we could follow the receiver only if the block has inst var ref. Currently we use scanMethod for fullBlock 
  	and that scanner does not provide this information. We could extend it based on the scanBlock: method"
  	"Use ReceiverResultReg for the closure to agree with store check trampoline"
  	objectRepresentation
  		genLoadSlot: FullClosureReceiverIndex
  			sourceReg: ClassReg
  				destReg: Arg0Reg.
  	objectRepresentation
  		genEnsureOopInRegNotForwarded: Arg0Reg scratchReg: TempReg updatingSlot: FullClosureReceiverIndex in: ReceiverResultReg.
  	self MoveR: Arg0Reg R: ReceiverResultReg.
  
  	self PushR: ReceiverResultReg. "closure receiver"
  	"Push copied values"
  	0 to: numCopied - 1 do:
  		[:i|
  		objectRepresentation
  			genLoadSlot: i + FullClosureFirstCopiedValueIndex
  			sourceReg: ClassReg
  			destReg: TempReg.
  		self PushR: TempReg].
  	"Push slots for temps"
  	methodOrBlockNumArgs + numCopied + 1 to: (coInterpreter temporaryCountOfMethodHeader: methodHeader) do:
  		[:i|
  		self PushR: SendNumArgsReg].
+ 
+ 	stackCheckLabel := self compileStackOverflowCheck: true!
- 	
- 	self MoveAw: coInterpreter stackLimitAddress R: TempReg.
- 	self CmpR: TempReg R: SPReg. "N.B. FLAGS := SPReg - TempReg"
- 	self JumpBelow: stackOverflowCall.
- 	stackCheckLabel := (self annotateBytecode: self Label)!



More information about the Vm-dev mailing list