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

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

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

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

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

Name: VMMaker.oscog-eem.2240
Author: eem
Time: 9 June 2017, 8:10:37.386604 pm
UUID: b7a78631-1fbc-42e2-a0e2-0a950a5db06e
Ancestors: VMMaker.oscog-eem.2239

Fix (I think) genGetInstanceOfFixedClass:into:initializingIf: for duff's device instance creation, and restore its use in genUnaryInlinePrimitive:.

Clément, I think I got it right.  I tested the generated code worked correctly for the 11 slot case and then did in-image compilation for a set of classes with slot sizes 9 thorugh 32 and the code looks good.  I hope you don't mind.

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

Item was changed:
+ ----- Method: CogObjectRepresentationForSpur>>genGetInstanceOf:into:initializingIf: (in category 'inline primitive support') -----
- ----- Method: CogObjectRepresentationForSpur>>genGetInstanceOf:into:initializingIf: (in category 'bytecode generator support') -----
  genGetInstanceOf: classObj into: destReg initializingIf: initializeInstance
  "Create an instance of classObj and assign it to destReg, initializing the instance
  if initializeInstance is true with nil or 0 as appropriate This is for inline primitives.
  Assume there is sufficient space in new space to complete the operation.
  Answer zero on success."
  | classIndex classFormat header slots |
  ((objectMemory isNonImmediate: classObj)
  and: [(coInterpreter objCouldBeClassObj: classObj)
  and: [(classIndex := objectMemory rawHashBitsOf: classObj) ~= 0
  and: [(objectMemory isFixedSizePointerFormat: (objectMemory instSpecOfClassFormat: (classFormat := objectMemory formatOfClass: classObj)))
  and: [(slots := objectMemory fixedFieldsOfClassFormat: classFormat) < objectMemory numSlotsMask]]]]) ifFalse:
  [^UnimplementedOperation].
 
  self deny: destReg = TempReg.
 
  header := objectMemory
  headerForSlots: slots
  format: (objectMemory instSpecOfClassFormat: classFormat)
  classIndex: classIndex.
 
  cogit MoveAw: objectMemory freeStartAddress R: destReg.
  self genStoreHeader: header intoNewInstance: destReg using: TempReg.
  cogit
  LoadEffectiveAddressMw: (objectMemory smallObjectBytesForSlots: slots) r: destReg R: TempReg;
  MoveR: TempReg Aw: objectMemory freeStartAddress.
  (initializeInstance and: [slots > 0]) ifTrue:
  [cogit genMoveConstant: objectMemory nilObject R: TempReg.
  0 to: slots - 1 do:
  [:i| cogit MoveR: TempReg
  Mw: i * objectMemory wordSize + objectMemory baseHeaderSize
  r: destReg]].
  ^0!

Item was changed:
+ ----- Method: CogObjectRepresentationForSpur>>genGetInstanceOfFixedClass:into:initializingIf: (in category 'inline primitive support') -----
- ----- Method: CogObjectRepresentationForSpur>>genGetInstanceOfFixedClass:into:initializingIf: (in category 'bytecode generator support') -----
  genGetInstanceOfFixedClass: classObj into: destReg initializingIf: initializeInstance
  "Create an instance of classObj and assign it to destReg, initializing the instance
  if initializeInstance is true with nil or 0 as appropriate This is for inline primitives.
  Assume there is sufficient space in new space to complete the operation.
  Answer zero on success."
  | classIndex classFormat header slots branch constReg inst loop delta loopCount slotsPerIteration |
  ((objectMemory isNonImmediate: classObj)
  and: [(coInterpreter objCouldBeClassObj: classObj)
  and: [(classIndex := objectMemory rawHashBitsOf: classObj) ~= 0
  and: [(objectMemory isFixedSizePointerFormat: (objectMemory instSpecOfClassFormat: (classFormat := objectMemory formatOfClass: classObj)))
  and: [(slots := objectMemory fixedFieldsOfClassFormat: classFormat) < objectMemory numSlotsMask]]]]) ifFalse:
  [^UnimplementedOperation].
 
  header := objectMemory
  headerForSlots: slots
  format: (objectMemory instSpecOfClassFormat: classFormat)
  classIndex: classIndex.
 
  cogit MoveAw: objectMemory freeStartAddress R: destReg.
  self genStoreHeader: header intoNewInstance: destReg using: TempReg.
  cogit
  LoadEffectiveAddressMw: (objectMemory smallObjectBytesForSlots: slots) r: destReg R: TempReg;
  MoveR: TempReg Aw: objectMemory freeStartAddress.
  (initializeInstance and: [slots > 0]) ifFalse:
  [^0].
