VM Maker: VMMaker.oscog-eem.2927.mcz

Previous Topic Next Topic
 
classic Classic list List threaded Threaded
1 message Options
Reply | Threaded
Open this post in threaded view
|

VM Maker: VMMaker.oscog-eem.2927.mcz

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

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

Name: VMMaker.oscog-eem.2927
Author: eem
Time: 7 January 2021, 2:05:43.745942 pm
UUID: 91ada8ee-d8ae-4034-ba1d-3da323ba1a3d
Ancestors: VMMaker.oscog-eem.2926

x86/x86_64 Cog MTVM:
Add the code to handle the lock already having the right value to x86/x86_64 generateLowLevelTryLock:.
Extend handleCompareAndSwapSimulationTrap: to simulate x86/x86_64 cmpxchg (add failedComparisonRegisterAccessor to the mix).
Always use a REX prefix for SETE.
Categorize all processor specific opcode generators under concretize processor-specific

Still the x86_64 low-level lock dfoesn't simulate correctly.  I suspect that setting the flags word doesn't actually set the flags in the plugin.

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

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

Item was changed:
+ ----- Method: CogX64Compiler>>concretizeBSR (in category 'generate machine code - concretize processor-specific') -----
- ----- Method: CogX64Compiler>>concretizeBSR (in category 'generate machine code - concretize') -----
  concretizeBSR
  "Bit Scan Reverse
  First operand is input register (mask)
  Second operand is output register (dest)"
  "BSR"
  <inline: true>
  | dest maskReg |
  maskReg := operands at: 0.
  dest := operands at: 1.
  machineCode
  at: 0 put: (self rexw: true r: dest x: 0 b: maskReg);
  at: 1 put: 16r0F;
  at: 2 put: 16rBD;
  at: 3 put: (self mod: ModReg RM: maskReg RO: dest).
  ^4!

Item was changed:
+ ----- Method: CogX64Compiler>>concretizeCDQ (in category 'generate machine code - concretize processor-specific') -----
- ----- Method: CogX64Compiler>>concretizeCDQ (in category 'generate machine code - concretize') -----
  concretizeCDQ
  "Will get inlined into concretizeAt: switch."
  <inline: true>
  machineCode
  at: 0 put: 16r48;
  at: 1 put: 16r99.
  ^2!

Item was changed:
+ ----- Method: CogX64Compiler>>concretizeCLD (in category 'generate machine code - concretize processor-specific') -----
- ----- Method: CogX64Compiler>>concretizeCLD (in category 'generate machine code - concretize') -----
  concretizeCLD
  <inline: true>
  machineCode at: 0 put: 16rFC.
  ^1!

Item was changed:
+ ----- Method: CogX64Compiler>>concretizeCPUID (in category 'generate machine code - concretize processor-specific') -----
- ----- Method: CogX64Compiler>>concretizeCPUID (in category 'generate machine code - concretize') -----
  concretizeCPUID
  <inline: true>
  machineCode
  at: 0 put: 16r0F;
  at: 1 put: 16rA2.
  ^2!

Item was changed:
+ ----- Method: CogX64Compiler>>concretizeIDIVR (in category 'generate machine code - concretize processor-specific') -----
- ----- Method: CogX64Compiler>>concretizeIDIVR (in category 'generate machine code - concretize') -----
  concretizeIDIVR
  "Will get inlined into concretizeAt: switch."
  <inline: true>
  | regDivisor |
  regDivisor := operands at: 0.
  machineCode
  at: 0 put: (self rexR: 0 x: 0 b: regDivisor);
  at: 1 put: 16rF7;
  at: 2 put: (self mod: ModReg RM: regDivisor RO: 7).
  ^3!

Item was changed:
+ ----- Method: CogX64Compiler>>concretizeLOCK (in category 'generate machine code - concretize processor-specific') -----
- ----- Method: CogX64Compiler>>concretizeLOCK (in category 'pro') -----
  concretizeLOCK
  <inline: true>
  machineCode at: 0 put: 16rF0.
  ^1!

