VM Maker: VMMaker.oscog-eem.2626.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.2626.mcz

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

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

Name: VMMaker.oscog-eem.2626
Author: eem
Time: 21 December 2019, 6:52:08.313069 pm
UUID: 83edb826-6857-47fe-bbf6-cadecbc72358
Ancestors: VMMaker.oscog-eem.2625

In calling machine code primitives on RISCs we must save & restore the link register around the call. We haven' noticed this issue before because we only have one mcprim (hashMultiply) and that gets implemeted entirtely in generated machine code if a processor implements MulRR.  ARMv8 will impl,ement MulRR but doesn't as yet, and so because the first RISC to call an mcprim, uncovering the bug.

Since we're interested in performance and there are typically regsietrfs to spare on RISC define saveAndRestoreLinkRegUsingCalleeSavedRegNotLiveAtPointOfSendAround: instead of using saveAndRestoreLinkRegAround: so that the Linkreg gets written and read from an available callee-saved reg (if available).

Simulation:
Make the checking of return addresses more precise; require that the pc we end up at is the return pc.

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

Item was added:
+ ----- Method: CogARMCompiler>>saveAndRestoreLinkRegUsingCalleeSavedRegNotLiveAtPointOfSendAround: (in category 'abi') -----
+ saveAndRestoreLinkRegUsingCalleeSavedRegNotLiveAtPointOfSendAround: aBlock
+ "Extra1Reg is callee-saved and not live at point of send."
+ <inline: #always>
+ | inst |
+ inst := cogit MoveR: LinkReg R: Extra1Reg.
+ aBlock value.
+ cogit MoveR: Extra1Reg R: LinkReg.
+ ^inst!

Item was added:
+ ----- Method: CogAbstractInstruction>>saveAndRestoreLinkRegUsingCalleeSavedRegNotLiveAtPointOfSendAround: (in category 'abi') -----
+ saveAndRestoreLinkRegUsingCalleeSavedRegNotLiveAtPointOfSendAround: aBlock
+ "If the processor's ABI includes a link register, generate instructions
+ to save and restore it in a callee-saved register (if available) or on the stack around aBlock, which is assumed to generate code.
+ By default, do nothing.  RISCs override."
+ <inline: #always>
+ ^aBlock value!

Item was changed:
  ----- Method: Cogit>>handleCallOrJumpSimulationTrap: (in category 'simulation only') -----
  handleCallOrJumpSimulationTrap: aProcessorSimulationTrap
  <doNotGenerate>