+ slots <= (slotsPerIteration := 8) ifTrue: "slotsPerIteration must be even; see cogit SubCq: objectMemory bytesPerOop R: TempReg below"
- slots <= (slotsPerIteration := 8) ifTrue: "slotsPerIteration must be a power of two. see bitAnd: below"
  [cogit genMoveConstant: objectMemory nilObject R: TempReg.
  0 to: slots - 1 do:
  [:i| cogit MoveR: TempReg
  Mw: i * objectMemory wordSize + objectMemory baseHeaderSize
  r: destReg].
  ^0].
+ "self halt: 'genGetInstanceOfFixedClass:... ', slots asInteger."
  constReg := cogit allocateRegNotConflictingWith: destReg.
  cogit genMoveConstant: objectMemory nilObject R: constReg.
 
  slots \\ slotsPerIteration ~= 0
+ ifTrue: "delta maps the offset at the loop entryPoint onto destReg + objectMemory baseHeaderSize"
+ [delta := (slotsPerIteration - (slots \\ slotsPerIteration) * objectMemory bytesPerOop) - objectMemory baseHeaderSize.
+ delta > 0 ifTrue: [cogit SubCq: delta R: destReg].
+ delta < 0 ifTrue: [cogit AddCq: delta negated R: destReg].
+ "now delta maps (loopCount * slotsPerIteration * objectMemory bytesPerOop) + objectMemory baseHeaderSize - delta to the start of the object"
+ delta := delta + objectMemory baseHeaderSize.
+ (objectMemory bytesPerOop < objectMemory baseHeaderSize
+  and: [slots \\ 2 = 1]) ifTrue: "if end of loop is not at start of next object, adjust loop limit in TempReg to point to last field filled."
+ [cogit SubCq: objectMemory bytesPerOop R: TempReg].
- ifTrue:
- [delta := objectMemory baseHeaderSize - ((slotsPerIteration - (slots \\ slotsPerIteration) bitAnd: slotsPerIteration - 1) * objectMemory bytesPerOop).
- delta ~= 0 ifTrue:
- [cogit AddCq: delta R: destReg].
  branch := cogit Jump: 0]
  ifFalse:
+ [delta := 0.
- [delta := objectMemory baseHeaderSize.
  cogit AddCq: objectMemory baseHeaderSize R: destReg].
+ "loopCount is number of times through the increment of destReg."
  loopCount := slots + slotsPerIteration - 1 // slotsPerIteration.
  self assert: loopCount > 1.
  loop := cogit Label.
  0 to: 7 do:
  [:i|
  inst := cogit MoveR: constReg Mw: i * objectMemory bytesPerOop r: destReg.
  slotsPerIteration - (slots \\ slotsPerIteration) = i ifTrue:
  [branch jmpTarget: inst]].
- "N.B. We get away with comparing against TempReg, which points to the start of the next
- object, not necessarily immediately after the last slot, because if the size is a multiple of 8,
- TempReg will point after the last slot, and if the size is not a multiple of 8 then the add of
- slotsPerIteration * objectMemory bytesPerOop will put destReg beyond TempReg any way."
  cogit
  AddCq: slotsPerIteration * objectMemory bytesPerOop R: destReg;
  CmpR: TempReg R: destReg;
  JumpBelow: loop;
+ SubCq: (loopCount * slotsPerIteration * objectMemory bytesPerOop) + objectMemory baseHeaderSize - delta R: destReg.
- SubCq: delta + (loopCount * slotsPerIteration * objectMemory bytesPerOop) R: destReg.
  ^0!

Item was changed:
+ ----- Method: CogObjectRepresentationForSpur>>genSetGCNeeded (in category 'inline primitive support') -----
- ----- Method: CogObjectRepresentationForSpur>>genSetGCNeeded (in category 'bytecode generator support') -----
  genSetGCNeeded
  <inline: true>
  cogit
  MoveCq: 1 R: TempReg;
  MoveR: TempReg Aw: coInterpreter needGCFlagAddress!

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
+ genGetInstanceOfFixedClass: self ssTop constant
- genGetInstanceOf: self ssTop constant
  into: resultReg
+ initializingIf: self extBSpecifiesInitializeInstance) ~= 0 ifTrue:
- initializingIf: self extBSpecifiesInitializeInstance) ~= 0 ifTrue:
  [^ShouldNotJIT]. "e.g. bad class"
  self ssPop: 1] .
  [20] -> "20 identityHash"
  [objectRepresentation genGetIdentityHash: rcvrReg resultReg: resultReg.
  self ssPop: 1] .
  "21 identityHash (SmallInteger)"
  "22 identityHash (Character)"
  "23 identityHash (SmallFloat64)"
  "24 identityHash (Behavior)"
  "30 immediateAsInteger (Character)
  31 immediateAsInteger (SmallFloat64)
  35 immediateAsFloat  (SmallInteger) "
  [30] ->
  [self ssTop popToReg: resultReg.
  objectRepresentation genConvertCharacterToSmallIntegerInReg: resultReg.
  self ssPop: 1].
  [35] ->
  [self assert: self processorHasDoublePrecisionFloatingPointSupport.
  self MoveR: rcvrReg R: TempReg.
  self genConvertSmallIntegerToIntegerInReg: TempReg.
  self ConvertR: TempReg Rd: DPFPReg0.
  self flag: #TODO. "Should never fail"
  self
  genAllocFloatValue: DPFPReg0
  into: resultReg
  scratchReg: TempReg
  scratchReg: NoReg. "scratch2 for V3 only"]
   }
 
  otherwise:
  [^EncounteredUnknownBytecode].
  extB := 0.
  numExtB := 0.
  self ssPushRegister: resultReg.
  ^0!

