VM Maker: VMMaker.oscog-cb.2113.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-cb.2113.mcz

commits-2
 
ClementBera uploaded a new version of VMMaker to project VM Maker:
http://source.squeak.org/VMMaker/VMMaker.oscog-cb.2113.mcz

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

Name: VMMaker.oscog-cb.2113
Author: cb
Time: 27 January 2017, 2:45:56.09265 pm
UUID: fc17c325-6a18-402c-8873-7e7facf7104d
Ancestors: VMMaker.oscog-cb.2112

Changed the machine compilation of BranchIfInstanceOf if there is one Behavior and the behavior is UndefinedObject, True and False to compile to a direct comparison to the unique instances instead of class index check. I am not sure it makes sense to add these cases when there are multiple behaviors.

Added a new trampoline to create new hashes. Unfortunately I did not succeed in using the trampoline in the existing primitives, so I made the trampoline Sista only and it's used in the inlined primitive.

=============== Diff against VMMaker.oscog-cb.2112 ===============

Item was added:
+ ----- Method: CoInterpreter>>ceNewHashOf: (in category 'trampolines') -----
+ ceNewHashOf: anObject
+ <api>
+ <option: #SistaVM>
+ "We know anObject has not a hash yet (or this trampoline would not be called.
+ Sets the hash, then answers it as a smallinteger"
+ ^ objectMemory integerObjectOf: (objectMemory newHashBitsOf: anObject)!

Item was changed:
  CogObjectRepresentation subclass: #CogObjectRepresentationForSpur
+ instanceVariableNames: 'ceScheduleScavengeTrampoline ceSmallActiveContextInMethodTrampoline ceSmallActiveContextInBlockTrampoline ceSmallActiveContextInFullBlockTrampoline ceLargeActiveContextInMethodTrampoline ceLargeActiveContextInBlockTrampoline ceLargeActiveContextInFullBlockTrampoline ceStoreCheckContextReceiverTrampoline ceStoreTrampolines ceNewHashTrampoline'
- instanceVariableNames: 'ceScheduleScavengeTrampoline ceSmallActiveContextInMethodTrampoline ceSmallActiveContextInBlockTrampoline ceSmallActiveContextInFullBlockTrampoline ceLargeActiveContextInMethodTrampoline ceLargeActiveContextInBlockTrampoline ceLargeActiveContextInFullBlockTrampoline ceStoreCheckContextReceiverTrampoline ceStoreTrampolines'
  classVariableNames: 'CheckRememberedInTrampoline NumStoreTrampolines'
  poolDictionaries: 'VMBytecodeConstants VMSqueakClassIndices'
  category: 'VMMaker-JIT'!

