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

commits at source.squeak.org commits at source.squeak.org
Thu Oct 29 21:12:41 UTC 2020


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

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

Name: VMMaker.oscog-eem.2862
Author: eem
Time: 29 October 2020, 2:12:30.601633 pm
UUID: a30f9d13-a2a4-415a-982c-898cc5b69848
Ancestors: VMMaker.oscog-eem.2861

Cogit: eliminate diplication in the new genReturnToInterpreterTrampoline.  Revise deriving the varBaseAddress after finding on MacOS that the linker may not "follow orders".  So take the minimum of several likely addresses, secretly hoping the minimum is something like stackLimit, which likely has the highest dynamic frequency (well done clang).

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

Item was changed:
  ----- Method: CogX64Compiler>>concretizeMoveRAw (in category 'generate machine code - concretize') -----
  concretizeMoveRAw
  	"Will get inlined into concretizeAt: switch."
  	<inline: true>
  	| addressOperand reg offset save1 savedSize |
  	reg := operands at: 0.
  	addressOperand := operands at: 1.
  	(self isAnInstruction: (cogit cCoerceSimple: addressOperand to: #'AbstractInstruction *')) ifTrue:
  		[addressOperand := (cogit cCoerceSimple: addressOperand to: #'AbstractInstruction *') address].
  	(self isAddressRelativeToVarBase: addressOperand) ifTrue:
  		[save1 := operands at: 1.
  		 operands
  			at: 1 put: addressOperand - cogit varBaseAddress;
  			at: 2 put: RBX.
  		 savedSize := self concretizeMoveRMwr.
  		 operands
  			at: 1 put: save1;
  			at: 2 put: 0.
  		^savedSize].
  	"If storing RAX, store directly, otherwise, because of instruction encoding limitations, the register
  	 _must_ be stored through RAX.  If reg = RBP or RSP simply store directly, otherwise swap RAX with
+ 	 the register before and after the store through RAX.  We avoid swapping before hand with RBP
- 	 the register before and after the store through RAX.  We avoid sweapping before hand with RBP
  	 and RSP because setting RSP to whatever the contents of RAX is can cause disastrous results if
  	 an interrupt is delivered immediately after that point.  See mail threads beginning with
  		http://lists.squeakfoundation.org/pipermail/vm-dev/2019-September/031428.html
  		http://lists.squeakfoundation.org/pipermail/vm-dev/2019-October/031499.html"
  	(reg = RAX or: [reg = RBP or: [reg = RSP]])
  		ifTrue: [offset := 0]
  		ifFalse:
  			[(reg = RBP or: [reg = RSP])
  				ifTrue:
  					[machineCode
  						at: 0 put: (self rexR: reg x: 0 b: RAX);
  						at: 1 put: 16r89;
  						at: 2 put: (self mod: ModReg RM: RAX RO: reg).
  					 offset := 3]
  				ifFalse:
  					[machineCode
  						at: 0 put: (self rexR: RAX x: 0 b: reg);
  						at: 1 put: 16r90 + (reg \\ 8).
  					 offset := 2]].
  	machineCode
  		at: 0 + offset put: 16r48;
  		at: 1 + offset put: 16rA3;
  		at: 2 + offset put: (addressOperand bitAnd: 16rFF);
  		at: 3 + offset put: (addressOperand >> 8 bitAnd: 16rFF);
  		at: 4 + offset put: (addressOperand >> 16 bitAnd: 16rFF);
  		at: 5 + offset put: (addressOperand >> 24 bitAnd: 16rFF);
  		at: 6 + offset put: (addressOperand >> 32 bitAnd: 16rFF);
  		at: 7 + offset put: (addressOperand >> 40 bitAnd: 16rFF);
  		at: 8 + offset put: (addressOperand >> 48 bitAnd: 16rFF);
  		at: 9 + offset put: (addressOperand >> 56 bitAnd: 16rFF).
  	reg = RAX ifTrue:
  		[^10].
  	(reg = RBP or: [reg = RSP]) ifTrue:
  		[^13].
  	"Now effect the assignment via xchg, which restores RAX"
  	machineCode
  		at: 12 put: (machineCode at: 0);
  		at: 13 put: (machineCode at: 1).
  	^14!

Item was changed:
  CogClass subclass: #Cogit
(excessive size, no diff calculated)

Item was added:
+ ----- Method: Cogit>>computeGoodVarBaseAddress (in category 'initialization') -----
+ computeGoodVarBaseAddress
+ 	"While we order variables in the CoInterpreter in order of dynamic frequency, and hence
+ 	 expect that stackPointer will be output first, C optimizers and linkers may get their own
+ 	 ideas and ``improve upon'' this ordering.  So we cannot depend on stackPointer being
+ 	 at the lowest address of the variables we want to access through VarBaseReg.  Here we
+ 	 choose the minimum amongst a set to try to choose a varBaseAddress that is just less
+ 	 than but iwht in range of all variables we want to access through it."
+ 	| minAddress |
+ 	minAddress := coInterpreter stackLimitAddress. "stackLimit is e.g. lowest using the clang toolchain on MacOS X"
+ 	coInterpreter stackPointerAddress < minAddress ifTrue:
+ 		[minAddress := coInterpreter stackPointerAddress].
+ 	coInterpreter framePointerAddress < minAddress ifTrue:
+ 		[minAddress := coInterpreter framePointerAddress].
+ 	coInterpreter instructionPointerAddress < minAddress ifTrue:
+ 		[minAddress := coInterpreter instructionPointerAddress].
+ 	coInterpreter argumentCountAddress < minAddress ifTrue:
+ 		[minAddress := coInterpreter argumentCountAddress].
+ 	coInterpreter primFailCodeAddress < minAddress ifTrue:
+ 		[minAddress := coInterpreter primFailCodeAddress].
+ 	^minAddress!

Item was changed:
  ----- Method: Cogit>>genReturnToInterpreterTrampoline (in category 'initialization') -----
  genReturnToInterpreterTrampoline
  	| startAddress |
  	<inline: false>
  	startAddress := methodZoneBase.
  	self zeroOpcodeIndex.
  	"Push the result, set the instruction pointer to the interpreter frame's saved ip,
  	 set the method and the bytecode set offset, then call interpret."
  	self PushR: ReceiverResultReg. "The result"
  	"Assign the iframeSavedIP to instructionPointer"
  	self MoveMw: FoxIFSavedIP r: FPReg R: TempReg.
  	self MoveR: TempReg Aw: coInterpreter instructionPointerAddress.
  	self genSmalltalkToCStackSwitch: false "pushLinkReg".
- 	cFramePointerInUse
- 		ifTrue: [backEnd genLoadCStackPointers]
- 		ifFalse: [backEnd genLoadCStackPointer].
  	"Sideways call interpret so that the stack looks correct, for exception handling etc"
  	backEnd genMarshallNArgs: 0 arg: nil arg: nil arg: nil arg: nil.
  	backEnd hasLinkRegister
  		ifTrue:
  			[self MoveAw: coInterpreter cReturnAddressAddress R: LinkReg]
  		ifFalse:
  			[self MoveAw: coInterpreter cReturnAddressAddress R: ABIResultReg.
  			 backEnd genSubstituteReturnAddressR: ABIResultReg].
  	self JumpFullRT: (self
  						cCode: [#interpret asUnsignedInteger]
  						inSmalltalk: [self simulatedTrampolineFor: #interpret]).
  	self outputInstructionsForGeneratedRuntimeAt: startAddress.
  	self recordGeneratedRunTime: 'ceReturnToInterpreterTrampoline' address: startAddress.
+ 	^startAddress!
- 	^self cCoerceSimple: startAddress to: #'void (*)(void)'!

Item was changed:
  ----- Method: Cogit>>initializeBackend (in category 'initialization') -----
  initializeBackend
  	methodLabel machineCodeSize: 0.
  	methodLabel opcode: Label.
  	methodLabel operands at: 0 put: 0.
  	methodLabel operands at: 1 put: 0. "label offset"
  	backEnd hasVarBaseRegister ifTrue:
+ 		[self assert: ((self registerMaskFor: VarBaseReg) noMask: CallerSavedRegisterMask).
+ 		 varBaseAddress := self computeGoodVarBaseAddress.
+ 		 self assert: coInterpreter stackLimitAddress >= varBaseAddress.
+ 		 self assert: coInterpreter cStackPointerAddress >= varBaseAddress.
+ 		 self assert: coInterpreter cFramePointerAddress >= varBaseAddress.
+ 		 self assert: coInterpreter cReturnAddressAddress >= varBaseAddress.
+ 		 self assert: coInterpreter nextProfileTickAddress >= varBaseAddress].
- 		[self assert: ((self registerMaskFor: VarBaseReg) noMask: CallerSavedRegisterMask)].
  	literalsManager allocateLiterals: 4; resetLiterals!

Item was changed:
  ----- Method: Cogit>>varBaseAddress (in category 'accessing') -----
  varBaseAddress
+ 	<cmacro: '() varBaseAddress'>
+ 	^varBaseAddress!
- 	^coInterpreter stackPointerAddress - objectMemory wordSize!



More information about the Vm-dev mailing list