Reply | Threaded
Open this post in threaded view
|

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

Eliot Miranda-2
 
Hi Clément, Hi Tim F,

    forgive me.  I managed to find the energy to fix the duff's device code.  I did so by a) making sayer that the image you supplied worked for the case of the 11 slot SqNumberParser that gets instantiated many times, and b) by using the following to look at all the cases:

| classes method |
classes := (9 to: 16) collect: [:n| Smalltalk allClasses detect: [:c| c instSize = n]].
method := AssemblerMethod new.
method
importMethodClass: #Object;
selector: #instantiate;
signFlag: true;
numArgs: 0.
classes do: [:c| method literal: c].
classes do: [:c| method pushConstant: c; callInlinePrimitive: 1011].
method
pushConsArrayWithElements: 8;
methodReturnTop.
SistaCogit 
genAndDis: method assemble
options: #(ObjectMemory Spur32BitCoMemoryManager
MULTIPLEBYTECODESETS true
SistaVM true
bytecodeTableInitializer initializeBytecodeTableForSqueakV3PlusClosuresSistaV1Hybrid)

Clément, you should be able to run the method and get an Array of classes  here's the code its generating.  I especially like that register allocation is working nicely with the results only being spilled once needed to do another allocation.

The first case is a 9 slot object, making 1 1/8 trips through the 8-element loop
00001861: movl %ds:0x8001c=#freeStart, %esi allocate the object to %esi
00001867: movl $0x01001b9f, %eax
0000186c: movl %eax, %ds:(%esi) store least significant half of header
0000186e: movl $0x09000000, %eax
00001873: movl %eax, %ds:0x4(%esi) store most significant half of header
00001876: leal %ds:0x30(%esi), %eax
00001879: movl %eax, %ds:0x8001c=#freeStart update freeStart to point to the start of the next object
0000187e: movl $0x00100000=nil, %edi
00001883: subl $0x00000014, %esi offset result for entry into the last instruction of loop
00001886: subl $0x00000004, %eax
00001889: jmp .+0x00000014 (0x0000189f=instantiate@9F)
0000188b: movl %edi, %ds:(%esi)
0000188d: movl %edi, %ds:0x4(%esi)
00001890: movl %edi, %ds:0x8(%esi)
00001893: movl %edi, %ds:0xc(%esi)
00001896: movl %edi, %ds:0x10(%esi)
00001899: movl %edi, %ds:0x14(%esi)
0000189c: movl %edi, %ds:0x18(%esi)
=>00189f: movl %edi, %ds:0x1c(%esi)
000018a2: addl $0x00000020, %esi increment result for next iteration of loop
000018a5: cmpl %eax, %esi
000018a7: jb .+0xffffffe2 (0x0000188b=instantiate@8B) jump to beginning of loop if not done
000018a9: subl $0x0000002c, %esi offset updated result to point back to start of object

