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

commits at source.squeak.org commits at source.squeak.org
Mon May 29 16:35:24 UTC 2017


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

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

Name: VMMaker.oscog-eem.2225
Author: eem
Time: 29 May 2017, 9:34:28.198165 am
UUID: a3791777-370b-419b-9708-9e73bf94e39b
Ancestors: VMMaker.oscog-nice.2224

Cogit:
Use genMarshallNArgs:arg:arg:arg:arg: when compiling an interpreter primitive call to allow adding the shadow parameter space on Win64.

Fix generation of JumpR on x64.  I forgot a rex byte.  This doesn't affect SysV because we only ever jump through ClassReg (in an open PIC dispatch) which is RCX (1) on SysV but R8 (8) on Win64.

Add tests for CallR and JumpR generation on x64.

Have printRumpCStackTo: include the sp and fp if in the range.

With the fix to JumpR a Win64 image simulates correctly (with smashing of the shadow parameter space).

=============== Diff against VMMaker.oscog-nice.2224 ===============

Item was changed:
  ----- Method: CogVMSimulator>>printRumpCStackTo: (in category 'rump c stack') -----
  printRumpCStackTo: address
  	self assert: (self isOnRumpCStack: address).
  	heapBase - objectMemory wordSize
  		to: address
  		by: objectMemory wordSize negated
  		do:
  			[:addr|
+ 			self printHex: addr.
+ 			addr = cogit processor sp
+ 				ifTrue: [self print: ' sp->']
+ 				ifFalse:
+ 					[addr = cogit processor fp
+ 						ifTrue: [self print: ' fp->']
+ 						ifFalse: [self tab]].
+ 			self tab; printHex: (objectMemory longAt: addr); cr]!
- 			self printHex: addr; tab; printHex: (objectMemory longAt: addr); cr]!

Item was changed:
  ----- Method: CogX64Compiler>>computeMaximumSize (in category 'generate machine code') -----
(excessive size, no diff calculated)

Item was changed:
  ----- Method: CogX64Compiler>>concretizeJumpR (in category 'generate machine code') -----
  concretizeJumpR
  	<inline: true>
  	| reg |
  	reg := operands at: 0.
  	machineCode
+ 		at: 0 put: (self rexR: 0 x: 0 b: reg);
+ 		at: 1 put: 16rFF;
+ 		at: 2 put: (self mod: ModReg RM: reg RO: 4).
+ 	^machineCodeSize := 3!
- 		at: 0 put: 16rFF;
- 		at: 1 put: (self mod: ModReg RM: reg RO: 4).
- 	^machineCodeSize := 2!

Item was added:
+ ----- Method: CogX64CompilerTests>>testCallR (in category 'tests') -----
+ testCallR
+ 	"self new testCallR"
+ 	self concreteCompilerClass registersWithNamesDo:
+ 		[:reg :regname| | inst len|
+ 			inst := self gen: CallR operand: reg.
+ 			len := inst concretizeAt: 0.
+ 			self processor
+ 				disassembleInstructionAt: 0
+ 				In: inst machineCode object
+ 				into: [:str :sz| | plainJane herIntended |
+ 					"Convert e.g. '00000000: movl %eax, 0x2(%eax) : 89 40 02' to  'movl %eax, 0x2(%eax)'"
+ 					plainJane := self strip: str.
+ 					herIntended := 'call ', regname.
+ 					self assert: herIntended equals: plainJane.
+ 					self assert: len = sz]]!

Item was added:
+ ----- Method: CogX64CompilerTests>>testJumpR (in category 'tests') -----
+ testJumpR
+ 	"self new testJumpR"
+ 	self concreteCompilerClass registersWithNamesDo:
+ 		[:reg :regname| | inst len|
+ 			inst := self gen: JumpR operand: reg.
+ 			len := inst concretizeAt: 0.
+ 			self processor
+ 				disassembleInstructionAt: 0
+ 				In: inst machineCode object
+ 				into: [:str :sz| | plainJane herIntended |
+ 					"Convert e.g. '00000000: movl %eax, 0x2(%eax) : 89 40 02' to  'movl %eax, 0x2(%eax)'"
+ 					plainJane := self strip: str.
+ 					herIntended := 'jmp ', regname.
+ 					self assert: herIntended equals: plainJane.
+ 					self assert: len = sz]]!

