[Vm-dev] VM Maker: VMMaker.oscog-nice.2003.mcz

commits at source.squeak.org commits at source.squeak.org
Tue Nov 29 01:25:04 UTC 2016


Nicolas Cellier uploaded a new version of VMMaker to project VM Maker:
http://source.squeak.org/VMMaker/VMMaker.oscog-nice.2003.mcz

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

Name: VMMaker.oscog-nice.2003
Author: nice
Time: 29 November 2016, 2:22:55.009541 am
UUID: f05dde07-c324-452a-a507-7795ad594dca
Ancestors: VMMaker.oscog-nice.2002

Retract the choice of cppIf: #WIN64 for x64 ABI testing 'cause it's not simulator friendly.
Instead use a boolean SysV which is OK both in generated code and simulator (a bit less explicit than ABI = #SysV, but it works better).

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

Item was changed:
  ----- Method: CogInLineLiteralsX64Compiler class>>initializeAbstractRegisters (in category 'class initialization') -----
  initializeAbstractRegisters
  	"Assign the abstract registers with the identities/indices of the relevant concrete registers."
  
  	super initializeAbstractRegisters.
+ 	RISCTempReg := SysV
- 	RISCTempReg := ABI = #SysV
  		ifTrue: [R8]
  		ifFalse: [R11]!

Item was changed:
  ----- Method: CogOutOfLineLiteralsX64Compiler class>>initializeAbstractRegisters (in category 'class initialization') -----
  initializeAbstractRegisters
  	"Assign the abstract registers with the identities/indices of the relevant concrete registers."
  
  	super initializeAbstractRegisters.
+ 	Extra6Reg := SysV
- 	Extra6Reg := ABI = #SysV
  		ifTrue: [R8]
  		ifFalse: [R11]!

Item was changed:
  CogAbstractInstruction subclass: #CogX64Compiler
  	instanceVariableNames: ''
+ 	classVariableNames: 'CDQ CMPXCHGAwR CMPXCHGMwrR CPUID IDIVR IMULRR LFENCE LOCK MFENCE ModReg ModRegInd ModRegIndDisp32 ModRegIndSIB ModRegRegDisp32 ModRegRegDisp8 R10 R11 R12 R13 R14 R15 R8 R9 RAX RBP RBX RCX RDI RDX RSI RSP SFENCE SIB1 SIB2 SIB4 SIB8 SysV XCHGAwR XCHGMwrR XCHGRR XMM0L XMM10L XMM11L XMM12L XMM13L XMM14L XMM15L XMM1L XMM2L XMM3L XMM4L XMM5L XMM6L XMM7L XMM8L XMM9L'
- 	classVariableNames: 'ABI CDQ CMPXCHGAwR CMPXCHGMwrR CPUID IDIVR IMULRR LFENCE LOCK MFENCE ModReg ModRegInd ModRegIndDisp32 ModRegIndSIB ModRegRegDisp32 ModRegRegDisp8 R10 R11 R12 R13 R14 R15 R8 R9 RAX RBP RBX RCX RDI RDX RSI RSP SFENCE SIB1 SIB2 SIB4 SIB8 XCHGAwR XCHGMwrR XCHGRR XMM0L XMM10L XMM11L XMM12L XMM13L XMM14L XMM15L XMM1L XMM2L XMM3L XMM4L XMM5L XMM6L XMM7L XMM8L XMM9L'
  	poolDictionaries: ''
  	category: 'VMMaker-JIT'!
  
  !CogX64Compiler commentStamp: 'eem 9/14/2015 17:12' prior: 0!
  I generate x64 (x86-64) instructions from CogAbstractInstructions.  For reference see
  1. IA-32 Intel® Architecture Software Developer's Manual Volume 2A: Instruction Set Reference, A-M
  2. IA-32 Intel® Architecture Software Developer's Manual Volume 2A: Instruction Set Reference, N-Z
  	http://www.intel.com/products/processor/manuals/
  or
  AMD64 Architecture Programmer's Manual Volume 3: General-Purpose and System Instructions
  AMD64 Architecture Programmer's Manual Volume 4: 128-bit Media Instructions
  AMD64 Architecture Programmer's Manual Volume 5: 64-bit Media and x87 Floating Point Instructions
  	http://developer.amd.com/resources/documentation-articles/developer-guides-manuals/
  (® is supposed to be the Unicode "registered  sign").!

Item was removed:
- ----- Method: CogX64Compiler class>>ABI (in category 'accessing') -----
- ABI
- 	"Answer the name of the supported ABI, #SysV or #MSVC"
- 	^ABI!

Item was changed:
  ----- Method: CogX64Compiler class>>initialize (in category 'class initialization') -----
  initialize
  	"Initialize various x64 instruction-related constants.
  	 [1] IA-32 Intel® Architecture Software Developer's Manual Volume 2A: Instruction Set Reference, A-M"
  
  	"CogX64Compiler initialize"
  
  	self ~~ CogX64Compiler ifTrue: [^self].
  
+ 	SysV ifNil:
+ 		[SysV := true]. "Default ABI; set to tru for SysV, false for WIN64"
- 	ABI ifNil:
- 		[ABI := #SysV]. "Default ABI; other choice is #MSVC"
  
  	RAX := 0.
  	RCX := 1.  "Were they completely mad or simply sadistic?"
  	RDX := 2.
  	RBX := 3.
  	RSP := 4.
  	RBP := 5.
  	RSI := 6.
  	RDI := 7.
  	R8 := 8.
  	R9 := 9.
  	R10 := 10.
  	R11 := 11.
  	R12 := 12.
  	R13 := 13.
  	R14 := 14.
  	R15 := 15.
  
  	XMM0L := 0.
  	XMM1L := 1.
  	XMM2L := 2.
  	XMM3L := 3.
  	XMM4L := 4.
  	XMM5L := 5.
  	XMM6L := 6.
  	XMM7L := 7.
  	XMM8L := 8.
  	XMM9L := 9.
  	XMM10L := 10.
  	XMM11L := 11.
  	XMM12L := 12.
  	XMM13L := 13.
  	XMM14L := 14.
  	XMM15L := 15.
  
  	"Mod R/M Mod fields.  See [1] Sec 2.4, 2.5 & 2.6 & Table 2-2"
  	ModRegInd := 0.
  		ModRegIndSIB := 4.
  		ModRegIndDisp32 := 5.
  	ModRegRegDisp8 := 1.
  	ModRegRegDisp32 := 2.
  	ModReg := 3.
  
  	"SIB Scaled Index modes.  See [1] Sec 2.4, 2.5 & 2.6 & Table 2-3"
  	SIB1 := 0.
  	SIB2 := 1.
  	SIB4 := 2.
  	SIB8 := 3.
  
  	"Specific instructions"
  	self
  		initializeSpecificOpcodes: #(CDQ IDIVR IMULRR CPUID LFENCE MFENCE SFENCE LOCK CMPXCHGAwR CMPXCHGMwrR XCHGAwR XCHGMwrR XCHGRR)
  		in: thisContext method!

Item was changed:
  ----- Method: CogX64Compiler class>>initializeAbstractRegisters (in category 'class initialization') -----
  initializeAbstractRegisters
  	"Assign the abstract registers with the identities/indices of the relevant concrete registers."
  	"[1] Figure 3.4 Register Usage in
  		System V Application Binary Interface
  		AMD64 Architecture Processor Supplement"
  
  	super initializeAbstractRegisters.
  
  	"N.B. RAX RCX & RDX are caller-save (scratch) registers.  Hence we use RCX for class and RDX for
  		receiver/result since these are written in all normal sends."
  
+ 	SysV
- 	ABI = #SysV
  		ifTrue: [self initializeAbstractRegistersSysV]
  		ifFalse: [self initializeAbstractRegistersWin64]!

Item was added:
+ ----- Method: CogX64Compiler class>>isSysV (in category 'accessing') -----
+ isSysV
+ 	"Answer true is ABI is SysV, false otherwise (for WIN64)"
+ 	^SysV!

Item was changed:
  ----- Method: CogX64Compiler>>genMarshallNArgs:arg:arg:arg:arg: (in category 'abi') -----
  genMarshallNArgs: numArgs arg: regOrConst0 arg: regOrConst1 arg: regOrConst2 arg: regOrConst3
  	"Generate the code to pass up to four arguments in a C run-time call.  Hack: each argument is
  	 either a negative number, which encodes a constant, or a non-negative number, that of a register.
  
  	 Run-time calls have no more than four arguments, so chosen so that on ARM, where in its C ABI the
  	 first four integer arguments are passed in registers, all arguments can be passed in registers.  We
  	 defer to the back end to generate this code not so much that the back end knows whether it uses
  	 the stack or registers to pass arguments (it does, but...). In fact we defer for an extremely evil reason.
  	 Doing so allows the x64 (where up to 6 args are passed) to assign the register arguments in an order
  	 that allows some of the argument registers to be used for specific abstract  registers, specifically
  	 ReceiverResultReg and ClassReg.  This is evil, evil, evil, but also it's really nice to keep using the old
  	 register assignments the original author has grown accustomed to.
  
  	 How can this possibly work?  Look at Cogit class>>runtime for a list of the run-time calls and their
  	 arguments, including which arguments are passed in which registers.  Look at CogX64Compiler's
  	 subclass implementations of initializeAbstractRegisters.  There are no calls in which ReceiverResultReg
  	 (RDX) and/or ClassReg (RCX) are passed along with Arg0Reg and Arg1Reg, and none in which the use of
  	 either ReceiverResultReg or ClassReg conflict for args 3 & 4.  So if args are assigned in order, the
  	 registers do not get overwritten.  Yes, this is evil, but it's so nice to continue to use RCX & RDX.
  
  	 Argument registers for args 0 to 3 in SysV are RDI RSI RDX RCX, and in Win64 are RCX RDX R8 R9"
  	<inline: true>
  	self 
+ 		cppIf: SysV
+ 		ifTrue: []
+ 		ifFalse:
- 		cppIf: #WIN64
- 		ifTrue:
  			["WIN64 ABI allways reserve shadow space on the stack for callee to save up to 4 register parameters"
  			cogit SubCq: 32 R: RSP].
  	numArgs = 0 ifTrue: [^self].
  	self 
+ 		cppIf: SysV
- 		cppIf: #WIN64
  		ifTrue:
  			[(cogit isTrampolineArgConstant: regOrConst0)
+ 				ifTrue: [cogit MoveCq: (cogit trampolineArgValue: regOrConst0) R: RDI] "a.k.a. Arg0Reg"
- 				ifTrue: [cogit MoveCq: (cogit trampolineArgValue: regOrConst0) R: RCX] "a.k.a. Arg0Reg"
  				ifFalse:
+ 					[regOrConst0 ~= RDI ifTrue:
+ 						[cogit MoveR: regOrConst0 R: RDI]].
- 					[regOrConst0 ~= RCX ifTrue:
- 						[cogit MoveR: regOrConst0 R: RCX]].
  			numArgs = 1 ifTrue: [^self].
  			(cogit isTrampolineArgConstant: regOrConst1)
+ 				ifTrue: [cogit MoveCq: (cogit trampolineArgValue: regOrConst1) R: RSI] "a.k.a. Arg1Reg"
- 				ifTrue: [cogit MoveCq: (cogit trampolineArgValue: regOrConst1) R: RDX] "a.k.a. Arg1Reg"
  				ifFalse:
+ 					[regOrConst1 ~= RSI ifTrue:
+ 						[cogit MoveR: regOrConst1 R: RSI]].
- 					[regOrConst1 ~= RDX ifTrue:
- 						[cogit MoveR: regOrConst1 R: RDX]].
  			numArgs = 2 ifTrue: [^self].
  			(cogit isTrampolineArgConstant: regOrConst2)
+ 				ifTrue: [cogit MoveCq: (cogit trampolineArgValue: regOrConst2) R: RDX] "a.k.a. ReceiverResultReg"
- 				ifTrue: [cogit MoveCq: (cogit trampolineArgValue: regOrConst2) R: R8] "a.k.a. RISCTempReg in CogInLineLiteralsX64Compiler and Extra6Reg in CogOutOfLineLiteralsX64Compiler"
  				ifFalse:
+ 					[regOrConst2 ~= RDX ifTrue:
+ 						[cogit MoveR: regOrConst2 R: RDX]].
- 					[regOrConst2 ~= R8 ifTrue:
- 						[cogit MoveR: regOrConst2 R: R8]].
  			 numArgs = 3 ifTrue: [^self].
  			 (cogit isTrampolineArgConstant: regOrConst3)
+ 					ifTrue: [cogit MoveCq: (cogit trampolineArgValue: regOrConst3) R: RCX] "a.k.a. ClassReg"
- 					ifTrue: [cogit MoveCq: (cogit trampolineArgValue: regOrConst3) R: R9] "a.k.a. SendNumArgsReg"
  					ifFalse:
+ 						[regOrConst3 ~= RCX ifTrue:
+ 							[cogit MoveR: regOrConst3 R: RCX]]]
- 						[regOrConst3 ~= R9 ifTrue:
- 							[cogit MoveR: regOrConst3 R: R9]]]
  		ifFalse:
  			[(cogit isTrampolineArgConstant: regOrConst0)
+ 				ifTrue: [cogit MoveCq: (cogit trampolineArgValue: regOrConst0) R: RCX] "a.k.a. Arg0Reg"
- 				ifTrue: [cogit MoveCq: (cogit trampolineArgValue: regOrConst0) R: RDI] "a.k.a. Arg0Reg"
  				ifFalse:
+ 					[regOrConst0 ~= RCX ifTrue:
+ 						[cogit MoveR: regOrConst0 R: RCX]].
- 					[regOrConst0 ~= RDI ifTrue:
- 						[cogit MoveR: regOrConst0 R: RDI]].
  			numArgs = 1 ifTrue: [^self].
  			(cogit isTrampolineArgConstant: regOrConst1)
+ 				ifTrue: [cogit MoveCq: (cogit trampolineArgValue: regOrConst1) R: RDX] "a.k.a. Arg1Reg"
- 				ifTrue: [cogit MoveCq: (cogit trampolineArgValue: regOrConst1) R: RSI] "a.k.a. Arg1Reg"
  				ifFalse:
+ 					[regOrConst1 ~= RDX ifTrue:
+ 						[cogit MoveR: regOrConst1 R: RDX]].
- 					[regOrConst1 ~= RSI ifTrue:
- 						[cogit MoveR: regOrConst1 R: RSI]].
  			numArgs = 2 ifTrue: [^self].
  			(cogit isTrampolineArgConstant: regOrConst2)
+ 				ifTrue: [cogit MoveCq: (cogit trampolineArgValue: regOrConst2) R: R8] "a.k.a. RISCTempReg in CogInLineLiteralsX64Compiler and Extra6Reg in CogOutOfLineLiteralsX64Compiler"
- 				ifTrue: [cogit MoveCq: (cogit trampolineArgValue: regOrConst2) R: RDX] "a.k.a. ReceiverResultReg"
  				ifFalse:
+ 					[regOrConst2 ~= R8 ifTrue:
+ 						[cogit MoveR: regOrConst2 R: R8]].
- 					[regOrConst2 ~= RDX ifTrue:
- 						[cogit MoveR: regOrConst2 R: RDX]].
  			 numArgs = 3 ifTrue: [^self].
  			 (cogit isTrampolineArgConstant: regOrConst3)
+ 					ifTrue: [cogit MoveCq: (cogit trampolineArgValue: regOrConst3) R: R9] "a.k.a. SendNumArgsReg"
- 					ifTrue: [cogit MoveCq: (cogit trampolineArgValue: regOrConst3) R: RCX] "a.k.a. ClassReg"
  					ifFalse:
+ 						[regOrConst3 ~= R9 ifTrue:
+ 							[cogit MoveR: regOrConst3 R: R9]]].
- 						[regOrConst3 ~= RCX ifTrue:
- 							[cogit MoveR: regOrConst3 R: RCX]]].
  	self assert: numArgs <= 4!