000018ac: movl %ds:0x8001c=#freeStart, %ebx
000018b2: movl $0x01001ba3, %eax
000018b7: movl %eax, %ds:(%ebx)
000018b9: movl $0x0a000000, %eax
000018be: movl %eax, %ds:0x4(%ebx)
000018c1: leal %ds:0x30(%ebx), %eax
000018c4: movl %eax, %ds:0x8001c=#freeStart
000018c9: movl $0x00100000=nil, %edi
000018ce: subl $0x00000010, %ebx
000018d1: jmp .+0x00000011 (0x000018e4=instantiate@E4)
000018d3: movl %edi, %ds:(%ebx)
000018d5: movl %edi, %ds:0x4(%ebx)
000018d8: movl %edi, %ds:0x8(%ebx)
000018db: movl %edi, %ds:0xc(%ebx)
000018de: movl %edi, %ds:0x10(%ebx)
000018e1: movl %edi, %ds:0x14(%ebx)
000018e4: movl %edi, %ds:0x18(%ebx)
000018e7: movl %edi, %ds:0x1c(%ebx)
000018ea: addl $0x00000020, %ebx
000018ed: cmpl %eax, %ebx
000018ef: jb .+0xffffffe2 (0x000018d3=instantiate@D3)
000018f1: subl $0x00000030, %ebx

000018f4: movl %ds:0x8001c=#freeStart, %ecx
000018fa: movl $0x01001b9e, %eax
000018ff: movl %eax, %ds:(%ecx)
00001901: movl $0x0b000000, %eax
00001906: movl %eax, %ds:0x4(%ecx)
00001909: leal %ds:0x38(%ecx), %eax
0000190c: movl %eax, %ds:0x8001c=#freeStart
00001911: movl $0x00100000=nil, %edi
00001916: subl $0x0000000c, %ecx
00001919: subl $0x00000004, %eax
0000191c: jmp .+0x0000000e (0x0000192c=instantiate@12C)
0000191e: movl %edi, %ds:(%ecx)
00001920: movl %edi, %ds:0x4(%ecx)
00001923: movl %edi, %ds:0x8(%ecx)
00001926: movl %edi, %ds:0xc(%ecx)
00001929: movl %edi, %ds:0x10(%ecx)
0000192c: movl %edi, %ds:0x14(%ecx)
0000192f: movl %edi, %ds:0x18(%ecx)
00001932: movl %edi, %ds:0x1c(%ecx)
00001935: addl $0x00000020, %ecx
00001938: cmpl %eax, %ecx
0000193a: jb .+0xffffffe2 (0x0000191e=instantiate@11E)
0000193c: subl $0x00000034, %ecx

0000193f: movl %ds:0x8001c=#freeStart, %edx
00001945: movl $0x0100179a, %eax
0000194a: movl %eax, %ds:(%edx)
0000194c: movl $0x0c000000, %eax
00001951: movl %eax, %ds:0x4(%edx)
00001954: leal %ds:0x38(%edx), %eax
00001957: movl %eax, %ds:0x8001c=#freeStart
0000195c: movl $0x00100000=nil, %edi
00001961: subl $0x00000008, %edx
00001964: jmp .+0x0000000b (0x00001971=instantiate@171)
00001966: movl %edi, %ds:(%edx)
00001968: movl %edi, %ds:0x4(%edx)
0000196b: movl %edi, %ds:0x8(%edx)
0000196e: movl %edi, %ds:0xc(%edx)
00001971: movl %edi, %ds:0x10(%edx)
00001974: movl %edi, %ds:0x14(%edx)
00001977: movl %edi, %ds:0x18(%edx)
0000197a: movl %edi, %ds:0x1c(%edx)
0000197d: addl $0x00000020, %edx
00001980: cmpl %eax, %edx
00001982: jb .+0xffffffe2 (0x00001966=instantiate@166)
00001984: subl $0x00000038, %edx
00001987: pushl %esi