+ | evaluable function memory result savedFramePointer savedStackPointer savedArgumentCount leaf retpc |
- | evaluable function memory result savedFramePointer savedStackPointer savedArgumentCount leaf |
  evaluable := simulatedTrampolines
  at: aProcessorSimulationTrap address
  ifAbsent: [self errorProcessingSimulationTrap: aProcessorSimulationTrap
  in: simulatedTrampolines].
  function := evaluable isBlock
  ifTrue: ['aBlock; probably some plugin primitive']
  ifFalse:
  [evaluable receiver == backEnd ifTrue:
  [^self handleABICallOrJumpSimulationTrap: aProcessorSimulationTrap evaluable: evaluable].
  evaluable selector].
  function ~~ #ceBaseFrameReturn: ifTrue:
  [coInterpreter assertValidExternalStackPointers].
  (backEnd wantsNearAddressFor: function) ifTrue:
  [^self perform: function with: aProcessorSimulationTrap].
  memory := coInterpreter memory.
  aProcessorSimulationTrap type == #call
  ifTrue:
  [(leaf := coInterpreter mcprims includes: function)
  ifTrue:
  [processor
  simulateLeafCallOf: aProcessorSimulationTrap address
  nextpc: aProcessorSimulationTrap nextpc
+ memory: memory.
+ retpc := processor leafRetpcIn: memory]
- memory: memory]
  ifFalse:
  [processor
  simulateCallOf: aProcessorSimulationTrap address
  nextpc: aProcessorSimulationTrap nextpc
+ memory: memory.
+ retpc := processor retpcIn: memory].
- memory: memory].
  self recordInstruction: {'(simulated call of '. aProcessorSimulationTrap address. '/'. function. ')'}]
  ifFalse:
  [leaf := false.
  processor
  simulateJumpCallOf: aProcessorSimulationTrap address
  memory: memory.
+ retpc := processor retpcIn: memory. "sideways call; the primitive has pushed a return address."
  self recordInstruction: {'(simulated jump to '. aProcessorSimulationTrap address. '/'. function. ')'}].
  savedFramePointer := coInterpreter framePointer.
  savedStackPointer := coInterpreter stackPointer.
  savedArgumentCount := coInterpreter argumentCount.
  result := ["self halt: evaluable selector."
      ((printRegisters or: [printInstructions]) and: [clickConfirm]) ifTrue:
  [(self confirm: 'skip run-time call?') ifFalse:
  [clickConfirm := false. self halt]].
    evaluable valueWithArguments: (processor
  postCallArgumentsNumArgs: evaluable numArgs
  in: memory)]
  on: ReenterMachineCode
  do: [:ex| ex return: ex returnValue].
 
  coInterpreter assertValidExternalStackPointers.
  "Verify the stack layout assumption compileInterpreterPrimitive: makes, provided we've
  not called something that has built a frame, such as closure value or evaluate method, or
  switched frames, such as primitiveSignal, primitiveWait, primitiveResume, primitiveSuspend et al."
  (function beginsWith: 'primitive') ifTrue:
  [coInterpreter checkForLastObjectOverwrite.
  coInterpreter primFailCode = 0
  ifTrue: [(#( primitiveClosureValue primitiveClosureValueWithArgs primitiveClosureValueNoContextSwitch
  primitiveFullClosureValue primitiveFullClosureValueWithArgs primitiveFullClosureValueNoContextSwitch
  primitiveSignal primitiveWait primitiveResume primitiveSuspend primitiveYield
  primitiveExecuteMethodArgsArray primitiveExecuteMethod
  primitivePerform primitivePerformWithArgs primitivePerformInSuperclass
  primitiveTerminateTo primitiveStoreStackp primitiveDoPrimitiveWithArgs)
  includes: function) ifFalse:
  ["This is a rare case (e.g. in Scorch where a married context's sender is set to nil on trapTrpped and hence the stack layout is altered."
  (function == #primitiveSlotAtPut and: [objectMemory isContext: (coInterpreter frameReceiver: coInterpreter framePointer)]) ifFalse:
  [self assert: savedFramePointer = coInterpreter framePointer.
  self assert: savedStackPointer + (savedArgumentCount * objectMemory wordSize)
  = coInterpreter stackPointer]]]
  ifFalse:
  [self assert: savedFramePointer = coInterpreter framePointer.
  self assert: savedStackPointer = coInterpreter stackPointer]].
  result ~~ #continueNoReturn ifTrue:
  [self recordInstruction: {'(simulated return to '. processor retpcIn: memory. ')'}.
  leaf
  ifTrue: [processor simulateLeafReturnIn: memory]
  ifFalse: [processor simulateReturnIn: memory].
+ self assert: processor pc = retpc.
- self assert: (processor pc between: codeBase and: methodZone freeStart).
  processor smashCallerSavedRegistersWithValuesFrom: 16r80000000 by: objectMemory wordSize in: memory].
  self assert: (result isInteger "an oop result"
  or: [result == coInterpreter
  or: [result == objectMemory
  or: [#(nil continue continueNoReturn) includes: result]]]).
  processor cResultRegister: (result
  ifNil: [0]
  ifNotNil: [result isInteger
  ifTrue: [result]
  ifFalse: [16rF00BA222]])
 
  "coInterpreter cr.
  processor sp + 32 to: processor sp - 32 by: -4 do:
  [:sp|
  sp = processor sp
  ifTrue: [coInterpreter print: 'sp->'; tab]
  ifFalse: [coInterpreter printHex: sp].
  coInterpreter tab; printHex: (coInterpreter longAt: sp); cr]"!

Item was changed:
  ----- Method: SimpleStackBasedCogit>>compileMachineCodeInterpreterPrimitive: (in category 'primitive generators') -----
  compileMachineCodeInterpreterPrimitive: primitiveRoutine
  "Compile a call to a machine-code convention interpreter primitive.  Call the C routine
  on the Smalltalk stack, assuming it consumes little or no stack space."
  <var: #primitiveRoutine declareC: 'void (*primitiveRoutine)(void)'>
  | jmpFail liveRegsMask |
  "for now handle functions with less than 4 arguments; our C call marshalling machinery
  extends up to 4 arguments only, and the first argument of an mcprim is the receiver."
  self assert: methodOrBlockNumArgs <= 3.
  liveRegsMask := (methodOrBlockNumArgs > self numRegArgs
    or: [methodOrBlockNumArgs = 0])
  ifTrue:
  [self registerMaskFor: ReceiverResultReg]
  ifFalse:
  [(self numRegArgs > 1 and: [methodOrBlockNumArgs > 1])
  ifFalse: [self registerMaskFor: ReceiverResultReg and: Arg0Reg]
  ifTrue: [self registerMaskFor: ReceiverResultReg and: Arg0Reg and: Arg1Reg]].
  backEnd genSaveRegs: (liveRegsMask bitAnd: CallerSavedRegisterMask).
  methodOrBlockNumArgs > self numRegArgs ifTrue:
  ["Wrangle args into Arg0Reg, Arg1Reg, SendNumArgsReg & ClassReg"
  "offset := self bitCountOf: (liveRegsMask bitAnd: CallerSavedRegisterMask)."
  self shouldBeImplemented].
  backEnd
  genMarshallNArgs: methodOrBlockNumArgs + 1
  arg: ReceiverResultReg
  arg: Arg0Reg
  arg: Arg1Reg
  arg: SendNumArgsReg
  "arg: ClassReg (when we extend C call marchalling to support 5 args for replaceFrom:to:with:startingAt:".
+ backEnd saveAndRestoreLinkRegUsingCalleeSavedRegNotLiveAtPointOfSendAround:
+ [self CallFullRT: primitiveRoutine asInteger].
- self CallFullRT: primitiveRoutine asInteger.
  backEnd
  genRemoveNArgsFromStack: methodOrBlockNumArgs + 1;
  genRestoreRegs: (liveRegsMask bitAnd: CallerSavedRegisterMask).
  self CmpCq: 0 R: backEnd cResultRegister.
  jmpFail := self JumpZero: 0.
  backEnd cResultRegister ~= ReceiverResultReg ifTrue:
  [self MoveR: backEnd cResultRegister R: ReceiverResultReg].
  self RetN: (methodOrBlockNumArgs > self numRegArgs
  ifTrue: [methodOrBlockNumArgs + 1 * objectMemory wordSize]
  ifFalse: [0]).
  jmpFail jmpTarget: self Label.
  ^0!