Item was changed:
  ----- Method: CogObjectRepresentationForSpur class>>numTrampolines (in category 'accessing') -----
  numTrampolines
  ^super numTrampolines
  + (SistaV1BytecodeSet
  ifTrue: [8] "(small,large)x(method,block,fullBlock) context creation,
  ceStoreCheckContextReceiverTrampoline and ceScheduleScavengeTrampoline"
+ ifFalse: [6] "(small,large)x(method,block) context creation,
- ifFalse: [6] "(small,large)x(method,block) context creation,
  ceStoreCheckContextReceiverTrampoline and ceScheduleScavengeTrampoline")
  + ((initializationOptions at: #IMMUTABILITY ifAbsent: [false])
  ifTrue: [NumStoreTrampolines]
+ ifFalse: [0])
+ + ((initializationOptions at: #SistaVM ifAbsent: [false])
+ ifTrue: [1] "newHash"
  ifFalse: [0])!

Item was changed:
  ----- Method: CogObjectRepresentationForSpur>>branchIf:instanceOfBehavior:target: (in category 'sista support') -----
  branchIf: reg instanceOfBehavior: classObj target: targetFixUp
  "Generate a branch if reg is an instance of classObj, otherwise fall-
  through. Cannot change the value of reg (may be used afterwards)."
  | classIndex jmp |
  <inline: true>
  <var: #targetFixUp type: #'AbstractInstruction *'>
  <var: #jmp type: #'AbstractInstruction *'>
  classIndex := objectMemory classTagForClass: classObj.
+ classIndex = (objectMemory fetchClassTagOf: objectMemory falseObject)
+ ifTrue: [ self branchIf: reg isOop: objectMemory falseObject target: targetFixUp ].
+ classIndex = (objectMemory fetchClassTagOf: objectMemory trueObject)
+ ifTrue: [ self branchIf: reg isOop: objectMemory trueObject target: targetFixUp ].
+ classIndex = (objectMemory fetchClassTagOf: objectMemory nilObject)
+ ifTrue: [ self branchIf: reg isOop: objectMemory nilObject target: targetFixUp ].
  (objectMemory isImmediateClass: classObj)
  ifTrue:
  [self branchIf: reg hasImmediateTag: classIndex target: targetFixUp ]
  ifFalse:
  [jmp := (self genJumpImmediate: reg) .
  self genGetClassIndexOfNonImm: reg into: TempReg.
  self genCmpClassIndex: classIndex R: TempReg.
  cogit JumpZero: targetFixUp.
  jmp jmpTarget: cogit Label ].
  ^0!

Item was added:
+ ----- Method: CogObjectRepresentationForSpur>>branchIf:isNotOop:target: (in category 'sista support') -----
+ branchIf: reg isNotOop:  oop target: targetFixup
+ <var: #targetFixUp type: #'AbstractInstruction *'>
+ <inline: true>
+ cogit CmpCq: oop R: reg.
+ cogit JumpNonZero: targetFixup.
+ ^ 0!

Item was added:
+ ----- Method: CogObjectRepresentationForSpur>>branchIf:isOop:target: (in category 'sista support') -----
+ branchIf: reg isOop:  oop target: targetFixup
+ <var: #targetFixUp type: #'AbstractInstruction *'>
+ <inline: true>
+ cogit CmpCq: oop R: reg.
+ cogit JumpZero: targetFixup.
+ ^ 0!

Item was changed:
  ----- Method: CogObjectRepresentationForSpur>>branchIf:notInstanceOfBehavior:target: (in category 'sista support') -----
  branchIf: reg notInstanceOfBehavior: classObj target: targetFixUp
  "Generate a branch if reg is an instance of classObj, otherwise fall-
  through. Cannot change the value of reg (may be used afterwards)."
  | classIndex |
  <inline: true>
  <var: #targetFixUp type: #'AbstractInstruction *'>
  classIndex := objectMemory classTagForClass: classObj.
+ classIndex = (objectMemory fetchClassTagOf: objectMemory falseObject)
+ ifTrue: [ self branchIf: reg isNotOop: objectMemory falseObject target: targetFixUp ].
+ classIndex = (objectMemory fetchClassTagOf: objectMemory trueObject)
+ ifTrue: [ self branchIf: reg isNotOop:  objectMemory trueObject target: targetFixUp ].
+ classIndex = (objectMemory fetchClassTagOf: objectMemory nilObject)
+ ifTrue: [ self branchIf: reg isNotOop:  objectMemory nilObject target: targetFixUp ].
  (objectMemory isImmediateClass: classObj)
  ifTrue:
  [self branchIf: reg hasNotImmediateTag: classIndex target: targetFixUp ]
  ifFalse:
  [(self genJumpImmediate: reg) jmpTarget: targetFixUp.
  self genGetClassIndexOfNonImm: reg into: TempReg.
  self genCmpClassIndex: classIndex R: TempReg.
  cogit JumpNonZero: targetFixUp ].
  ^0!

Item was added:
+ ----- Method: CogObjectRepresentationForSpur>>genGetIdentityHash:resultReg: (in category 'sista support') -----
+ genGetIdentityHash: rcvrReg resultReg: resultReg
+ <var: #jumpSet type: #'AbstractInstruction *'>
+ | jumpSet |
+ "ReceiverResultReg is required for the trampoline. We force the allocation,
+ and we have two path to avoid conflicts in ReceiverResultReg."
+ cogit voidReceiverResultRegContainsSelf.
+ resultReg = ReceiverResultReg
+ ifTrue:
+ [cogit ssTop popToReg: rcvrReg.
+ self genGetHashFieldNonImmOf: rcvrReg asSmallIntegerInto: resultReg.
+ cogit CmpCq: ConstZero R: resultReg.
+ jumpSet := cogit JumpNonZero: 0.
+ cogit MoveR: rcvrReg R: resultReg.
+ cogit CallRT: ceNewHashTrampoline.
+ cogit annotateBytecode: cogit Label]
+ ifFalse:
+ [cogit ssTop popToReg: ReceiverResultReg.
+ self genGetHashFieldNonImmOf: ReceiverResultReg asSmallIntegerInto: resultReg.
+ cogit CmpCq: ConstZero R: resultReg.
+ jumpSet := cogit JumpNonZero: 0.
+ cogit CallRT: ceNewHashTrampoline.
+ cogit annotateBytecode: (cogit MoveR: ReceiverResultReg R: resultReg)].
+ jumpSet jmpTarget: cogit Label.!

Item was added:
+ ----- Method: CogObjectRepresentationForSpur>>genNewHashTrampoline (in category 'initialization') -----
+ genNewHashTrampoline
+ "In non sista VM this is used only from the identityHash primitive, hence only the result of the trampoline, the hash, should be in ReceiverResultReg, other registers can just be ignored.
+ In the sista VM, the inlined hash operation requires registers to be saved"
+ <inline: true>
+ <option: #SistaVM>
+ ^ cogit
+ genTrampolineFor: 1
+ called: 'newHashTrampoline'
+ numArgs: 1
+ arg: ReceiverResultReg
+ arg: nil
+ arg: nil
+ arg: nil
+ regsToSave: (CallerSavedRegisterMask bitClear: (cogit registerMaskFor: ReceiverResultReg))
+ pushLinkReg: true
+ resultReg: ReceiverResultReg
+ appendOpcodes: true!

Item was changed:
  ----- Method: CogObjectRepresentationForSpur>>generateObjectRepresentationTrampolines (in category 'initialization') -----
  generateObjectRepresentationTrampolines
  "Do the store check.  Answer the argument for the benefit of the code generator;
  ReceiverResultReg may be caller-saved and hence smashed by this call.  Answering
  it allows the code generator to reload ReceiverResultReg cheaply.
  In Spur the only thing we leave to the run-time is adding the receiver to the
  remembered set and setting its isRemembered bit."
  self
  cppIf: IMMUTABILITY
  ifTrue:
  [self cCode: [] inSmalltalk:
  [ceStoreTrampolines := CArrayAccessor on: (Array new: NumStoreTrampolines)].
  0 to: NumStoreTrampolines - 1 do:
  [:instVarIndex |
  ceStoreTrampolines
  at: instVarIndex
  put: (self
  genStoreTrampolineCalled: (cogit
  trampolineName: 'ceStoreTrampoline'
  numArgs: instVarIndex
  limit: NumStoreTrampolines - 2)
  instVarIndex: instVarIndex)]].
+ SistaVM ifTrue: [ceNewHashTrampoline := self genNewHashTrampoline].
  ceStoreCheckTrampoline := self genStoreCheckTrampoline.
  ceStoreCheckContextReceiverTrampoline := self genStoreCheckContextReceiverTrampoline.
  ceScheduleScavengeTrampoline := cogit
  genTrampolineFor: #ceScheduleScavenge
  called: 'ceScheduleScavengeTrampoline'
  regsToSave: CallerSavedRegisterMask.
  ceSmallActiveContextInMethodTrampoline := self genActiveContextTrampolineLarge: false inBlock: 0 called: 'ceSmallMethodContext'.
  ceSmallActiveContextInBlockTrampoline := self genActiveContextTrampolineLarge: false inBlock: InVanillaBlock called: 'ceSmallBlockContext'.
  SistaV1BytecodeSet ifTrue:
  [ceSmallActiveContextInFullBlockTrampoline := self genActiveContextTrampolineLarge: false inBlock: InFullBlock called: 'ceSmallFullBlockContext'].
  ceLargeActiveContextInMethodTrampoline := self genActiveContextTrampolineLarge: true inBlock: 0 called: 'ceLargeMethodContext'.
  ceLargeActiveContextInBlockTrampoline := self genActiveContextTrampolineLarge: true inBlock: InVanillaBlock called: 'ceLargeBlockContext'.
  SistaV1BytecodeSet ifTrue:
  [ceLargeActiveContextInFullBlockTrampoline := self genActiveContextTrampolineLarge: true inBlock: InFullBlock called: 'ceLargeFullBlockContext'].
 
  LowcodeVM ifTrue: [ self generateLowcodeObjectTrampolines ]!

Item was changed:
  ----- Method: SistaCogit>>genUnaryInlinePrimitive: (in category 'inline primitive generators') -----
  genUnaryInlinePrimitive: prim
  "Unary inline primitives."
  "SistaV1: 248 11111000 iiiiiiii mjjjjjjj Call Primitive #iiiiiiii + (jjjjjjj * 256) m=1 means inlined primitive, no hard return after execution.
  See EncoderForSistaV1's class comment and StackInterpreter>>#unaryInlinePrimitive:"
  | rcvrReg resultReg |
  rcvrReg := self allocateRegForStackEntryAt: 0.
  resultReg := self allocateRegNotConflictingWith: (self registerMaskFor: rcvrReg).
  prim
  caseOf: {
  "00 unchecked class"
  [1] -> "01 unchecked pointer numSlots"
  [self ssTop popToReg: rcvrReg.
  self ssPop: 1.
  objectRepresentation
  genGetNumSlotsOf: rcvrReg into: resultReg;
  genConvertIntegerToSmallIntegerInReg: resultReg].
  "02 unchecked pointer basicSize"
  [3] -> "03 unchecked byte numBytes"
  [self ssTop popToReg: rcvrReg.
  self ssPop: 1.
  objectRepresentation
  genGetNumBytesOf: rcvrReg into: resultReg;
  genConvertIntegerToSmallIntegerInReg: resultReg].
  "04 unchecked short16Type format numShorts"
  "05 unchecked word32Type format numWords"
  "06 unchecked doubleWord64Type format numDoubleWords"
  [11] -> "11 unchecked fixed pointer basicNew"
  [self ssTop type ~= SSConstant ifTrue:
  [^EncounteredUnknownBytecode].
  (objectRepresentation
  genGetInstanceOf: self ssTop constant
  into: resultReg
  initializingIf: self extBSpecifiesInitializeInstance) ~= 0 ifTrue:
  [^ShouldNotJIT]. "e.g. bad class"
  self ssPop: 1] .
  [20] -> "20 identityHash"
+ [objectRepresentation genGetIdentityHash: rcvrReg resultReg: resultReg.
- [self ssTop popToReg: rcvrReg.
- objectRepresentation genGetHashFieldNonImmOf: rcvrReg asSmallIntegerInto: resultReg.
  self ssPop: 1] .
  "21 identityHash (SmallInteger)"
  "22 identityHash (Character)"
  "23 identityHash (SmallFloat64)"
  "24 identityHash (Behavior)"
  "30 immediateAsInteger (Character)
  31 immediateAsInteger (SmallFloat64)"
  [30] ->
  [self ssTop popToReg: resultReg.
  objectRepresentation genConvertCharacterToSmallIntegerInReg: resultReg.
  self ssPop: 1]
   }
 
  otherwise:
  [^EncounteredUnknownBytecode].
  extB := 0.
  numExtB := 0.
  self ssPushRegister: resultReg.
  ^0!

Item was changed:
  ----- Method: Spur32BitMemoryManager>>fetchClassTagOf: (in category 'interpreter access') -----
  fetchClassTagOf: oop
+ <api>
  | tagBits |
  ^(tagBits := oop bitAnd: self tagMask) ~= 0
  ifTrue: [(tagBits bitAnd: 1) ~= 0 ifTrue: [1] ifFalse: [tagBits]]
  ifFalse: [self classIndexOf: oop]!

Item was changed:
  ----- Method: SpurMemoryManager>>hashBitsOf: (in category 'header access') -----
  hashBitsOf: objOop
  | hash |
  hash := self rawHashBitsOf: objOop.
  hash = 0 ifTrue:
  ["would like to assert
  self assert: (coInterpreter addressCouldBeClassObj: objOop) not
   but instance-specific behaviors that are instances of themselves may
   fail this test."
+ hash := self newHashBitsOf: objOop].
- hash := self newObjectHash bitAnd: self identityHashHalfWordMask.
- self setHashBitsOf: objOop to: hash].
  ^hash!

Item was added:
+ ----- Method: SpurMemoryManager>>newHashBitsOf: (in category 'header access') -----
+ newHashBitsOf: objOop
+ | hash |
+ hash := self newObjectHash bitAnd: self identityHashHalfWordMask.
+ self setHashBitsOf: objOop to: hash.
+ ^hash!