00001988: movl %ds:0x8001c=#freeStart, %esi
0000198e: movl $0x0100155c, %eax
00001993: movl %eax, %ds:(%esi)
00001995: movl $0x0d000000, %eax
0000199a: movl %eax, %ds:0x4(%esi)
0000199d: leal %ds:0x40(%esi), %eax
000019a0: movl %eax, %ds:0x8001c=#freeStart
000019a5: movl $0x00100000=nil, %edi
000019aa: subl $0x00000004, %esi
000019ad: subl $0x00000004, %eax
000019b0: jmp .+0x00000008 (0x000019ba=instantiate@1BA)
000019b2: movl %edi, %ds:(%esi)
000019b4: movl %edi, %ds:0x4(%esi)
000019b7: movl %edi, %ds:0x8(%esi)
000019ba: movl %edi, %ds:0xc(%esi)
000019bd: movl %edi, %ds:0x10(%esi)
000019c0: movl %edi, %ds:0x14(%esi)
000019c3: movl %edi, %ds:0x18(%esi)
000019c6: movl %edi, %ds:0x1c(%esi)
000019c9: addl $0x00000020, %esi
000019cc: cmpl %eax, %esi
000019ce: jb .+0xffffffe2 (0x000019b2=instantiate@1B2)
000019d0: subl $0x0000003c, %esi
000019d3: pushl %ebx

000019d4: movl %ds:0x8001c=#freeStart, %ebx
000019da: movl $0x01000668, %eax
000019df: movl %eax, %ds:(%ebx)
000019e1: movl $0x0e000000, %eax
000019e6: movl %eax, %ds:0x4(%ebx)
000019e9: leal %ds:0x40(%ebx), %eax
000019ec: movl %eax, %ds:0x8001c=#freeStart
000019f1: movl $0x00100000=nil, %edi
000019f6: jmp .+0x00000005 (0x000019fd=instantiate@1FD)
000019f8: movl %edi, %ds:(%ebx)
000019fa: movl %edi, %ds:0x4(%ebx)
000019fd: movl %edi, %ds:0x8(%ebx)
00001a00: movl %edi, %ds:0xc(%ebx)
00001a03: movl %edi, %ds:0x10(%ebx)
00001a06: movl %edi, %ds:0x14(%ebx)
00001a09: movl %edi, %ds:0x18(%ebx)
00001a0c: movl %edi, %ds:0x1c(%ebx)
00001a0f: addl $0x00000020, %ebx
00001a12: cmpl %eax, %ebx
00001a14: jb .+0xffffffe2 (0x000019f8=instantiate@1F8)
00001a16: subl $0x00000040, %ebx
00001a19: pushl %ecx

00001a1a: movl %ds:0x8001c=#freeStart, %ecx
00001a20: movl $0x01001bd3, %eax
00001a25: movl %eax, %ds:(%ecx)
00001a27: movl $0x0f000000, %eax
00001a2c: movl %eax, %ds:0x4(%ecx)
00001a2f: leal %ds:0x48(%ecx), %eax
00001a32: movl %eax, %ds:0x8001c=#freeStart
00001a37: movl $0x00100000=nil, %edi
00001a3c: addl $0x00000004, %ecx
00001a3f: subl $0x00000004, %eax
00001a42: jmp .+0x00000002 (0x00001a46=instantiate@246)
00001a44: movl %edi, %ds:(%ecx)
00001a46: movl %edi, %ds:0x4(%ecx)
00001a49: movl %edi, %ds:0x8(%ecx)
00001a4c: movl %edi, %ds:0xc(%ecx)
00001a4f: movl %edi, %ds:0x10(%ecx)
00001a52: movl %edi, %ds:0x14(%ecx)
00001a55: movl %edi, %ds:0x18(%ecx)
00001a58: movl %edi, %ds:0x1c(%ecx)
00001a5b: addl $0x00000020, %ecx
00001a5e: cmpl %eax, %ecx
00001a60: jb .+0xffffffe2 (0x00001a44=instantiate@244)
00001a62: subl $0x00000044, %ecx
00001a65: pushl %edx

The final case is a 16 slot object, making 2 trips through the 8-element loop
00001a66: movl %ds:0x8001c=#freeStart, %edx
00001a6c: movl $0x01001bd0, %eax
00001a71: movl %eax, %ds:(%edx)
00001a73: movl $0x10000000, %eax
00001a78: movl %eax, %ds:0x4(%edx)
00001a7b: leal %ds:0x48(%edx), %eax
00001a7e: movl %eax, %ds:0x8001c=#freeStart
00001a83: movl $0x00100000=nil, %edi
00001a88: addl $0x00000008, %edx offset result to skip header
00001a8b: movl %edi, %ds:(%edx)
00001a8d: movl %edi, %ds:0x4(%edx)
00001a90: movl %edi, %ds:0x8(%edx)
00001a93: movl %edi, %ds:0xc(%edx)
00001a96: movl %edi, %ds:0x10(%edx)
00001a99: movl %edi, %ds:0x14(%edx)
00001a9c: movl %edi, %ds:0x18(%edx)
00001a9f: movl %edi, %ds:0x1c(%edx)
00001aa2: addl $0x00000020, %edx
00001aa5: cmpl %eax, %edx
00001aa7: jb .+0xffffffe2 (0x00001a8b=instantiate@28B)
00001aa9: subl $0x00000048, %edx offset updated result to point back to start of object