Item was changed:
+ ----- Method: CogX64Compiler>>concretizeMOVSB (in category 'generate machine code - concretize processor-specific') -----
- ----- Method: CogX64Compiler>>concretizeMOVSB (in category 'generate machine code - concretize') -----
  concretizeMOVSB
  <inline: true>
  machineCode at: 0 put: 16rA4.
  ^1!

Item was changed:
+ ----- Method: CogX64Compiler>>concretizeMOVSQ (in category 'generate machine code - concretize processor-specific') -----
- ----- Method: CogX64Compiler>>concretizeMOVSQ (in category 'generate machine code - concretize') -----
  concretizeMOVSQ
  <inline: true>
  machineCode
  at: 0 put: (self rexw: true r: 0 x: 0 b: 0);
  at: 1 put: 16rA5.
  ^2!

Item was changed:
+ ----- Method: CogX64Compiler>>concretizeMoveRAwNoVBR (in category 'generate machine code - concretize processor-specific') -----
- ----- Method: CogX64Compiler>>concretizeMoveRAwNoVBR (in category 'generate machine code - concretize') -----
  concretizeMoveRAwNoVBR
  "A version of concretizeMoveRAw tat does not use VarBaseReg."
  <inline: true>
  | addressOperand reg offset |
  reg := operands at: 0.
  addressOperand := operands at: 1.
  (self isAnInstruction: (cogit cCoerceSimple: addressOperand to: #'AbstractInstruction *')) ifTrue:
  [addressOperand := (cogit cCoerceSimple: addressOperand to: #'AbstractInstruction *') address].
  "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 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:
+ ----- Method: CogX64Compiler>>concretizeREP (in category 'generate machine code - concretize processor-specific') -----
- ----- Method: CogX64Compiler>>concretizeREP (in category 'generate machine code - concretize') -----
  concretizeREP
  <inline: true>
  machineCode at: 0 put: 16rF3.
  ^1!

Item was changed:
+ ----- Method: CogX64Compiler>>concretizeSet: (in category 'generate machine code - concretize processor-specific') -----
- ----- Method: CogX64Compiler>>concretizeSet: (in category 'proc') -----
  concretizeSet: conditionCode
+ | reg |
+ reg := operands at: 0.
- | reg offset |
- offset := (reg := operands at: 0) >= R8
- ifTrue: [machineCode at: 0 put: 16r40.
- 1]
- ifFalse: [0].
  machineCode
+ at: 0 put: (reg >= R8 ifTrue: [16r44] ifFalse: [16r40]);
+ at: 1 put: 16r0F;
+ at: 2 put: 16r90 + conditionCode;
+ at: 3 put: (self mod: ModReg RM: (reg bitAnd: 7) RO: 0).
- at: 0 + offset put: 16r0F;
- at: 1 + offset put: 16r90 + conditionCode;
- at: 2 + offset put: (self mod: ModReg RM: (reg bitAnd: 7) RO: 0).
  "cogit processor disassembleInstructionAt: 0 In: machineCode object"
+ ^4!
- ^3 + offset!

Item was changed:
+ ----- Method: CogX64Compiler>>concretizeXCHGRR (in category 'generate machine code - concretize processor-specific') -----
- ----- Method: CogX64Compiler>>concretizeXCHGRR (in category 'generate machine code - concretize') -----
  concretizeXCHGRR
  | r1 r2 |
  r1 := operands at: 0.
  r2 := operands at: 1.
  r2 = RAX ifTrue:
  [r2 := r1. r1 := RAX].
  r1 = RAX ifTrue:
  [machineCode
  at: 0 put: (self rexR: 0 x: 0 b: r2);
  at: 1 put: 16r90 + (r2 \\ 8).
  ^2].
  machineCode
  at: 0 put: (self rexR: r1 x: 0 b: r2);
  at: 1 put: 16r87;
  at: 2 put: (self mod: ModReg RM: r2 RO: r1).
  ^3!

Item was changed:
  ----- Method: CogX64Compiler>>generateLowLevelTryLock: (in category 'multi-threading') -----
  generateLowLevelTryLock: vmOwnerLockAddress
  "Generate a function that attempts to lock the vmOwnerLock and answers if it succeeded."
  <inline: true>
+ | vmOwnerLockAddressReg jumpEqual |
- | vmOwnerLockAddressReg |
  vmOwnerLockAddress = 0 ifTrue:
  [cogit
  MoveCq: 1 R: ABIResultReg;
  RetN: 0.
  ^self].
  "RAX holds the value of lock if unlocked (zero), receives the existing value of the lock; RAX is implicit in CMPXCHG"
  vmOwnerLockAddressReg := CArg1Reg.
  cogit
  MoveCq: 0 R: RAX;
  MoveCq: vmOwnerLockAddress R: vmOwnerLockAddressReg;
  gen: LOCK;
+ gen: CMPXCHGRMr operand: CArg0Reg operand: vmOwnerLockAddressReg.
+ jumpEqual := cogit JumpZero: 0.
+ cogit CmpR: CArg0Reg R: RAX. "If not equal to zero is it already equal to the desired value?"
+ jumpEqual jmpTarget: (cogit gen: SETE operand: ABIResultReg).
+ cogit RetN: 0!
- gen: CMPXCHGRMr operand: CArg0Reg operand: vmOwnerLockAddressReg;
- gen: SETE operand: ABIResultReg;
- RetN: 0!

Item was changed:
  ----- Method: CogX64Compiler>>numLowLevelLockOpcodes (in category 'multi-threading') -----
  numLowLevelLockOpcodes
  <inline: #always>
  "ceTryLockVMOwner:
  xorq %rax, %rax
  movq &vmOwnerLock, %rsi
  lock cmpxchgq %rdi, (%rsi) N.B. lock cmpxchgq are two separate opcodes
+ jz equal
+ cmpq %rdi, %rax
+ equal:
  setz %alt
  ret"
+ ^8!
- ^6!

Item was changed:
  ----- Method: Cogit>>handleCompareAndSwapSimulationTrap: (in category 'simulation only') -----
  handleCompareAndSwapSimulationTrap: aCompareAndSwapSimulationTrap
  | variableValue |
  variableValue := (simulatedVariableGetters
  at: aCompareAndSwapSimulationTrap address
  ifAbsent: [self errorProcessingSimulationTrap: aCompareAndSwapSimulationTrap
  in: simulatedVariableGetters])
  value asInteger.
+ variableValue = aCompareAndSwapSimulationTrap expectedValue
+ ifTrue:
+ [(simulatedVariableSetters
+ at: aCompareAndSwapSimulationTrap address
+ ifAbsent: [self errorProcessingSimulationTrap: aCompareAndSwapSimulationTrap
+ in: simulatedVariableSetters]) value: aCompareAndSwapSimulationTrap storedValue.
+ processor
+ setFlagsForCompareAndSwap: true;
+ perform: aCompareAndSwapSimulationTrap registerAccessor
+ with: (processor convertIntegerToInternal: variableValue)]
+ ifFalse:
+ [processor
+ setFlagsForCompareAndSwap: false;
+ perform: aCompareAndSwapSimulationTrap failedComparisonRegisterAccessor
+ with: (processor convertIntegerToInternal: variableValue)].
- processor setFlagsForCompareAndSwap: variableValue = aCompareAndSwapSimulationTrap expectedValue.
- variableValue = aCompareAndSwapSimulationTrap expectedValue ifTrue:
- [(simulatedVariableSetters
- at: aCompareAndSwapSimulationTrap address
- ifAbsent: [self errorProcessingSimulationTrap: aCompareAndSwapSimulationTrap
- in: simulatedVariableSetters]) value: aCompareAndSwapSimulationTrap storedValue].
- processor
- perform: aCompareAndSwapSimulationTrap registerAccessor
- with: (processor convertIntegerToInternal: variableValue).
  processor pc: aCompareAndSwapSimulationTrap nextpc.
  aCompareAndSwapSimulationTrap resume: processor!