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

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

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

Name: VMMaker.oscog-eem.2223
Author: eem
Time: 27 May 2017, 8:56:50.429078 am
UUID: 9eb5defa-0b35-4377-a2d5-6456742d0719
Ancestors: VMMaker.oscog-eem.2222

Cogit simulation:
Provide support for smashing the shadow parameter space by refactoring smashCallerSavedRegistersWithValuesFrom:by: to smashCallerSavedRegistersWithValuesFrom:by:in:.  Needs Cog-eem.341

Remove a couple of unused and dubious methods in the CogAbstractInstruction hierarchy.

Reduce the result of fromIEEE64BitWord: to a SmallFloat64 when possible.

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

Item was removed:
- ----- Method: CogARMCompiler>>genRestoreRegsExcept: (in category 'abi') -----
- genRestoreRegsExcept: abstractReg
- "Restore the general purpose registers except for abstractReg for a trampoline call."
- "Restore none, because the ARM ABI only defines callee saved registers, no caller-saved regs."
- !

Item was removed:
- ----- Method: CogARMCompiler>>numberOfSaveableRegisters (in category 'abi') -----
- numberOfSaveableRegisters
- "Answer the number of registers to be saved in a trampoline call that saves registers.
- None, See genSaveRegisters."
- <cmacro: '(self) 0'>
- ^0!

Item was removed:
- ----- Method: CogAbstractInstruction>>numberOfSaveableRegisters (in category 'abi') -----
- numberOfSaveableRegisters
- "Answer the number of registers to be saved in a trampoline call that saves registers.
- See genSaveRegisters"
- self subclassResponsibility!

Item was removed:
- ----- Method: CogIA32Compiler>>genRestoreRegsExcept: (in category 'abi') -----
- genRestoreRegsExcept: preservedReg
- self assert: (EDI > EAX and: [EDI - EAX + 1 = 6]).
- EAX to: EDI do:
- [:reg|
- (reg between: ESP and: EBP) ifFalse:
- [preservedReg = reg
- ifTrue: [cogit AddCq: 4 R: ESP]
- ifFalse: [cogit PopR: reg]]].
- ^0!

Item was removed:
- ----- Method: CogIA32Compiler>>numberOfSaveableRegisters (in category 'abi') -----
- numberOfSaveableRegisters
- "Answer the number of registers to be saved in a trampoline call that saves registers.
- See genSaveRegisters"
- <cmacro: '(self) 6'>
- ^6!

Item was removed:
- ----- Method: CogMIPSELCompiler>>genRestoreRegsExcept: (in category 'abi') -----
- genRestoreRegsExcept: abstractReg
- "Restore the general purpose registers except for abstractReg for a trampoline call."
- self flag: #bogus.!

Item was removed:
- ----- Method: CogMIPSELCompiler>>numberOfSaveableRegisters (in category 'abi') -----
- numberOfSaveableRegisters
- "Answer the number of registers to be saved in a trampoline call that saves registers.
- None, See genSaveRegisters."
- <cmacro: '(self) 0'>
- ^0!

Item was removed:
- ----- Method: CogX64Compiler>>genRestoreRegsExcept: (in category 'abi') -----
- genRestoreRegsExcept: preservedReg
- self assert: (R15 > RAX and: [R15 - RAX + 1 = 16]).
- RAX to: R15 do:
- [:reg|
- (reg between: RSP and: RBP) ifFalse:
- [preservedReg = reg
- ifTrue: [cogit AddCq: 8 R: RSP]
- ifFalse: [cogit PopR: reg]]].
- ^0!

Item was removed:
- ----- Method: CogX64Compiler>>numberOfSaveableRegisters (in category 'abi') -----
- numberOfSaveableRegisters
- "Answer the number of registers to be saved in a trampoline call that saves registers.
- See genSaveRegisters"
- <cmacro: '(self) 14'>
- ^14!

Item was changed:
  ----- Method: Cogit>>handleCallOrJumpSimulationTrap: (in category 'simulation only') -----
  handleCallOrJumpSimulationTrap: aProcessorSimulationTrap
  <doNotGenerate>
+ | evaluable function memory result savedFramePointer savedStackPointer savedArgumentCount rpc |
- | evaluable function result savedFramePointer savedStackPointer savedArgumentCount rpc |
  evaluable := simulatedTrampolines at: aProcessorSimulationTrap address.
  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].
  (function beginsWith: 'ceShort') ifTrue:
  [^self perform: function with: aProcessorSimulationTrap].
+ aProcessorSimulationTrap type == #call
- aProcessorSimulationTrap type = #call
  ifTrue:
  [processor
  simulateCallOf: aProcessorSimulationTrap address
  nextpc: aProcessorSimulationTrap nextpc
+ memory: (memory := coInterpreter memory).
+ self recordInstruction: {'(simulated call of '. aProcessorSimulationTrap address. '/'. function. ')'}]
- memory: coInterpreter memory.
- self recordInstruction: {'(simulated call of '. aProcessorSimulationTrap address. '/'. function. ')'}]
  ifFalse:
  [processor
  simulateJumpCallOf: aProcessorSimulationTrap address
+ memory: (memory := coInterpreter memory).
- memory: coInterpreter memory.
  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)]
- in: coInterpreter 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. ')'}.
+ rpc := processor retpcIn: memory.
- [self recordInstruction: {'(simulated return to '. processor retpcIn: coInterpreter memory. ')'}.
- rpc := processor retpcIn: coInterpreter memory.
  self assert: (rpc >= codeBase and: [rpc < methodZone freeStart]).
  processor
+ smashCallerSavedRegistersWithValuesFrom: 16r80000000 by: objectMemory wordSize in: memory;
+ simulateReturnIn: memory].
- smashCallerSavedRegistersWithValuesFrom: 16r80000000 by: objectMemory wordSize;
- simulateReturnIn: coInterpreter 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: Float class>>fromIEEE64BitWord: (in category '*VMMaker-instance creation') -----
  fromIEEE64BitWord: anInteger
+ | value |
+ value := self basicNew: 2.
+ value
- ^(self basicNew: 2)
  basicAt: 1 put: (anInteger bitShift: -32);
+ basicAt: 2 put: (anInteger bitAnd: 16rFFFFFFFF).
+ ^value isFinite
+ ifTrue: [value * 1.0] "reduce to SmallFloat64 if possible"
+ ifFalse: [value]
+
+ "[| r |
+ r := Random new.
+ 100000 timesRepeat:
+ [| h l f |
+ h := (r next * 16r100000000) rounded bitAnd: 16rFFFFFFFF.
+ l := (r next * 16r100000000) rounded bitAnd: 16rFFFFFFFF.
+ f := Float fromIEEE64BitWord: (h bitShift: 32) + l.
+ self assert: h = (f basicAt: 1).
+ self assert: l = (f basicAt: 2)]] timeToRun"!
- basicAt: 2 put: (anInteger bitAnd: 16rFFFFFFFF);
- yourself!