And this pushes the remaining results and cones an 8 element array with the results
00001aac: pushl %esi
00001aad: pushl %ebx
00001aae: pushl %ecx
00001aaf: pushl %edx
00001ab0: movl %ds:0x8001c=#freeStart, %edx
00001ab6: movl $0x02000033, %eax
00001abb: movl %eax, %ds:(%edx)
00001abd: movl $0x08000000, %eax
00001ac2: movl %eax, %ds:0x4(%edx)
00001ac5: leal %ds:0x28(%edx), %eax
00001ac8: movl %eax, %ds:0x8001c=#freeStart
00001acd: cmpl $0x00060000='scavengeThreshold', %eax
00001ad2: jb .+0x00000005 (0x00001ad9=instantiate@2D9)
00001ad4: call .+0xfffff1df (0x00000cb8=ceScheduleScavengeTrampoline)
IsRelativeCall:
00001ad9: popl %eax
00001ada: movl %eax, %ds:0x24(%edx)
00001add: popl %eax
00001ade: movl %eax, %ds:0x20(%edx)
00001ae1: popl %eax
00001ae2: movl %eax, %ds:0x1c(%edx)
00001ae5: popl %eax
00001ae6: movl %eax, %ds:0x18(%edx)
00001ae9: popl %eax
00001aea: movl %eax, %ds:0x14(%edx)
00001aed: popl %eax
00001aee: movl %eax, %ds:0x10(%edx)
00001af1: popl %eax
00001af2: movl %eax, %ds:0xc(%edx)
00001af5: popl %eax
00001af6: movl %eax, %ds:0x8(%edx)

00001af9: movl %ebp, %esp
00001afb: popl %ebp
00001afc: ret $0x0004

On Fri, Jun 9, 2017 at 8:11 PM, <[hidden email]> wrote:
 
Eliot Miranda uploaded a new version of VMMaker to project VM Maker:
http://source.squeak.org/VMMaker/VMMaker.oscog-eem.2240.mcz

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

Name: VMMaker.oscog-eem.2240
Author: eem
Time: 9 June 2017, 8:10:37.386604 pm
UUID: b7a78631-1fbc-42e2-a0e2-0a950a5db06e
Ancestors: VMMaker.oscog-eem.2239

Fix (I think) genGetInstanceOfFixedClass:into:initializingIf: for duff's device instance creation, and restore its use in genUnaryInlinePrimitive:.

Clément, I think I got it right.  I tested the generated code worked correctly for the 11 slot case and then did in-image compilation for a set of classes with slot sizes 9 thorugh 32 and the code looks good.  I hope you don't mind.

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

Item was changed:
+ ----- Method: CogObjectRepresentationForSpur>>genGetInstanceOf:into:initializingIf: (in category 'inline primitive support') -----
- ----- Method: CogObjectRepresentationForSpur>>genGetInstanceOf:into:initializingIf: (in category 'bytecode generator support') -----
  genGetInstanceOf: classObj into: destReg initializingIf: initializeInstance
        "Create an instance of classObj and assign it to destReg, initializing the instance
         if initializeInstance is true with nil or 0 as appropriate This is for inline primitives.
         Assume there is sufficient space in new space to complete the operation.
         Answer zero on success."
        | classIndex classFormat header slots |
        ((objectMemory isNonImmediate: classObj)
         and: [(coInterpreter objCouldBeClassObj: classObj)
         and: [(classIndex := objectMemory rawHashBitsOf: classObj) ~= 0
         and: [(objectMemory isFixedSizePointerFormat: (objectMemory instSpecOfClassFormat: (classFormat := objectMemory formatOfClass: classObj)))
         and: [(slots := objectMemory fixedFieldsOfClassFormat: classFormat) < objectMemory numSlotsMask]]]]) ifFalse:
                [^UnimplementedOperation].

        self deny: destReg = TempReg.

        header := objectMemory
                                        headerForSlots: slots
                                        format: (objectMemory instSpecOfClassFormat: classFormat)
                                        classIndex: classIndex.

        cogit MoveAw: objectMemory freeStartAddress R: destReg.
        self genStoreHeader: header intoNewInstance: destReg using: TempReg.
        cogit
                LoadEffectiveAddressMw: (objectMemory smallObjectBytesForSlots: slots) r: destReg R: TempReg;
                MoveR: TempReg Aw: objectMemory freeStartAddress.
        (initializeInstance and: [slots > 0]) ifTrue:
                [cogit genMoveConstant: objectMemory nilObject R: TempReg.
                 0 to: slots - 1 do:
                        [:i| cogit MoveR: TempReg
                                        Mw: i * objectMemory wordSize + objectMemory baseHeaderSize
                                        r: destReg]].
        ^0!

