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

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

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

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

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

Name: VMMaker.oscog-eem.1565
Author: eem
Time: 7 December 2015, 5:25:51.389 pm
UUID: 98c5bc39-e721-42ba-9bac-5b1dbfc0963b
Ancestors: VMMaker.oscog-EstebanLorenzano.1564

x64 Cogit:
Half-fix StackToRegisterMappingCogit>>genDoubleArithmetic:preOpCheck: so as not to produce a bogus value when faced with a smallFloat arg.  With this fix the simulator generates output in an emergency evaluator complaining of a primitive failure (which wouldn't fail wityh conversion of smallFloat args).  (Still have to define it for SimpleStackBasedCogit).

Implement the default do-nothing maybeGenConvertIfSmallFloatIn:into:andJumpTo: which will soon provide the relevant conversion.

Rename genLoadHeader:intoNewInstance:using: to genStoreHeader:intoNewInstance:using:, which is what it does.

Eliminate the unnecessary nop when MoveCqR uses MoveCwR to generate a long constant.

=============== Diff against VMMaker.oscog-EstebanLorenzano.1564 ===============

Item was changed:
  ----- Method: CogInLineLiteralsX64Compiler>>concretizeMoveCwR (in category 'generate machine code') -----
  concretizeMoveCwR
  "Will get inlined into concretizeAt: switch."
  <inline: true>
  | value reg offset |
  value := operands at: 0.
  reg := self concreteRegister: (operands at: 1).
  (self isAnInstruction: (cogit cCoerceSimple: value to: #'AbstractInstruction *')) ifTrue:
  [value := (cogit cCoerceSimple: value to: #'AbstractInstruction *') address].
  (cogit addressIsInCurrentCompilation: value) ifTrue:
  [offset := value - (address + 7).
  machineCode
  at: 0 put: (self rexR: reg x: 0 b: 0);
  at: 1 put: 16r8D; "LoadEffectiveAddress"
  at: 2 put: (self mod: ModRegInd RM: 5 RO: reg);
  at: 3 put: (offset bitAnd: 16rFF);
  at: 4 put: (offset >> 8 bitAnd: 16rFF);
  at: 5 put: (offset >> 16 bitAnd: 16rFF);
  at: 6 put: (offset >> 24 bitAnd: 16rFF).
  ^machineCodeSize := 7].
  machineCode
  at:  0 put: (self rexR: reg x: 0 b: reg);
  at:  1 put: 16rB8 + (reg bitAnd: 7);
  at:  2 put: (value bitAnd: 16rFF);
  at:  3 put: (value >> 8 bitAnd: 16rFF);
  at:  4 put: (value >> 16 bitAnd: 16rFF);
  at:  5 put: (value >> 24 bitAnd: 16rFF);
  at:  6 put: (value >> 32 bitAnd: 16rFF);
  at:  7 put: (value >> 40 bitAnd: 16rFF);
  at:  8 put: (value >> 48 bitAnd: 16rFF);
+ at:  9 put: (value >> 56 bitAnd: 16rFF).
+ opcode = MoveCqR ifTrue:
+ [^machineCodeSize := 10].
+ "Add a nop to disambiguate between MoveCwR/PushCwR and ArithCwR, which ends with a (self mod: ModReg RM: 0 RO: 0)"
+ machineCode at: 10 put: 16r90.
- at:  9 put: (value >> 56 bitAnd: 16rFF);
- at: 10 put: 16r90. "Add a nop to disambiguate between MoveCwR/PushCwR and ArithCwR, which ends with a (self mod: ModReg RM: 0 RO: 0)"
  self assert: (self mod: ModReg RM: 0 RO: 0) > 16r90.
  ^machineCodeSize := 11!

Item was added:
+ ----- Method: CogObjectRepresentation>>maybeGenConvertIfSmallFloatIn:into:andJumpTo: (in category 'primitive generators') -----
+ maybeGenConvertIfSmallFloatIn: oopReg into: dpReg andJumpTo: targetInst
+ "If the receiver supports immediate floats then generate a test for a smallFloat in  oopReg,
+ converting it to the float value in dpReg and jumping to targetInst.  Otherwise do nothing."
+ <var: 'targetInst' type: #'AbstractInstruction *'>
+ ^0!

Item was removed:
- ----- Method: CogObjectRepresentationFor32BitSpur>>genLoadHeader:intoNewInstance:using: (in category 'initialization') -----
- genLoadHeader: header intoNewInstance: rcvrReg using: scratchReg
- "Generate the instructions to move the constant header into a new instance pointed to by rcvrReg."
- <inline: true>
- self flag: #endianness.
- cogit
- MoveCq: (self low32BitsOf: header) R: scratchReg;
- MoveR: scratchReg Mw: 0 r: rcvrReg;
- MoveCq: header >> 32 R: scratchReg;
- MoveR: scratchReg Mw: 4 r: rcvrReg!

Item was added:
+ ----- Method: CogObjectRepresentationFor32BitSpur>>genStoreHeader:intoNewInstance:using: (in category 'initialization') -----
+ genStoreHeader: header intoNewInstance: rcvrReg using: scratchReg
+ "Generate the instructions to move the constant header into a new instance pointed to by rcvrReg."
+ <inline: true>
+ self flag: #endianness.
+ cogit
+ MoveCq: (self low32BitsOf: header) R: scratchReg;
+ MoveR: scratchReg Mw: 0 r: rcvrReg;
+ MoveCq: header >> 32 R: scratchReg;
+ MoveR: scratchReg Mw: 4 r: rcvrReg!

Item was removed:
- ----- Method: CogObjectRepresentationFor64BitSpur>>genLoadHeader:intoNewInstance:using: (in category 'initialization') -----
- genLoadHeader: header intoNewInstance: rcvrReg using: scratchReg
- "Generate the instructions to move the constant header into a new instance pointed to by rcvrReg."
- <inline: true>
- cogit
- MoveCq: header R: scratchReg;
- MoveR: TempReg Mw: 0 r: rcvrReg!

Item was added:
+ ----- Method: CogObjectRepresentationFor64BitSpur>>genStoreHeader:intoNewInstance:using: (in category 'initialization') -----
+ genStoreHeader: header intoNewInstance: rcvrReg using: scratchReg
+ "Generate the instructions to move the constant header into a new instance pointed to by rcvrReg."
+ <inline: true>
+ cogit
+ MoveCq: header R: scratchReg;
+ MoveR: scratchReg Mw: 0 r: rcvrReg!

Item was changed:
  ----- Method: CogObjectRepresentationForSpur>>genAllocFloatValue:into:scratchReg:scratchReg: (in category 'primitive generators') -----
  genAllocFloatValue: dpreg into: resultReg scratchReg: scratch1 scratchReg: scratch2
  <returnTypeC: #'AbstractInstruction *'>
  | allocSize newFloatHeader jumpFail |
  <var: #jumpFail type: #'AbstractInstruction *'>
  allocSize := objectMemory baseHeaderSize + (objectMemory sizeof: #double).
  newFloatHeader := objectMemory
  headerForSlots: (self sizeof: #double) / objectMemory wordSize
  format: objectMemory firstLongFormat
  classIndex: ClassFloatCompactIndex.
  cogit MoveAw: objectMemory freeStartAddress R: resultReg.
  cogit LoadEffectiveAddressMw: allocSize r: resultReg R: scratch1.
  cogit CmpCq: objectMemory getScavengeThreshold R: scratch1.
  jumpFail := cogit JumpAboveOrEqual: 0.
  cogit MoveR: scratch1 Aw: objectMemory freeStartAddress.
+ self genStoreHeader: newFloatHeader intoNewInstance: resultReg using: scratch1.
- self genLoadHeader: newFloatHeader intoNewInstance: resultReg using: scratch1.
  cogit MoveRd: dpreg M64: objectMemory baseHeaderSize r: resultReg.
  ^jumpFail!

Item was changed:
  ----- Method: CogObjectRepresentationForSpur>>genGetActiveContextLarge:inBlock: (in category 'initialization') -----
  genGetActiveContextLarge: isLarge inBlock: isInBlock
  "Create a trampoline to answer the active context that will
  answer it if a frame is already married, and create it otherwise.
  Assume numArgs is in SendNumArgsReg and ClassReg is free."
  | header slotSize jumpSingle loopHead jumpNeedScavenge continuation exit |
  <var: #jumpNeedScavenge type: #'AbstractInstruction *'>
  <var: #continuation type: #'AbstractInstruction *'>
  <var: #jumpSingle type: #'AbstractInstruction *'>
  <var: #loopHead type: #'AbstractInstruction *'>
  <var: #exit type: #'AbstractInstruction *'>
  cogit "load the flag; stash it in both TempReg & ClassReg; do the compare (a prime candidated for use of AndCq:R:R:)"
  MoveMw: FoxMethod r: FPReg R: ClassReg;
  AndCq: MFMethodFlagHasContextFlag R: ClassReg R: TempReg.
  jumpSingle := cogit JumpZero: 0. "jump if flag bit not set"
  cogit "since the flag bit was set, get the context in the receiver reg and return"
  MoveMw: FoxThisContext r: FPReg R: ReceiverResultReg;
  RetN: 0.
  jumpSingle jmpTarget: cogit Label.
 
  "OK, it doesn't exist; instantiate and initialize it"
  "set the hasContext flag; See CoInterpreter class>>initializeFrameIndices"
  cogit
  OrCq: MFMethodFlagHasContextFlag R: ClassReg;
  MoveR: ClassReg Mw: FoxMethod r: FPReg.
  "now get the home CogMethod into ClassReg and save for post-instantiation."
  isInBlock
  ifTrue:
  [cogit
  SubCq: 3 R: ClassReg; "-3 is -(hasContext+isBlock) flags"
  MoveM16: 0 r: ClassReg R: TempReg;
  SubR: TempReg R: ClassReg]
  ifFalse:
  [cogit SubCq: 1 R: ClassReg]. "-1 is hasContext flag"
 
  "instantiate the context..."
  slotSize := isLarge ifTrue: [LargeContextSlots] ifFalse: [SmallContextSlots].
  header := objectMemory
  headerForSlots: slotSize
  format: objectMemory indexablePointersFormat
  classIndex: ClassMethodContextCompactIndex.
  self flag: #endianness.
  cogit MoveAw: objectMemory freeStartAddress R: ReceiverResultReg.
+ self genStoreHeader: header intoNewInstance: ReceiverResultReg using: TempReg.
- self genLoadHeader: header intoNewInstance: ReceiverResultReg using: TempReg.
  cogit
  MoveR: ReceiverResultReg R: TempReg;
  AddCq: (objectMemory smallObjectBytesForSlots: slotSize) R: TempReg;
  MoveR: TempReg Aw: objectMemory freeStartAddress;
  CmpCq: objectMemory getScavengeThreshold R: TempReg.
  jumpNeedScavenge := cogit JumpAboveOrEqual: 0.
 
  "Now initialize the fields of the context.  See CoInterpreter>>marryFrame:SP:copyTemps:"
  "sender gets frame pointer as a SmallInteger"
  continuation :=
  cogit MoveR: FPReg R: TempReg.
  self genSetSmallIntegerTagsIn: TempReg.
  cogit MoveR: TempReg Mw: objectMemory baseHeaderSize + (SenderIndex * objectMemory bytesPerOop) r: ReceiverResultReg.
 
  "pc gets frame caller as a SmallInteger"
  cogit MoveMw: FoxSavedFP r: FPReg R: TempReg.
  self genSetSmallIntegerTagsIn: TempReg.
  cogit MoveR: TempReg Mw: objectMemory baseHeaderSize + (InstructionPointerIndex * objectMemory bytesPerOop) r: ReceiverResultReg.
 
  "Set the method field, freeing up ClassReg again, and frame's context field,"
  cogit
  MoveMw: (cogit offset: CogMethod of: #methodObject) r: ClassReg R: TempReg;
  MoveR: TempReg Mw: objectMemory baseHeaderSize + (MethodIndex * objectMemory wordSize) r: ReceiverResultReg;
  MoveR: ReceiverResultReg Mw: FoxThisContext r: FPReg.
 
  "Now compute stack pointer; this is stackPointer (- 1 for return pc if a CISC) - framePointer - wordSize (1 each for saved pc, method, context, receiver) + 1 (1-relative) + numArgs"
  "TPR note - the code here is actually doing
  context stackPointer := ((((fp - sp) / wordSize) - [3|4]) + num args) asSmallInteger"
  cogit
  MoveR: FPReg R: TempReg;
  SubR: SPReg R: TempReg;
  LogicalShiftRightCq: self log2BytesPerWord R: TempReg;
  SubCq: (cogit backEnd hasLinkRegister ifTrue: [3] ifFalse: [4]) R: TempReg;
  AddR: SendNumArgsReg R: TempReg.
  self genConvertIntegerToSmallIntegerInReg: TempReg.
  cogit MoveR: TempReg Mw: objectMemory baseHeaderSize + (StackPointerIndex * objectMemory bytesPerOop) r: ReceiverResultReg.
 
  "Set closureOrNil to either the stacked receiver or nil"
  isInBlock
  ifTrue:
  [cogit
  MoveR: SendNumArgsReg R: TempReg;
  AddCq: 2 R: TempReg; "+2 for saved fp and saved pc"
  MoveXwr: TempReg R: FPReg R: TempReg]
  ifFalse:
  [cogit genMoveConstant: objectMemory nilObject R: TempReg].
  cogit MoveR: TempReg Mw: objectMemory baseHeaderSize + (ClosureIndex * objectMemory bytesPerOop) r: ReceiverResultReg.
 
  "Set the receiver"
  cogit
  MoveMw: FoxMFReceiver r: FPReg R: TempReg;
  MoveR: TempReg Mw: objectMemory baseHeaderSize + (ReceiverIndex * objectMemory bytesPerOop) r: ReceiverResultReg.
 
  "Now copy the arguments.  This is tricky because of the shortage of registers,.  ClassReg ranges
  from 1 to numArgs (SendNumArgsReg), and from ReceiverIndex + 1 to ReceiverIndex + numArgs.
  1 to: numArgs do:
  [:i|
  temp := longAt(FPReg + ((SendNumArgs - i + 2) * wordSize)). +2 for saved pc and savedfp
  longAtput(FPReg + FoxMFReceiver + (i * wordSize), temp)]"
  "TPR note: this is a prime candidate for passing off to the backend to do at least faintly optimal code"
  cogit MoveCq: 1 R: ClassReg.
  loopHead := cogit CmpR: SendNumArgsReg R: ClassReg.
  exit := cogit JumpGreater: 0.
  cogit
  MoveR: SendNumArgsReg R: TempReg;
  SubR: ClassReg R: TempReg;
  AddCq: 2 R: TempReg; "+2 for saved fp and saved pc"
  MoveXwr: TempReg R: FPReg R: TempReg;
  AddCq: ReceiverIndex + (objectMemory baseHeaderSize / objectMemory wordSize) R: ClassReg; "Now convert ClassReg from frame index to context index"
  MoveR: TempReg Xwr: ClassReg R: ReceiverResultReg;
  SubCq: ReceiverIndex + (objectMemory baseHeaderSize / objectMemory wordSize) - 1 R: ClassReg; "convert back adding 1 ;-)"
  Jump: loopHead.
  exit jmpTarget: cogit Label.
 
  "Finally nil or copy the non-argument temps.
  ClassReg := FPReg + FoxMFReceiver.
  SendNumArgsReg := SendNumArgsReg+ReceiverIndex.
  [ClassReg := ClassReg - wordSize.
   backEnd hasLinkRegister
  ifTrue: [ClassReg > SPReg]
  ifFalse: [ClassReg >= SPReg]] whileTrue:
  [receiver[SendNumArgsReg] := *ClassReg.
  SendNumArgsReg := SendNumArgsReg + 1]]"
  coInterpreter marryFrameCopiesTemps ifFalse:
  [cogit MoveCq: objectMemory nilObject R: TempReg].
  cogit
  MoveR: FPReg R: ClassReg;
  AddCq: FoxMFReceiver R: ClassReg;
  AddCq: ReceiverIndex + 1 + (objectMemory baseHeaderSize / objectMemory wordSize) R: SendNumArgsReg.
  loopHead :=
  cogit SubCq: objectMemory wordSize R: ClassReg.
  cogit CmpR: SPReg R: ClassReg.
  "If on a CISC there's a retpc for the trampoline call on top of stack; if on a RISC there isn't."
  exit := cogit backEnd hasLinkRegister
  ifTrue: [cogit JumpBelow: 0]
  ifFalse: [cogit JumpBelowOrEqual: 0].
  coInterpreter marryFrameCopiesTemps ifTrue:
  [cogit MoveMw: 0 r: ClassReg R: TempReg].
  cogit
  MoveR: TempReg Xwr: SendNumArgsReg R: ReceiverResultReg;
  AddCq: 1 R: SendNumArgsReg;
  Jump: loopHead.
  exit jmpTarget: cogit Label.
 
  cogit RetN: 0.
 
  jumpNeedScavenge jmpTarget: cogit Label.
  cogit backEnd saveAndRestoreLinkRegAround:
  [cogit CallRT: ceScheduleScavengeTrampoline].
  cogit Jump: continuation.
  ^0!

Item was removed:
- ----- Method: CogObjectRepresentationForSpur>>genLoadHeader:intoNewInstance:using: (in category 'initialization') -----
- genLoadHeader: header intoNewInstance: rcvrReg using: scratchReg
- "Generate the instructions to move the constant header into a new instance pointed to by rcvrReg."
- <inline: true>
- self subclassResponsibility!

Item was changed:
  ----- Method: CogObjectRepresentationForSpur>>genNewArrayOfSize:initialized: (in category 'bytecode generator support') -----
  genNewArrayOfSize: size initialized: initialized
  "Generate a call to code that allocates a new Array of size.
  The Array should be initialized with nils iff initialized is true.
  The size arg is passed in SendNumArgsReg, the result
  must come back in ReceiverResultReg."
  | header skip |
  <var: #skip type: #'AbstractInstruction *'>
  self assert: size < objectMemory numSlotsMask.
  header := objectMemory
  headerForSlots: size
  format: objectMemory arrayFormat
  classIndex: ClassArrayCompactIndex.
  cogit MoveAw: objectMemory freeStartAddress R: ReceiverResultReg.
+ self genStoreHeader: header intoNewInstance: ReceiverResultReg using: TempReg.
- self genLoadHeader: header intoNewInstance: ReceiverResultReg using: TempReg.
  (initialized and: [size > 0]) ifTrue:
  [cogit genMoveConstant: objectMemory nilObject R: TempReg.
  0 to: size - 1 do:
  [:i| cogit MoveR: TempReg
  Mw: i * objectMemory wordSize + objectMemory baseHeaderSize
  r: ReceiverResultReg]].
  cogit
  LoadEffectiveAddressMw: (objectMemory smallObjectBytesForSlots: size) r: ReceiverResultReg R: TempReg;
  MoveR: TempReg Aw: objectMemory freeStartAddress;
  CmpCq: objectMemory getScavengeThreshold R: TempReg.
  skip := cogit JumpBelow: 0.
  cogit CallRT: ceScheduleScavengeTrampoline.
  skip jmpTarget: cogit Label.
  ^0!

Item was changed:
  ----- Method: CogObjectRepresentationForSpur>>genNoPopCreateClosureAt:numArgs:numCopied:contextNumArgs:large:inBlock: (in category 'bytecode generator support') -----
  genNoPopCreateClosureAt: bcpc numArgs: numArgs numCopied: numCopied contextNumArgs: ctxtNumArgs large: isLargeCtxt inBlock: isInBlock
  "Create a closure with the given startpc, numArgs and numCopied
  within a context with ctxtNumArgs, large if isLargeCtxt that is in a
  block if isInBlock.  Do /not/ initialize the copied values."
  | numSlots byteSize header skip |
  <var: #skip type: #'AbstractInstruction *'>
 
  "First get thisContext into ReceiverResultRega and thence in ClassReg."
  self genGetActiveContextNumArgs: ctxtNumArgs large: isLargeCtxt inBlock: isInBlock.
  cogit MoveR: ReceiverResultReg R: ClassReg.
 
  numSlots := ClosureFirstCopiedValueIndex + numCopied.
  byteSize := objectMemory smallObjectBytesForSlots: numSlots.
  header := objectMemory
  headerForSlots: numSlots
  format: objectMemory indexablePointersFormat
  classIndex: ClassBlockClosureCompactIndex.
  cogit MoveAw: objectMemory freeStartAddress R: ReceiverResultReg.
+ self genStoreHeader: header intoNewInstance: ReceiverResultReg using: TempReg.
- self genLoadHeader: header intoNewInstance: ReceiverResultReg using: TempReg.
  cogit
  LoadEffectiveAddressMw: byteSize r: ReceiverResultReg R: TempReg;
  MoveR: TempReg Aw: objectMemory freeStartAddress;
  CmpCq: objectMemory getScavengeThreshold R: TempReg.
  skip := cogit JumpBelow: 0.
  cogit CallRT: ceScheduleScavengeTrampoline.
  skip jmpTarget: cogit Label.
 
  cogit
  MoveR: ClassReg Mw: ClosureOuterContextIndex * objectMemory bytesPerOop + objectMemory baseHeaderSize r: ReceiverResultReg;
  MoveCq: (objectMemory integerObjectOf: bcpc) R: TempReg;
  MoveR: TempReg Mw: ClosureStartPCIndex * objectMemory bytesPerOop + objectMemory baseHeaderSize r: ReceiverResultReg;
  MoveCq: (objectMemory integerObjectOf: numArgs) R: TempReg;
  MoveR: TempReg Mw: ClosureNumArgsIndex * objectMemory bytesPerOop + objectMemory baseHeaderSize r: ReceiverResultReg.
  ^0!

Item was added:
+ ----- Method: CogObjectRepresentationForSpur>>genStoreHeader:intoNewInstance:using: (in category 'initialization') -----
+ genStoreHeader: header intoNewInstance: rcvrReg using: scratchReg
+ "Generate the instructions to move the constant header into a new instance pointed to by rcvrReg."
+ <inline: true>
+ self subclassResponsibility!

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

Item was changed:
  ----- Method: StackToRegisterMappingCogit>>genDoubleArithmetic:preOpCheck: (in category 'primitive generators') -----
  genDoubleArithmetic: arithmeticOperator preOpCheck: preOpCheckOrNil
  "Receiver and arg in registers.
  Stack looks like
  return address"
  <var: #preOpCheckOrNil declareC: 'AbstractInstruction *(*preOpCheckOrNil)(int rcvrReg, int argReg)'>
+ | jumpFailClass jumpFailClass2 jumpFailAlloc jumpFailCheck jumpImmediate jumpNonInt doOp |
- | jumpFailClass jumpFailAlloc jumpFailCheck jumpImmediate jumpNonInt doOp |
  <var: #jumpFailClass type: #'AbstractInstruction *'>
+ <var: #jumpFailClass2 type: #'AbstractInstruction *'>
  <var: #jumpFailAlloc type: #'AbstractInstruction *'>
  <var: #jumpImmediate type: #'AbstractInstruction *'>
  <var: #jumpNonInt type: #'AbstractInstruction *'>
  <var: #jumpFailCheck type: #'AbstractInstruction *'>
  <var: #doOp type: #'AbstractInstruction *'>
  objectRepresentation genGetDoubleValueOf: ReceiverResultReg into: DPFPReg0.
  self MoveR: Arg0Reg R: ClassReg.
  jumpImmediate := objectRepresentation genJumpImmediate: Arg0Reg.
  objectRepresentation genGetCompactClassIndexNonImmOf: Arg0Reg into: SendNumArgsReg.
  objectRepresentation genCmpClassFloatCompactIndexR: SendNumArgsReg.
  jumpFailClass := self JumpNonZero: 0.
  objectRepresentation genGetDoubleValueOf: Arg0Reg into: DPFPReg1.
  doOp := self Label.
  preOpCheckOrNil ifNotNil:
  [jumpFailCheck := self perform: preOpCheckOrNil with: DPFPReg0 with: DPFPReg1].
  self gen: arithmeticOperator operand: DPFPReg1 operand: DPFPReg0.
  jumpFailAlloc := objectRepresentation
  genAllocFloatValue: DPFPReg0
  into: SendNumArgsReg
  scratchReg: ClassReg
  scratchReg: TempReg.
  self MoveR: SendNumArgsReg R: ReceiverResultReg.
  self RetN: 0.
  "We need to push the register args on two paths; this one and the interpreter primitive path.
  But the interpreter primitive path won't unless regArgsHaveBeenPushed is false."
  self assert: methodOrBlockNumArgs <= self numRegArgs.
  jumpFailClass jmpTarget: self Label.
  preOpCheckOrNil ifNotNil:
  [jumpFailCheck jmpTarget: jumpFailClass getJmpTarget].
  backEnd genPushRegisterArgsForNumArgs: methodOrBlockNumArgs scratchReg: SendNumArgsReg.
+ jumpFailClass2 := self Jump: 0.
- jumpFailClass := self Jump: 0.
  jumpImmediate jmpTarget: self Label.
+ objectRepresentation maybeGenConvertIfSmallFloatIn: Arg0Reg into: DPFPReg1 andJumpTo: doOp.
  objectRepresentation smallIntegerIsOnlyImmediateType ifFalse:
+ [jumpNonInt := objectRepresentation genJumpNotSmallInteger: Arg0Reg scratch: TempReg.
+ jumpNonInt jmpTarget: jumpFailClass getJmpTarget].
- [jumpNonInt := objectRepresentation genJumpNotSmallInteger: Arg0Reg scratch: TempReg].
  objectRepresentation genConvertSmallIntegerToIntegerInReg: ClassReg.
  self ConvertR: ClassReg Rd: DPFPReg1.
  self Jump: doOp.
  jumpFailAlloc jmpTarget: self Label.
  self compileFallbackToInterpreterPrimitive: 0.
+ jumpFailClass2 jmpTarget: self Label.
- jumpFailClass jmpTarget: self Label.
- objectRepresentation smallIntegerIsOnlyImmediateType ifFalse:
- [jumpNonInt jmpTarget: jumpFailClass getJmpTarget].
  ^0!

Reply | Threaded
Open this post in threaded view
|

Re: VM Maker: VMMaker.oscog-eem.1565.mcz

Eliot Miranda-2
 
Thar she blows...
The 64-bit JIT is complete enough in the simulator to bring up a functional emergency evaluator.

Inline image 1

On Mon, Dec 7, 2015 at 5:26 PM, <[hidden email]> wrote:

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

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

Name: VMMaker.oscog-eem.1565
Author: eem
Time: 7 December 2015, 5:25:51.389 pm
UUID: 98c5bc39-e721-42ba-9bac-5b1dbfc0963b
Ancestors: VMMaker.oscog-EstebanLorenzano.1564

x64 Cogit:
Half-fix StackToRegisterMappingCogit>>genDoubleArithmetic:preOpCheck: so as not to produce a bogus value when faced with a smallFloat arg.  With this fix the simulator generates output in an emergency evaluator complaining of a primitive failure (which wouldn't fail wityh conversion of smallFloat args).  (Still have to define it for SimpleStackBasedCogit).

Implement the default do-nothing maybeGenConvertIfSmallFloatIn:into:andJumpTo: which will soon provide the relevant conversion.

Rename genLoadHeader:intoNewInstance:using: to genStoreHeader:intoNewInstance:using:, which is what it does.

Eliminate the unnecessary nop when MoveCqR uses MoveCwR to generate a long constant.

=============== Diff against VMMaker.oscog-EstebanLorenzano.1564 ===============

Item was changed:
  ----- Method: CogInLineLiteralsX64Compiler>>concretizeMoveCwR (in category 'generate machine code') -----
  concretizeMoveCwR
        "Will get inlined into concretizeAt: switch."
        <inline: true>
        | value reg offset |
        value := operands at: 0.
        reg := self concreteRegister: (operands at: 1).
        (self isAnInstruction: (cogit cCoerceSimple: value to: #'AbstractInstruction *')) ifTrue:
                [value := (cogit cCoerceSimple: value to: #'AbstractInstruction *') address].
        (cogit addressIsInCurrentCompilation: value) ifTrue:
                [offset := value - (address + 7).
                 machineCode
                        at: 0 put: (self rexR: reg x: 0 b: 0);
                        at: 1 put: 16r8D; "LoadEffectiveAddress"
                        at: 2 put: (self mod: ModRegInd RM: 5 RO: reg);
                        at: 3 put: (offset bitAnd: 16rFF);
                        at: 4 put: (offset >> 8 bitAnd: 16rFF);
                        at: 5 put: (offset >> 16 bitAnd: 16rFF);
                        at: 6 put: (offset >> 24 bitAnd: 16rFF).
                ^machineCodeSize := 7].
        machineCode
                at:  0 put: (self rexR: reg x: 0 b: reg);
                at:  1 put: 16rB8 + (reg bitAnd: 7);
                at:  2 put: (value bitAnd: 16rFF);
                at:  3 put: (value >> 8 bitAnd: 16rFF);
                at:  4 put: (value >> 16 bitAnd: 16rFF);
                at:  5 put: (value >> 24 bitAnd: 16rFF);
                at:  6 put: (value >> 32 bitAnd: 16rFF);
                at:  7 put: (value >> 40 bitAnd: 16rFF);
                at:  8 put: (value >> 48 bitAnd: 16rFF);
+               at:  9 put: (value >> 56 bitAnd: 16rFF).
+       opcode = MoveCqR ifTrue:
+               [^machineCodeSize := 10].
+       "Add a nop to disambiguate between MoveCwR/PushCwR and ArithCwR, which ends with a (self mod: ModReg RM: 0 RO: 0)"
+       machineCode at: 10 put: 16r90.
-               at:  9 put: (value >> 56 bitAnd: 16rFF);
-               at: 10 put: 16r90. "Add a nop to disambiguate between MoveCwR/PushCwR and ArithCwR, which ends with a (self mod: ModReg RM: 0 RO: 0)"
        self assert: (self mod: ModReg RM: 0 RO: 0) > 16r90.
        ^machineCodeSize := 11!

Item was added:
+ ----- Method: CogObjectRepresentation>>maybeGenConvertIfSmallFloatIn:into:andJumpTo: (in category 'primitive generators') -----
+ maybeGenConvertIfSmallFloatIn: oopReg into: dpReg andJumpTo: targetInst
+       "If the receiver supports immediate floats then generate a test for a smallFloat in  oopReg,
+        converting it to the float value in dpReg and jumping to targetInst.  Otherwise do nothing."
+       <var: 'targetInst' type: #'AbstractInstruction *'>
+       ^0!

Item was removed:
- ----- Method: CogObjectRepresentationFor32BitSpur>>genLoadHeader:intoNewInstance:using: (in category 'initialization') -----
- genLoadHeader: header intoNewInstance: rcvrReg using: scratchReg
-       "Generate the instructions to move the constant header into a new instance pointed to by rcvrReg."
-       <inline: true>
-       self flag: #endianness.
-       cogit
-               MoveCq: (self low32BitsOf: header) R: scratchReg;
-               MoveR: scratchReg Mw: 0 r: rcvrReg;
-               MoveCq: header >> 32 R: scratchReg;
-               MoveR: scratchReg Mw: 4 r: rcvrReg!

Item was added:
+ ----- Method: CogObjectRepresentationFor32BitSpur>>genStoreHeader:intoNewInstance:using: (in category 'initialization') -----
+ genStoreHeader: header intoNewInstance: rcvrReg using: scratchReg
+       "Generate the instructions to move the constant header into a new instance pointed to by rcvrReg."
+       <inline: true>
+       self flag: #endianness.
+       cogit
+               MoveCq: (self low32BitsOf: header) R: scratchReg;
+               MoveR: scratchReg Mw: 0 r: rcvrReg;
+               MoveCq: header >> 32 R: scratchReg;
+               MoveR: scratchReg Mw: 4 r: rcvrReg!

Item was removed:
- ----- Method: CogObjectRepresentationFor64BitSpur>>genLoadHeader:intoNewInstance:using: (in category 'initialization') -----
- genLoadHeader: header intoNewInstance: rcvrReg using: scratchReg
-       "Generate the instructions to move the constant header into a new instance pointed to by rcvrReg."
-       <inline: true>
-       cogit
-               MoveCq: header R: scratchReg;
-               MoveR: TempReg Mw: 0 r: rcvrReg!

Item was added:
+ ----- Method: CogObjectRepresentationFor64BitSpur>>genStoreHeader:intoNewInstance:using: (in category 'initialization') -----
+ genStoreHeader: header intoNewInstance: rcvrReg using: scratchReg
+       "Generate the instructions to move the constant header into a new instance pointed to by rcvrReg."
+       <inline: true>
+       cogit
+               MoveCq: header R: scratchReg;
+               MoveR: scratchReg Mw: 0 r: rcvrReg!

Item was changed:
  ----- Method: CogObjectRepresentationForSpur>>genAllocFloatValue:into:scratchReg:scratchReg: (in category 'primitive generators') -----
  genAllocFloatValue: dpreg into: resultReg scratchReg: scratch1 scratchReg: scratch2
        <returnTypeC: #'AbstractInstruction *'>
        | allocSize newFloatHeader jumpFail |
        <var: #jumpFail type: #'AbstractInstruction *'>
        allocSize := objectMemory baseHeaderSize + (objectMemory sizeof: #double).
        newFloatHeader := objectMemory
                                                        headerForSlots: (self sizeof: #double) / objectMemory wordSize
                                                        format: objectMemory firstLongFormat
                                                        classIndex: ClassFloatCompactIndex.
        cogit MoveAw: objectMemory freeStartAddress R: resultReg.
        cogit LoadEffectiveAddressMw: allocSize r: resultReg R: scratch1.
        cogit CmpCq: objectMemory getScavengeThreshold R: scratch1.
        jumpFail := cogit JumpAboveOrEqual: 0.
        cogit MoveR: scratch1 Aw: objectMemory freeStartAddress.
+       self genStoreHeader: newFloatHeader intoNewInstance: resultReg using: scratch1.
-       self genLoadHeader: newFloatHeader intoNewInstance: resultReg using: scratch1.
        cogit MoveRd: dpreg M64: objectMemory baseHeaderSize r: resultReg.
        ^jumpFail!

Item was changed:
  ----- Method: CogObjectRepresentationForSpur>>genGetActiveContextLarge:inBlock: (in category 'initialization') -----
  genGetActiveContextLarge: isLarge inBlock: isInBlock
        "Create a trampoline to answer the active context that will
         answer it if a frame is already married, and create it otherwise.
         Assume numArgs is in SendNumArgsReg and ClassReg is free."
        | header slotSize jumpSingle loopHead jumpNeedScavenge continuation exit |
        <var: #jumpNeedScavenge type: #'AbstractInstruction *'>
        <var: #continuation type: #'AbstractInstruction *'>
        <var: #jumpSingle type: #'AbstractInstruction *'>
        <var: #loopHead type: #'AbstractInstruction *'>
        <var: #exit type: #'AbstractInstruction *'>
        cogit "load the flag; stash it in both TempReg & ClassReg; do the compare (a prime candidated for use of AndCq:R:R:)"
                MoveMw: FoxMethod r: FPReg R: ClassReg;
                AndCq: MFMethodFlagHasContextFlag R: ClassReg R: TempReg.
        jumpSingle := cogit JumpZero: 0. "jump if flag bit not set"
        cogit "since the flag bit was set, get the context in the receiver reg and return"
                MoveMw: FoxThisContext r: FPReg R: ReceiverResultReg;
                RetN: 0.
        jumpSingle jmpTarget: cogit Label.

        "OK, it doesn't exist; instantiate and initialize it"
        "set the hasContext flag; See CoInterpreter class>>initializeFrameIndices"
        cogit
                OrCq: MFMethodFlagHasContextFlag R: ClassReg;
                MoveR: ClassReg Mw: FoxMethod r: FPReg.
        "now get the home CogMethod into ClassReg and save for post-instantiation."
        isInBlock
                ifTrue:
                        [cogit
                                SubCq: 3 R: ClassReg; "-3 is -(hasContext+isBlock) flags"
                                MoveM16: 0 r: ClassReg R: TempReg;
                                SubR: TempReg R: ClassReg]
                ifFalse:
                        [cogit SubCq: 1 R: ClassReg]. "-1 is hasContext flag"

        "instantiate the context..."
        slotSize := isLarge ifTrue: [LargeContextSlots] ifFalse: [SmallContextSlots].
        header := objectMemory
                                        headerForSlots: slotSize
                                        format: objectMemory indexablePointersFormat
                                        classIndex: ClassMethodContextCompactIndex.
        self flag: #endianness.
        cogit MoveAw: objectMemory freeStartAddress R: ReceiverResultReg.
+       self genStoreHeader: header intoNewInstance: ReceiverResultReg using: TempReg.
-       self genLoadHeader: header intoNewInstance: ReceiverResultReg using: TempReg.
        cogit
                MoveR: ReceiverResultReg R: TempReg;
                AddCq: (objectMemory smallObjectBytesForSlots: slotSize) R: TempReg;
                MoveR: TempReg Aw: objectMemory freeStartAddress;
                CmpCq: objectMemory getScavengeThreshold R: TempReg.
        jumpNeedScavenge := cogit JumpAboveOrEqual: 0.

        "Now initialize the fields of the context.  See CoInterpreter>>marryFrame:SP:copyTemps:"
        "sender gets frame pointer as a SmallInteger"
        continuation :=
        cogit MoveR: FPReg R: TempReg.
        self genSetSmallIntegerTagsIn: TempReg.
        cogit MoveR: TempReg Mw: objectMemory baseHeaderSize + (SenderIndex * objectMemory bytesPerOop) r: ReceiverResultReg.

        "pc gets frame caller as a SmallInteger"
        cogit MoveMw: FoxSavedFP r: FPReg R: TempReg.
        self genSetSmallIntegerTagsIn: TempReg.
        cogit MoveR: TempReg Mw: objectMemory baseHeaderSize + (InstructionPointerIndex * objectMemory bytesPerOop) r: ReceiverResultReg.

        "Set the method field, freeing up ClassReg again, and frame's context field,"
        cogit
                MoveMw: (cogit offset: CogMethod of: #methodObject) r: ClassReg R: TempReg;
                MoveR: TempReg Mw: objectMemory baseHeaderSize + (MethodIndex * objectMemory wordSize) r: ReceiverResultReg;
                MoveR: ReceiverResultReg Mw: FoxThisContext r: FPReg.

        "Now compute stack pointer; this is stackPointer (- 1 for return pc if a CISC) - framePointer - wordSize (1 each for saved pc, method, context, receiver) + 1 (1-relative) + numArgs"
        "TPR note - the code here is actually doing
        context stackPointer := ((((fp - sp) / wordSize) - [3|4]) + num args) asSmallInteger"
        cogit
                MoveR: FPReg R: TempReg;
                SubR: SPReg R: TempReg;
                LogicalShiftRightCq: self log2BytesPerWord R: TempReg;
                SubCq: (cogit backEnd hasLinkRegister ifTrue: [3] ifFalse: [4]) R: TempReg;
                AddR: SendNumArgsReg R: TempReg.
        self genConvertIntegerToSmallIntegerInReg: TempReg.
        cogit MoveR: TempReg Mw: objectMemory baseHeaderSize + (StackPointerIndex * objectMemory bytesPerOop) r: ReceiverResultReg.

        "Set closureOrNil to either the stacked receiver or nil"
        isInBlock
                ifTrue:
                        [cogit
                                MoveR: SendNumArgsReg R: TempReg;
                                AddCq: 2 R: TempReg; "+2 for saved fp and saved pc"
                                MoveXwr: TempReg R: FPReg R: TempReg]
                ifFalse:
                        [cogit genMoveConstant: objectMemory nilObject R: TempReg].
        cogit MoveR: TempReg Mw: objectMemory baseHeaderSize + (ClosureIndex * objectMemory bytesPerOop) r: ReceiverResultReg.

        "Set the receiver"
        cogit
                MoveMw: FoxMFReceiver r: FPReg R: TempReg;
                MoveR: TempReg Mw: objectMemory baseHeaderSize + (ReceiverIndex * objectMemory bytesPerOop) r: ReceiverResultReg.

        "Now copy the arguments.  This is tricky because of the shortage of registers,.  ClassReg ranges
         from 1 to numArgs (SendNumArgsReg), and from ReceiverIndex + 1 to ReceiverIndex + numArgs.
         1 to: numArgs do:
                [:i|
                temp := longAt(FPReg + ((SendNumArgs - i + 2) * wordSize)). +2 for saved pc and savedfp
                longAtput(FPReg + FoxMFReceiver + (i * wordSize), temp)]"
        "TPR note: this is a prime candidate for passing off to the backend to do at least faintly optimal code"
        cogit MoveCq: 1 R: ClassReg.
        loopHead := cogit CmpR: SendNumArgsReg R: ClassReg.
        exit := cogit JumpGreater: 0.
        cogit
                MoveR: SendNumArgsReg R: TempReg;
                SubR: ClassReg R: TempReg;
                AddCq: 2 R: TempReg; "+2 for saved fp and saved pc"
                MoveXwr: TempReg R: FPReg R: TempReg;
                AddCq: ReceiverIndex + (objectMemory baseHeaderSize / objectMemory wordSize) R: ClassReg; "Now convert ClassReg from frame index to context index"
                MoveR: TempReg Xwr: ClassReg R: ReceiverResultReg;
                SubCq: ReceiverIndex + (objectMemory baseHeaderSize / objectMemory wordSize) - 1 R: ClassReg; "convert back adding 1 ;-)"
                Jump: loopHead.
        exit jmpTarget: cogit Label.

        "Finally nil or copy the non-argument temps.
         ClassReg := FPReg + FoxMFReceiver.
         SendNumArgsReg := SendNumArgsReg+ReceiverIndex.
         [ClassReg := ClassReg - wordSize.
          backEnd hasLinkRegister
                        ifTrue: [ClassReg > SPReg]
                        ifFalse: [ClassReg >= SPReg]] whileTrue:
                [receiver[SendNumArgsReg] := *ClassReg.
                 SendNumArgsReg := SendNumArgsReg + 1]]"
        coInterpreter marryFrameCopiesTemps ifFalse:
                [cogit MoveCq: objectMemory nilObject R: TempReg].
        cogit
                MoveR: FPReg R: ClassReg;
                AddCq: FoxMFReceiver R: ClassReg;
                AddCq: ReceiverIndex + 1 + (objectMemory baseHeaderSize / objectMemory wordSize) R: SendNumArgsReg.
        loopHead :=
        cogit SubCq: objectMemory wordSize R: ClassReg.
        cogit CmpR: SPReg R: ClassReg.
        "If on a CISC there's a retpc for the trampoline call on top of stack; if on a RISC there isn't."
        exit := cogit backEnd hasLinkRegister
                                ifTrue: [cogit JumpBelow: 0]
                                ifFalse: [cogit JumpBelowOrEqual: 0].
        coInterpreter marryFrameCopiesTemps ifTrue:
                [cogit MoveMw: 0 r: ClassReg R: TempReg].
        cogit
                MoveR: TempReg Xwr: SendNumArgsReg R: ReceiverResultReg;
                AddCq: 1 R: SendNumArgsReg;
                Jump: loopHead.
        exit jmpTarget: cogit Label.

        cogit RetN: 0.

        jumpNeedScavenge jmpTarget: cogit Label.
        cogit backEnd saveAndRestoreLinkRegAround:
                [cogit CallRT: ceScheduleScavengeTrampoline].
        cogit Jump: continuation.
        ^0!

Item was removed:
- ----- Method: CogObjectRepresentationForSpur>>genLoadHeader:intoNewInstance:using: (in category 'initialization') -----
- genLoadHeader: header intoNewInstance: rcvrReg using: scratchReg
-       "Generate the instructions to move the constant header into a new instance pointed to by rcvrReg."
-       <inline: true>
-       self subclassResponsibility!

Item was changed:
  ----- Method: CogObjectRepresentationForSpur>>genNewArrayOfSize:initialized: (in category 'bytecode generator support') -----
  genNewArrayOfSize: size initialized: initialized
        "Generate a call to code that allocates a new Array of size.
         The Array should be initialized with nils iff initialized is true.
         The size arg is passed in SendNumArgsReg, the result
         must come back in ReceiverResultReg."
        | header skip |
        <var: #skip type: #'AbstractInstruction *'>
        self assert: size < objectMemory numSlotsMask.
        header := objectMemory
                                        headerForSlots: size
                                        format: objectMemory arrayFormat
                                        classIndex: ClassArrayCompactIndex.
        cogit MoveAw: objectMemory freeStartAddress R: ReceiverResultReg.
+       self genStoreHeader: header intoNewInstance: ReceiverResultReg using: TempReg.
-       self genLoadHeader: header intoNewInstance: ReceiverResultReg using: TempReg.
        (initialized and: [size > 0]) ifTrue:
                [cogit genMoveConstant: objectMemory nilObject R: TempReg.
                 0 to: size - 1 do:
                        [:i| cogit MoveR: TempReg
                                        Mw: i * objectMemory wordSize + objectMemory baseHeaderSize
                                        r: ReceiverResultReg]].
        cogit
                LoadEffectiveAddressMw: (objectMemory smallObjectBytesForSlots: size) r: ReceiverResultReg R: TempReg;
                MoveR: TempReg Aw: objectMemory freeStartAddress;
                CmpCq: objectMemory getScavengeThreshold R: TempReg.
        skip := cogit JumpBelow: 0.
        cogit CallRT: ceScheduleScavengeTrampoline.
        skip jmpTarget: cogit Label.
        ^0!

Item was changed:
  ----- Method: CogObjectRepresentationForSpur>>genNoPopCreateClosureAt:numArgs:numCopied:contextNumArgs:large:inBlock: (in category 'bytecode generator support') -----
  genNoPopCreateClosureAt: bcpc numArgs: numArgs numCopied: numCopied contextNumArgs: ctxtNumArgs large: isLargeCtxt inBlock: isInBlock
        "Create a closure with the given startpc, numArgs and numCopied
         within a context with ctxtNumArgs, large if isLargeCtxt that is in a
         block if isInBlock.  Do /not/ initialize the copied values."
        | numSlots byteSize header skip |
        <var: #skip type: #'AbstractInstruction *'>

        "First get thisContext into ReceiverResultRega and thence in ClassReg."
        self genGetActiveContextNumArgs: ctxtNumArgs large: isLargeCtxt inBlock: isInBlock.
        cogit MoveR: ReceiverResultReg R: ClassReg.

        numSlots := ClosureFirstCopiedValueIndex + numCopied.
        byteSize := objectMemory smallObjectBytesForSlots: numSlots.
        header := objectMemory
                                        headerForSlots: numSlots
                                        format: objectMemory indexablePointersFormat
                                        classIndex: ClassBlockClosureCompactIndex.
        cogit MoveAw: objectMemory freeStartAddress R: ReceiverResultReg.
+       self genStoreHeader: header intoNewInstance: ReceiverResultReg using: TempReg.
-       self genLoadHeader: header intoNewInstance: ReceiverResultReg using: TempReg.
        cogit
                LoadEffectiveAddressMw: byteSize r: ReceiverResultReg R: TempReg;
                MoveR: TempReg Aw: objectMemory freeStartAddress;
                CmpCq: objectMemory getScavengeThreshold R: TempReg.
        skip := cogit JumpBelow: 0.
        cogit CallRT: ceScheduleScavengeTrampoline.
        skip jmpTarget: cogit Label.

        cogit
                MoveR: ClassReg Mw: ClosureOuterContextIndex * objectMemory bytesPerOop + objectMemory baseHeaderSize r: ReceiverResultReg;
                MoveCq: (objectMemory integerObjectOf: bcpc) R: TempReg;
                MoveR: TempReg Mw: ClosureStartPCIndex * objectMemory bytesPerOop + objectMemory baseHeaderSize r: ReceiverResultReg;
                MoveCq: (objectMemory integerObjectOf: numArgs) R: TempReg;
                MoveR: TempReg Mw: ClosureNumArgsIndex * objectMemory bytesPerOop + objectMemory baseHeaderSize r: ReceiverResultReg.
        ^0!

Item was added:
+ ----- Method: CogObjectRepresentationForSpur>>genStoreHeader:intoNewInstance:using: (in category 'initialization') -----
+ genStoreHeader: header intoNewInstance: rcvrReg using: scratchReg
+       "Generate the instructions to move the constant header into a new instance pointed to by rcvrReg."
+       <inline: true>
+       self subclassResponsibility!

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

Item was changed:
  ----- Method: StackToRegisterMappingCogit>>genDoubleArithmetic:preOpCheck: (in category 'primitive generators') -----
  genDoubleArithmetic: arithmeticOperator preOpCheck: preOpCheckOrNil
        "Receiver and arg in registers.
         Stack looks like
                return address"
        <var: #preOpCheckOrNil declareC: 'AbstractInstruction *(*preOpCheckOrNil)(int rcvrReg, int argReg)'>
+       | jumpFailClass jumpFailClass2 jumpFailAlloc jumpFailCheck jumpImmediate jumpNonInt doOp |
-       | jumpFailClass jumpFailAlloc jumpFailCheck jumpImmediate jumpNonInt doOp |
        <var: #jumpFailClass type: #'AbstractInstruction *'>
+       <var: #jumpFailClass2 type: #'AbstractInstruction *'>
        <var: #jumpFailAlloc type: #'AbstractInstruction *'>
        <var: #jumpImmediate type: #'AbstractInstruction *'>
        <var: #jumpNonInt type: #'AbstractInstruction *'>
        <var: #jumpFailCheck type: #'AbstractInstruction *'>
        <var: #doOp type: #'AbstractInstruction *'>
        objectRepresentation genGetDoubleValueOf: ReceiverResultReg into: DPFPReg0.
        self MoveR: Arg0Reg R: ClassReg.
        jumpImmediate := objectRepresentation genJumpImmediate: Arg0Reg.
        objectRepresentation genGetCompactClassIndexNonImmOf: Arg0Reg into: SendNumArgsReg.
        objectRepresentation genCmpClassFloatCompactIndexR: SendNumArgsReg.
        jumpFailClass := self JumpNonZero: 0.
        objectRepresentation genGetDoubleValueOf: Arg0Reg into: DPFPReg1.
        doOp := self Label.
        preOpCheckOrNil ifNotNil:
                [jumpFailCheck := self perform: preOpCheckOrNil with: DPFPReg0 with: DPFPReg1].
        self gen: arithmeticOperator operand: DPFPReg1 operand: DPFPReg0.
        jumpFailAlloc := objectRepresentation
                                                genAllocFloatValue: DPFPReg0
                                                into: SendNumArgsReg
                                                scratchReg: ClassReg
                                                scratchReg: TempReg.
        self MoveR: SendNumArgsReg R: ReceiverResultReg.
        self RetN: 0.
        "We need to push the register args on two paths; this one and the interpreter primitive path.
        But the interpreter primitive path won't unless regArgsHaveBeenPushed is false."
        self assert: methodOrBlockNumArgs <= self numRegArgs.
        jumpFailClass jmpTarget: self Label.
        preOpCheckOrNil ifNotNil:
                [jumpFailCheck jmpTarget: jumpFailClass getJmpTarget].
        backEnd genPushRegisterArgsForNumArgs: methodOrBlockNumArgs scratchReg: SendNumArgsReg.
+       jumpFailClass2 := self Jump: 0.
-       jumpFailClass := self Jump: 0.
        jumpImmediate jmpTarget: self Label.
+       objectRepresentation maybeGenConvertIfSmallFloatIn: Arg0Reg into: DPFPReg1 andJumpTo: doOp.
        objectRepresentation smallIntegerIsOnlyImmediateType ifFalse:
+               [jumpNonInt := objectRepresentation genJumpNotSmallInteger: Arg0Reg scratch: TempReg.
+                jumpNonInt jmpTarget: jumpFailClass getJmpTarget].
-               [jumpNonInt := objectRepresentation genJumpNotSmallInteger: Arg0Reg scratch: TempReg].
        objectRepresentation genConvertSmallIntegerToIntegerInReg: ClassReg.
        self ConvertR: ClassReg Rd: DPFPReg1.
        self Jump: doOp.
        jumpFailAlloc jmpTarget: self Label.
        self compileFallbackToInterpreterPrimitive: 0.
+       jumpFailClass2 jmpTarget: self Label.
-       jumpFailClass jmpTarget: self Label.
-       objectRepresentation smallIntegerIsOnlyImmediateType ifFalse:
-               [jumpNonInt jmpTarget: jumpFailClass getJmpTarget].
        ^0!




--
_,,,^..^,,,_
best, Eliot
Reply | Threaded
Open this post in threaded view
|

Re: VM Maker: VMMaker.oscog-eem.1565.mcz

timrowledge


> On 07-12-2015, at 5:32 PM, Eliot Miranda <[hidden email]> wrote:
>
> Thar she blows...
> The 64-bit JIT is complete enough in the simulator to bring up a functional emergency evaluator.

Well done. Now, I don’t know if this is the first time you’ve ever done this but….



tim
--
tim Rowledge; [hidden email]; http://www.rowledge.org/tim
Flabbergasted (adj.), appalled over how much weight you have gained.


Reply | Threaded
Open this post in threaded view
|

Re: VM Maker: VMMaker.oscog-eem.1565.mcz

Ryan Macnak
 
Huzzah!

On Mon, Dec 7, 2015 at 5:43 PM, tim Rowledge <[hidden email]> wrote:


> On 07-12-2015, at 5:32 PM, Eliot Miranda <[hidden email]> wrote:
>
> Thar she blows...
> The 64-bit JIT is complete enough in the simulator to bring up a functional emergency evaluator.

Well done. Now, I don’t know if this is the first time you’ve ever done this but….



tim
--
tim Rowledge; [hidden email]; http://www.rowledge.org/tim
Flabbergasted (adj.), appalled over how much weight you have gained.