Item was changed:
  ----- Method: CogX64Compiler>>genRemoveNArgsFromStack: (in category 'abi') -----
  genRemoveNArgsFromStack: n
  	"This is a no-op on x64 SysV since the ABI passes up to 6 args in registers and trampolines currently observe a limit of 4.
  	But the WIN64 ABI allways reserve shadow space for saving up to 4 parameter registers (even if less than 4 args)."
  	self assert: n <= 4.
+ 	self cppIf: SysV ifTrue: [] ifFalse:
- 	self cppIf: #WIN64 ifTrue:
  		[cogit AddCq: 32 R: RSP].
  	^0!

Item was changed:
  ----- Method: CogX64Compiler>>numIntRegArgs (in category 'accessing') -----
  numIntRegArgs
  	self
+ 		cppIf: SysV
+ 		ifTrue: [^6]
+ 		ifFalse: [^4]!
- 		cppIf: #WIN64
- 		ifTrue: [^4]
- 		ifFalse: [^6]!

Item was changed:
  ----- Method: Cogit>>compileCallFor:numArgs:floatArg:floatArg:floatArg:floatArg:resultReg:regsToSave: (in category 'initialization') -----
  compileCallFor: aRoutine numArgs: numArgs floatArg: regOrConst0 floatArg: regOrConst1 floatArg: regOrConst2 floatArg: regOrConst3 resultReg: resultRegOrNone regsToSave: regMask
  	"Generate a call to aRoutine with up to 4 arguments.  If resultRegOrNone is not
  	 NoReg assign the C result to resultRegOrNone.  If saveRegs, save all registers.
  	 Hack: a negative arg value indicates an abstract register, a non-negative value
  	 indicates a constant."
  	<option: #LowcodeVM>
  	<var: #aRoutine type: #'void *'>
  	<inline: false>
  	| regsToSave |
  	regsToSave := resultRegOrNone = NoReg
  						ifTrue: [regMask]
  						ifFalse: [regMask bitClear: (self registerMaskFor: resultRegOrNone)].
  	cStackAlignment > objectMemory wordSize ifTrue:
  		[backEnd
  			genAlignCStackSavingRegisters: regsToSave
  			numArgs: numArgs
  			wordAlignment: cStackAlignment / objectMemory wordSize].
  	backEnd
  		genSaveRegs: regsToSave;
  		genMarshallNArgs: numArgs floatArg: regOrConst0 floatArg: regOrConst1 floatArg: regOrConst2 floatArg: regOrConst3.
  	self CallFullRT: (self cCode: [aRoutine asUnsignedInteger]
  						inSmalltalk: [self simulatedTrampolineFor: aRoutine]).
  	resultRegOrNone ~= NoReg ifTrue:
  		[backEnd genWriteCResultIntoReg: resultRegOrNone].
+ 	backEnd genRemoveNFloatArgsFromStack: numArgs.
- 	 numArgs > 0 ifTrue:
- 		[backEnd genRemoveNFloatArgsFromStack: numArgs].
  	backEnd genRestoreRegs: regsToSave!



More information about the Vm-dev mailing list