Item was changed:
+ ----- Method: CogObjectRepresentationForSpur>>genGetInstanceOfFixedClass:into:initializingIf: (in category 'inline primitive support') -----
- ----- Method: CogObjectRepresentationForSpur>>genGetInstanceOfFixedClass:into:initializingIf: (in category 'bytecode generator support') -----
  genGetInstanceOfFixedClass: classObj into: destReg initializingIf: initializeInstance
        "Create an instance of classObj and assign it to destReg, initializing the instance
         if initializeInstance is true with nil or 0 as appropriate This is for inline primitives.
         Assume there is sufficient space in new space to complete the operation.
         Answer zero on success."
        | classIndex classFormat header slots branch constReg inst loop delta loopCount slotsPerIteration |
        ((objectMemory isNonImmediate: classObj)
         and: [(coInterpreter objCouldBeClassObj: classObj)
         and: [(classIndex := objectMemory rawHashBitsOf: classObj) ~= 0
         and: [(objectMemory isFixedSizePointerFormat: (objectMemory instSpecOfClassFormat: (classFormat := objectMemory formatOfClass: classObj)))
         and: [(slots := objectMemory fixedFieldsOfClassFormat: classFormat) < objectMemory numSlotsMask]]]]) ifFalse:
                [^UnimplementedOperation].

        header := objectMemory
                                        headerForSlots: slots
                                        format: (objectMemory instSpecOfClassFormat: classFormat)
                                        classIndex: classIndex.

        cogit MoveAw: objectMemory freeStartAddress R: destReg.
        self genStoreHeader: header intoNewInstance: destReg using: TempReg.
        cogit
                LoadEffectiveAddressMw: (objectMemory smallObjectBytesForSlots: slots) r: destReg R: TempReg;
                MoveR: TempReg Aw: objectMemory freeStartAddress.
        (initializeInstance and: [slots > 0]) ifFalse:
                [^0].
+       slots <= (slotsPerIteration := 8) ifTrue: "slotsPerIteration must be even; see cogit SubCq: objectMemory bytesPerOop R: TempReg below"
-       slots <= (slotsPerIteration := 8) ifTrue: "slotsPerIteration must be a power of two. see bitAnd: below"
                [cogit genMoveConstant: objectMemory nilObject R: TempReg.
                 0 to: slots - 1 do:
                        [:i| cogit MoveR: TempReg
                                        Mw: i * objectMemory wordSize + objectMemory baseHeaderSize
                                        r: destReg].
                ^0].
+       "self halt: 'genGetInstanceOfFixedClass:... ', slots asInteger."
        constReg := cogit allocateRegNotConflictingWith: destReg.
        cogit genMoveConstant: objectMemory nilObject R: constReg.

        slots \\ slotsPerIteration ~= 0