Item was changed:
  ----- Method: SimpleStackBasedCogit>>compileInterpreterPrimitive:flags: (in category 'primitive generators') -----
  compileInterpreterPrimitive: primitiveRoutine flags: flags
  	"Compile a call to an interpreter primitive.  Call the C routine with the
  	 usual stack-switching dance, test the primFailCode and then either
  	 return on success or continue to the method body."
  	<var: #primitiveRoutine declareC: 'void (*primitiveRoutine)(void)'>
  	| jmp jmpSamplePrim continuePostSamplePrim jmpSampleNonPrim continuePostSampleNonPrim |
  	<var: #jmp type: #'AbstractInstruction *'>
  	<var: #jmpSamplePrim type: #'AbstractInstruction *'>
  	<var: #jmpSampleNonPrim type: #'AbstractInstruction *'>
  	<var: #continuePostSamplePrim type: #'AbstractInstruction *'>
  	<var: #continuePostSampleNonPrim type: #'AbstractInstruction *'>
  
  	"Save processor fp, sp and return pc in the interpreter's frame stack and instruction pointers"
  	self genExternalizePointersForPrimitiveCall.
  	"Switch to the C stack."
  	self genLoadCStackPointersForPrimCall.
  
  	(flags anyMask: PrimCallCollectsProfileSamples) ifTrue:
  		["Test nextProfileTick for being non-zero and call checkProfileTick if so"
  		objectMemory wordSize = 4
  			ifTrue:
  				[self MoveAw: coInterpreter nextProfileTickAddress R: TempReg.
  				 self MoveAw: coInterpreter nextProfileTickAddress + objectMemory wordSize R: ClassReg.
  				 self OrR: TempReg R: ClassReg]
  			ifFalse:
  				[self MoveAw: coInterpreter nextProfileTickAddress R: TempReg.
  				 self CmpCq: 0 R: TempReg].
  		"If set, jump to record sample call."
  		jmpSampleNonPrim := self JumpNonZero: 0.
  		continuePostSampleNonPrim := self Label].
  
  	"Old full prim trace is in VMMaker-eem.550 and prior"
  	self recordPrimTrace ifTrue:
  		[self genFastPrimTraceUsing: ClassReg and: SendNumArgsReg].
  
  	"Clear the primFailCode and set argumentCount"
  	self MoveCq: 0 R: TempReg.
  	self MoveR: TempReg Aw: coInterpreter primFailCodeAddress.
  	methodOrBlockNumArgs ~= 0 ifTrue:
  		[self MoveCq: methodOrBlockNumArgs R: TempReg].
  	self MoveR: TempReg Aw: coInterpreter argumentCountAddress.
  
  	"If required, set primitiveFunctionPointer and newMethod"
  	(flags anyMask: PrimCallNeedsPrimitiveFunction) ifTrue:
  		[self MoveCw: primitiveRoutine asInteger R: TempReg.
  		 primSetFunctionLabel :=
  		 self MoveR: TempReg Aw: coInterpreter primitiveFunctionPointerAddress].
  	(flags anyMask: PrimCallNeedsNewMethod+PrimCallMayCallBack) ifTrue:
  		["The ceActivateFailingPrimitiveMethod: machinery can't handle framelessness."
  		 (flags anyMask: PrimCallMayCallBack) ifTrue:
  			[needsFrame := true].
  		 methodLabel addDependent:
  			(self annotateAbsolutePCRef:
  				(self MoveCw: methodLabel asInteger R: ClassReg)).
  		 self MoveMw: (self offset: CogMethod of: #methodObject) r: ClassReg R: TempReg.
  		 self MoveR: TempReg Aw: coInterpreter newMethodAddress].
  
  	"Invoke the primitive"
  	self PrefetchAw: coInterpreter primFailCodeAddress.
  	(flags anyMask: PrimCallMayCallBack)
  		ifTrue: "Sideways call the C primitive routine so that we return through cePrimReturnEnterCogCode."
  			["On Spur ceActivateFailingPrimitiveMethod: would like to retry if forwarders
  			  are found. So insist on PrimCallNeedsPrimitiveFunction being set too."
  			 self assert: (flags anyMask: PrimCallNeedsPrimitiveFunction).
+ 			 backEnd
+ 				genMarshallNArgs: 0 arg: 0 arg: 0 arg: 0 arg: 0;
+ 				genSubstituteReturnAddress:
+ 					((flags anyMask: PrimCallCollectsProfileSamples)
+ 						ifTrue: [cePrimReturnEnterCogCodeProfiling]
+ 						ifFalse: [cePrimReturnEnterCogCode]).
- 			 backEnd genSubstituteReturnAddress:
- 				((flags anyMask: PrimCallCollectsProfileSamples)
- 					ifTrue: [cePrimReturnEnterCogCodeProfiling]
- 					ifFalse: [cePrimReturnEnterCogCode]).
  			 primInvokeInstruction := self JumpFullRT: primitiveRoutine asInteger.
  			 jmp := jmpSamplePrim := continuePostSamplePrim := nil]
  		ifFalse:
  			["Call the C primitive routine."
+ 			backEnd genMarshallNArgs: 0 arg: 0 arg: 0 arg: 0 arg: 0.
  			primInvokeInstruction := self CallFullRT: primitiveRoutine asInteger.
+ 			backEnd genRemoveNArgsFromStack: 0.
  			(flags anyMask: PrimCallCollectsProfileSamples) ifTrue:
  				[self assert: (flags anyMask: PrimCallNeedsNewMethod).
  				"Test nextProfileTick for being non-zero and call checkProfileTick if so"
  				objectMemory wordSize = 4
  					ifTrue:
  						[self MoveAw: coInterpreter nextProfileTickAddress R: TempReg.
  						 self MoveAw: coInterpreter nextProfileTickAddress + objectMemory wordSize R: ClassReg.
  						 self OrR: TempReg R: ClassReg]
  					ifFalse:
  						[self MoveAw: coInterpreter nextProfileTickAddress R: TempReg.
  						 self CmpCq: 0 R: TempReg].
  				"If set, jump to record sample call."
  				jmpSamplePrim := self JumpNonZero: 0.
  				continuePostSamplePrim := self Label].
  			objectRepresentation maybeCompileRetryOnPrimitiveFail: primitiveIndex.
  			self maybeCompileAllocFillerCheck.
  			"Switch back to the Smalltalk stack.  Stack better be in either of these two states:
  				success:	stackPointer ->	result (was receiver)
  											arg1
  											...
  											argN
  											return pc
  				failure:						receiver
  											arg1
  											...
  							stackPointer ->	argN
  											return pc
  			In either case we can push the instructionPointer or load it into the LinkRegister to reestablish the return pc"
  			self MoveAw: coInterpreter instructionPointerAddress
  				R: (backEnd hasLinkRegister ifTrue: [LinkReg] ifFalse: [ClassReg]).
  			backEnd genLoadStackPointers.
  			"Test primitive failure"
  			self MoveAw: coInterpreter primFailCodeAddress R: TempReg.
  			backEnd hasLinkRegister ifFalse: [self PushR: ClassReg]. "Restore return pc on CISCs"
  			self flag: 'ask concrete code gen if move sets condition codes?'.
  			self CmpCq: 0 R: TempReg.
  			jmp := self JumpNonZero: 0.
  			"Fetch result from stack"
  			self MoveMw: (backEnd hasLinkRegister ifTrue: [0] ifFalse: [objectMemory wordSize])
  				r: SPReg
  				R: ReceiverResultReg.
  			self RetN: objectMemory wordSize].	"return to caller, popping receiver"
  
  	(flags anyMask: PrimCallCollectsProfileSamples) ifTrue:
  		["The sample is collected by cePrimReturnEnterCogCode for external calls"
  		jmpSamplePrim ifNotNil:
  			["Call ceCheckProfileTick: to record sample and then continue."
  			jmpSamplePrim jmpTarget: self Label.
  			self assert: (flags anyMask: PrimCallNeedsNewMethod).
  			self CallFullRT: (self cCode: [#ceCheckProfileTick asUnsignedIntegerPtr]
  							   inSmalltalk: [self simulatedTrampolineFor: #ceCheckProfileTick]).
  			"reenter the post-primitive call flow"
  			self Jump: continuePostSamplePrim].
  		"Null newMethod and call ceCheckProfileTick: to record sample and then continue.
  		 ceCheckProfileTick will map null/0 to coInterpreter nilObject"
  		jmpSampleNonPrim jmpTarget: self Label.
  		self MoveCq: 0 R: TempReg.
  		self MoveR: TempReg Aw: coInterpreter newMethodAddress.
  		self CallFullRT: (self cCode: [#ceCheckProfileTick asUnsignedIntegerPtr]
  						   inSmalltalk: [self simulatedTrampolineFor: #ceCheckProfileTick]).
  		"reenter the post-primitive call flow"
  		self Jump: continuePostSampleNonPrim].
  
  	jmp ifNotNil:
  		["Jump to restore of receiver reg and proceed to frame build for failure."
  		 jmp jmpTarget: self Label.
  		 "Restore receiver reg from stack.  If on RISCs ret pc is in LinkReg, if on CISCs ret pc is on stack."
  		 self MoveMw: objectMemory wordSize * (methodOrBlockNumArgs + (backEnd hasLinkRegister ifTrue: [0] ifFalse: [1]))
  			r: SPReg
  			R: ReceiverResultReg].
  	^0!



More information about the Vm-dev mailing list