+               ifTrue: "delta maps the offset at the loop entryPoint onto destReg + objectMemory baseHeaderSize"
+                       [delta := (slotsPerIteration - (slots \\ slotsPerIteration) * objectMemory bytesPerOop) - objectMemory baseHeaderSize.
+                        delta > 0 ifTrue: [cogit SubCq: delta R: destReg].
+                        delta < 0 ifTrue: [cogit AddCq: delta negated R: destReg].
+                        "now delta maps (loopCount * slotsPerIteration * objectMemory bytesPerOop) + objectMemory baseHeaderSize - delta to the start of the object"
+                        delta := delta + objectMemory baseHeaderSize.
+                        (objectMemory bytesPerOop < objectMemory baseHeaderSize
+                         and: [slots \\ 2 = 1]) ifTrue: "if end of loop is not at start of next object, adjust loop limit in TempReg to point to last field filled."
+                               [cogit SubCq: objectMemory bytesPerOop R: TempReg].
-               ifTrue:
-                       [delta := objectMemory baseHeaderSize - ((slotsPerIteration - (slots \\ slotsPerIteration) bitAnd: slotsPerIteration - 1) * objectMemory bytesPerOop).
-                        delta ~= 0 ifTrue:
-                               [cogit AddCq: delta R: destReg].
                         branch := cogit Jump: 0]
                ifFalse:
+                       [delta := 0.
-                       [delta := objectMemory baseHeaderSize.
                         cogit AddCq: objectMemory baseHeaderSize R: destReg].
+       "loopCount is number of times through the increment of destReg."
        loopCount := slots + slotsPerIteration - 1 // slotsPerIteration.
        self assert: loopCount > 1.
        loop := cogit Label.
        0 to: 7 do:
                [:i|
                inst := cogit MoveR: constReg Mw: i * objectMemory bytesPerOop r: destReg.
                slotsPerIteration - (slots \\ slotsPerIteration) = i ifTrue:
                        [branch jmpTarget: inst]].
-       "N.B. We get away with comparing against TempReg, which points to the start of the next
-        object, not necessarily immediately after the last slot, because if the size is a multiple of 8,
-        TempReg will point after the last slot, and if the size is not a multiple of 8 then the add of
-        slotsPerIteration * objectMemory bytesPerOop will put destReg beyond TempReg any way."
        cogit
                AddCq: slotsPerIteration * objectMemory bytesPerOop R: destReg;
                CmpR: TempReg R: destReg;
                JumpBelow: loop;
+               SubCq: (loopCount * slotsPerIteration * objectMemory bytesPerOop) + objectMemory baseHeaderSize - delta R: destReg.
-               SubCq: delta + (loopCount * slotsPerIteration * objectMemory bytesPerOop) R: destReg.
        ^0!

Item was changed:
+ ----- Method: CogObjectRepresentationForSpur>>genSetGCNeeded (in category 'inline primitive support') -----
- ----- Method: CogObjectRepresentationForSpur>>genSetGCNeeded (in category 'bytecode generator support') -----
  genSetGCNeeded
        <inline: true>
        cogit
                MoveCq: 1 R: TempReg;
                MoveR: TempReg Aw: coInterpreter needGCFlagAddress!

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
+                                       genGetInstanceOfFixedClass: self ssTop constant
-                                       genGetInstanceOf: self ssTop constant
                                                into: resultReg
+                                                       initializingIf: self extBSpecifiesInitializeInstance) ~= 0 ifTrue:
-                                               initializingIf: self extBSpecifiesInitializeInstance) ~= 0 ifTrue:
                                        [^ShouldNotJIT]. "e.g. bad class"
                                 self ssPop: 1] .
                        [20] -> "20     identityHash"
                                [objectRepresentation genGetIdentityHash: rcvrReg resultReg: resultReg.
                                 self ssPop: 1] .
                                        "21             identityHash (SmallInteger)"
                                        "22             identityHash (Character)"
                                        "23             identityHash (SmallFloat64)"
                                        "24             identityHash (Behavior)"
                                        "30     immediateAsInteger (Character)
                                         31     immediateAsInteger (SmallFloat64)
                                         35             immediateAsFloat          (SmallInteger)        "
                        [30] ->
                                [self ssTop popToReg: resultReg.
                                 objectRepresentation genConvertCharacterToSmallIntegerInReg: resultReg.
                                 self ssPop: 1].
                        [35] ->
                                [self assert: self processorHasDoublePrecisionFloatingPointSupport.
                                self MoveR: rcvrReg R: TempReg.
                                self genConvertSmallIntegerToIntegerInReg: TempReg.
                                self ConvertR: TempReg Rd: DPFPReg0.
                                self flag: #TODO. "Should never fail"
                                self
                                        genAllocFloatValue: DPFPReg0
                                        into: resultReg
                                        scratchReg: TempReg
                                        scratchReg: NoReg. "scratch2 for V3 only"]
                                  }

                otherwise:
                        [^EncounteredUnknownBytecode].
        extB := 0.
        numExtB := 0.
        self ssPushRegister: resultReg.
        ^0!





--
_,,,^..^,,,_
best, Eliot