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

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

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

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

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

Name: VMMaker.oscog-eem.2684
Author: eem
Time: 29 January 2020, 9:03:48.746473 am
UUID: 6a1e487e-4d6d-4360-8c12-6a12a2266daf
Ancestors: VMMaker.oscog-eem.2683

Dual Mapped Zone:
        provide writableMethodFor: as a convenience for obtaining a writable cogMethod.

Simulation:
        clean up several mistakes in VMMaker.oscog-eem.2683.  Apply the codeTodataDelta inside method surrogates correctly.
        avoid redefining/overriding objectHeader[:] which are defined manually in CogMethodSurrogate (and comment why).  Filter in CogBlockMethod class>>fieldAccessorSourceFor:bytesPerWord:
        Have VMStructType>>checkGenerateSurrogate:bytesPerWord: generate code in #'accessing generated', and fix a few bugs with the differencing code therein.
        fieldAccessorSourceFor:bytesPerWord: has no business filtering *anything*.

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

Item was added:
+ ----- Method: CogBlockMethod class>>fieldAccessorSourceFor:bytesPerWord: (in category 'code generation') -----
+ fieldAccessorSourceFor: surrogateClass bytesPerWord: bytesPerWord
+ "Override to remove the objectHeader[:] accessors as these are defined manually in CogMethodSurrogate"
+ ^(super fieldAccessorSourceFor: surrogateClass bytesPerWord: bytesPerWord)
+ removeKey: {surrogateClass. #objectHeader} ifAbsent: [];
+ removeKey: {surrogateClass. #objectHeader:} ifAbsent: [];
+ yourself!

Item was changed:
  ----- Method: CogBlockMethod class>>setter:bitPosition:bitWidth:type: (in category 'code generation') -----
  setter: getter bitPosition: bitPosition bitWidth: bitWidth type: typeOrNil
  ^String streamContents:
  [:s| | startByte endByte shift alignedPowerOf2 accessor mask |
  startByte := bitPosition // 8.
  endByte := bitPosition + bitWidth - 1 // 8.
  shift := bitPosition \\ 8.
  alignedPowerOf2 := (#(8 16 32 64) includes: bitWidth) and: [shift = 0].
  accessor := 'unsigned'
  , (#('Byte' 'Short' 'Long' 'Long')
  at: endByte - startByte + 1
  ifAbsent: ['Long64'])
  , 'At: index'.
  mask := #(16rFF 16rFFFF 16rFFFFFFFF 16rFFFFFFFF)
  at: endByte - startByte + 1
  ifAbsent: [(2 raisedTo: 64) - 1].
  s nextPutAll: getter; nextPutAll: ': aValue'; crtab: 1.
  s crtab: 1; nextPutAll: '| index delta |'; crtab: 1.
  s nextPutAll: 'index := address + '.
  (self offsetForInstVar: getter) ifNotNil:
  [:offsetExpr| s nextPutAll: offsetExpr, ' + '].
  s print: startByte + 1; nextPut: $.; crtab: 1.
  (typeOrNil notNil or: [alignedPowerOf2]) ifFalse:
  [s nextPutAll: 'self assert: (aValue between: 0 and: '; nextPutAll:  ((1 << bitWidth) - 1) hex; nextPutAll: ').'; crtab: 1].
  s nextPutAll: '(delta := cogit codeToDataDelta) > 0 ifTrue:'; crtab: 2.
  s nextPutAll: '[self assert: (cogit addressIsInCodeZone: address - delta).'; crtab: 2; space.
+ self putAtPut: accessor, ' - delta'
- self putAtPut: accessor
  type: typeOrNil
  mask: (alignedPowerOf2 ifFalse: [mask - ((1 << bitWidth - 1) << shift)])
  shift: shift
  on: s
  indent: 3.
  s nextPutAll: '].'; crtab: 1.
  alignedPowerOf2 ifTrue:
  [s nextPut: $^].
+ self putAtPut: accessor
- self putAtPut: (accessor copyReplaceAll: 'address' with: 'address - delta')
  type: typeOrNil
  mask: (alignedPowerOf2 ifFalse: [mask - ((1 << bitWidth - 1) << shift)])
  shift: shift
  on: s
  indent: 2.
  alignedPowerOf2 ifFalse:
  [s nextPut: $.; crtab: 1; nextPutAll: '^aValue']]!

Item was removed:
- ----- Method: CogBlockMethodSurrogate32>>blockEntryOffset (in category 'accessing generated') -----
- blockEntryOffset
- ^memory unsignedShortAt: address + 7 + baseHeaderSize!

Item was removed:
- ----- Method: CogBlockMethodSurrogate32>>blockEntryOffset: (in category 'accessing generated') -----
- blockEntryOffset: aValue
-
- | index delta |
- index := address + baseHeaderSize + 7.
- (delta := cogit codeToDataDelta) > 0 ifTrue:
- [self assert: (cogit addressIsInCodeZone: address - delta).
- memory
- unsignedShortAt: index
- put: aValue].
- ^memory
- unsignedShortAt: index
- put: aValue!

Item was removed:
- ----- Method: CogBlockMethodSurrogate32>>blockSize (in category 'accessing generated') -----
- blockSize
- ^memory unsignedShortAt: address + 5 + baseHeaderSize!

Item was removed:
- ----- Method: CogBlockMethodSurrogate32>>blockSize: (in category 'accessing generated') -----
- blockSize: aValue
-
- | index delta |
- index := address + baseHeaderSize + 5.
- (delta := cogit codeToDataDelta) > 0 ifTrue:
- [self assert: (cogit addressIsInCodeZone: address - delta).
- memory
- unsignedShortAt: index
- put: aValue].
- ^memory
- unsignedShortAt: index
- put: aValue!

Item was changed:
  ----- Method: CogBlockMethodSurrogate32>>padToWord: (in category 'accessing generated') -----
  padToWord: aValue
 
  | index delta |
  index := address + 5.
  (delta := cogit codeToDataDelta) > 0 ifTrue:
  [self assert: (cogit addressIsInCodeZone: address - delta).
  memory
+ unsignedLongAt: index - delta
- unsignedLongAt: index
  put: aValue].
  ^memory
  unsignedLongAt: index
  put: aValue!

Item was changed:
  ----- Method: CogBlockMethodSurrogate64>>padToWord: (in category 'accessing generated') -----
  padToWord: aValue
 
  | index delta |
  index := address + 5.
  (delta := cogit codeToDataDelta) > 0 ifTrue:
  [self assert: (cogit addressIsInCodeZone: address - delta).
  memory
+ unsignedLong64At: index - delta
- unsignedLong64At: index
  put: aValue].
  ^memory
  unsignedLong64At: index
  put: aValue!

Item was changed:
  ----- Method: CogMethodSurrogate>>cbUsesInstVars: (in category 'accessing generated') -----
  cbUsesInstVars: aValue
 
  | index delta |
  index := address + baseHeaderSize + 3.
  (delta := cogit codeToDataDelta) > 0 ifTrue:
  [self assert: (cogit addressIsInCodeZone: address - delta).
  memory
+ unsignedByteAt: index - delta
+ put: (((memory unsignedByteAt: index - delta) bitAnd: 16rFD) + (aValue ifTrue: [2] ifFalse: [0]))].
- unsignedByteAt: index
- put: (((memory unsignedByteAt: index) bitAnd: 16rFD) + (aValue ifTrue: [2] ifFalse: [0]))].
  memory
  unsignedByteAt: index
  put: (((memory unsignedByteAt: index) bitAnd: 16rFD) + (aValue ifTrue: [2] ifFalse: [0])).
  ^aValue!

Item was changed:
  ----- Method: CogMethodSurrogate>>cmHasMovableLiteral: (in category 'accessing generated') -----
  cmHasMovableLiteral: aValue
 
  | index delta |
  index := address + baseHeaderSize + 3.
  (delta := cogit codeToDataDelta) > 0 ifTrue:
  [self assert: (cogit addressIsInCodeZone: address - delta).
  memory
+ unsignedByteAt: index - delta
+ put: (((memory unsignedByteAt: index - delta) bitAnd: 16rFB) + (aValue ifTrue: [4] ifFalse: [0]))].
- unsignedByteAt: index
- put: (((memory unsignedByteAt: index) bitAnd: 16rFB) + (aValue ifTrue: [4] ifFalse: [0]))].
  memory
  unsignedByteAt: index
  put: (((memory unsignedByteAt: index) bitAnd: 16rFB) + (aValue ifTrue: [4] ifFalse: [0])).
  ^aValue!

Item was changed:
  ----- Method: CogMethodSurrogate>>cmNumArgs: (in category 'accessing generated') -----
  cmNumArgs: aValue
 
  | index delta |
  index := address + baseHeaderSize + 1.
  (delta := cogit codeToDataDelta) > 0 ifTrue:
  [self assert: (cogit addressIsInCodeZone: address - delta).
  memory
+ unsignedByteAt: index - delta
- unsignedByteAt: index
  put: aValue].
  ^memory
  unsignedByteAt: index
  put: aValue!

Item was changed:
  ----- Method: CogMethodSurrogate>>cmRefersToYoung: (in category 'accessing generated') -----
  cmRefersToYoung: aValue
 
  | index delta |
  index := address + baseHeaderSize + 2.
  (delta := cogit codeToDataDelta) > 0 ifTrue:
  [self assert: (cogit addressIsInCodeZone: address - delta).
  memory
+ unsignedByteAt: index - delta
+ put: (((memory unsignedByteAt: index - delta) bitAnd: 16rF7) + (aValue ifTrue: [8] ifFalse: [0]))].
- unsignedByteAt: index
- put: (((memory unsignedByteAt: index) bitAnd: 16rF7) + (aValue ifTrue: [8] ifFalse: [0]))].
  memory
  unsignedByteAt: index
  put: (((memory unsignedByteAt: index) bitAnd: 16rF7) + (aValue ifTrue: [8] ifFalse: [0])).
  ^aValue!

Item was changed:
  ----- Method: CogMethodSurrogate>>cmType: (in category 'accessing generated') -----
  cmType: aValue
 
  | index delta |
  index := address + baseHeaderSize + 2.
  self assert: (aValue between: 0 and: 16r7).
  (delta := cogit codeToDataDelta) > 0 ifTrue:
  [self assert: (cogit addressIsInCodeZone: address - delta).
  memory
+ unsignedByteAt: index - delta
+ put: ((memory unsignedByteAt: index - delta) bitAnd: 16rF8) + aValue].
- unsignedByteAt: index
- put: ((memory unsignedByteAt: index) bitAnd: 16rF8) + aValue].
  memory
  unsignedByteAt: index
  put: ((memory unsignedByteAt: index) bitAnd: 16rF8) + aValue.
  ^aValue!

Item was changed:
  ----- Method: CogMethodSurrogate>>cmUsageCount: (in category 'accessing generated') -----
  cmUsageCount: aValue
 
  | index delta |
  index := address + baseHeaderSize + 2.
  self assert: (aValue between: 0 and: 16r7).
  (delta := cogit codeToDataDelta) > 0 ifTrue:
  [self assert: (cogit addressIsInCodeZone: address - delta).
  memory
+ unsignedByteAt: index - delta
+ put: ((memory unsignedByteAt: index - delta) bitAnd: 16r1F) + (aValue bitShift: 5)].
- unsignedByteAt: index
- put: ((memory unsignedByteAt: index) bitAnd: 16r1F) + (aValue bitShift: 5)].
  memory
  unsignedByteAt: index
  put: ((memory unsignedByteAt: index) bitAnd: 16r1F) + (aValue bitShift: 5).
  ^aValue!

Item was changed:
  ----- Method: CogMethodSurrogate>>cmUsesPenultimateLit: (in category 'accessing generated') -----
  cmUsesPenultimateLit: aValue
 
  | index delta |
  index := address + baseHeaderSize + 3.
  (delta := cogit codeToDataDelta) > 0 ifTrue:
  [self assert: (cogit addressIsInCodeZone: address - delta).
  memory
+ unsignedByteAt: index - delta
+ put: (((memory unsignedByteAt: index - delta) bitAnd: 16rFE) + (aValue ifTrue: [1] ifFalse: [0]))].
- unsignedByteAt: index
- put: (((memory unsignedByteAt: index) bitAnd: 16rFE) + (aValue ifTrue: [1] ifFalse: [0]))].
  memory
  unsignedByteAt: index
  put: (((memory unsignedByteAt: index) bitAnd: 16rFE) + (aValue ifTrue: [1] ifFalse: [0])).
  ^aValue!

Item was changed:
  ----- Method: CogMethodSurrogate>>cpicHasMNUCaseOrCMIsFullBlock: (in category 'accessing generated') -----
  cpicHasMNUCaseOrCMIsFullBlock: aValue
 
  | index delta |
  index := address + baseHeaderSize + 2.
  (delta := cogit codeToDataDelta) > 0 ifTrue:
  [self assert: (cogit addressIsInCodeZone: address - delta).
  memory
+ unsignedByteAt: index - delta
+ put: (((memory unsignedByteAt: index - delta) bitAnd: 16rEF) + (aValue ifTrue: [16] ifFalse: [0]))].
- unsignedByteAt: index
- put: (((memory unsignedByteAt: index) bitAnd: 16rEF) + (aValue ifTrue: [16] ifFalse: [0]))].
  memory
  unsignedByteAt: index
  put: (((memory unsignedByteAt: index) bitAnd: 16rEF) + (aValue ifTrue: [16] ifFalse: [0])).
  ^aValue!

Item was changed:
  ----- Method: CogMethodSurrogate>>homeOffset: (in category 'accessing generated') -----
  homeOffset: aValue
 
  | index delta |
  index := address + 1.
  (delta := cogit codeToDataDelta) > 0 ifTrue:
  [self assert: (cogit addressIsInCodeZone: address - delta).
  memory
+ unsignedShortAt: index - delta
- unsignedShortAt: index
  put: aValue].
  ^memory
  unsignedShortAt: index
  put: aValue!

Item was changed:
  ----- Method: CogMethodSurrogate>>objectHeader (in category 'accessing') -----
  objectHeader
+ "N.B. This *must* be signed.  We use it for relocation when compacting the code zone."
  ^baseHeaderSize = 8
  ifTrue: [memory long64At: address + 1]
  ifFalse: [memory longAt: address + 1]!

Item was changed:
  ----- Method: CogMethodSurrogate>>objectHeader: (in category 'accessing') -----
  objectHeader: aValue
  | delta |
  (delta := cogit codeToDataDelta) > 0 ifTrue:
  [self assert: (cogit addressIsInCodeZone: address - delta).
  baseHeaderSize = 8
+ ifTrue: [memory long64At: address - delta + 1 put: aValue]
+ ifFalse: [memory longAt: address - delta + 1 put: aValue]].
- ifTrue: [memory long64At: address + 1 put: aValue]
- ifFalse: [memory longAt: address + 1 put: aValue]].
  ^baseHeaderSize = 8
+ ifTrue: [memory long64At: address + 1 put: aValue]
+ ifFalse: [memory longAt: address + 1 put: aValue]!
- ifTrue: [memory long64At: address - delta + 1 put: aValue]
- ifFalse: [memory longAt: address - delta + 1 put: aValue]!

Item was changed:
  ----- Method: CogMethodSurrogate>>stackCheckOffset: (in category 'accessing generated') -----
  stackCheckOffset: aValue
 
  | index delta |
  index := address + baseHeaderSize + 3.
  self assert: (aValue between: 0 and: 16rFFF).
  (delta := cogit codeToDataDelta) > 0 ifTrue:
  [self assert: (cogit addressIsInCodeZone: address - delta).
  memory
+ unsignedShortAt: index - delta
+ put: ((memory unsignedShortAt: index - delta) bitAnd: 16rF) + (aValue bitShift: 4)].
- unsignedShortAt: index
- put: ((memory unsignedShortAt: index) bitAnd: 16rF) + (aValue bitShift: 4)].
  memory
  unsignedShortAt: index
  put: ((memory unsignedShortAt: index) bitAnd: 16rF) + (aValue bitShift: 4).
  ^aValue!

Item was changed:
  ----- Method: CogMethodSurrogate>>startpc: (in category 'accessing generated') -----
  startpc: aValue
 
  | index delta |
  index := address + 3.
  (delta := cogit codeToDataDelta) > 0 ifTrue:
  [self assert: (cogit addressIsInCodeZone: address - delta).
  memory
+ unsignedShortAt: index - delta
- unsignedShortAt: index
  put: aValue].
  ^memory
  unsignedShortAt: index
  put: aValue!

Item was added:
+ ----- Method: CogMethodSurrogate32>>blockEntryOffset (in category 'accessing generated') -----
+ blockEntryOffset
+ ^memory unsignedShortAt: address + 7 + baseHeaderSize!

Item was added:
+ ----- Method: CogMethodSurrogate32>>blockEntryOffset: (in category 'accessing generated') -----
+ blockEntryOffset: aValue
+
+ | index delta |
+ index := address + baseHeaderSize + 7.
+ (delta := cogit codeToDataDelta) > 0 ifTrue:
+ [self assert: (cogit addressIsInCodeZone: address - delta).
+ memory
+ unsignedShortAt: index - delta
+ put: aValue].
+ ^memory
+ unsignedShortAt: index
+ put: aValue!

Item was added:
+ ----- Method: CogMethodSurrogate32>>blockSize (in category 'accessing generated') -----
+ blockSize
+ ^memory unsignedShortAt: address + 5 + baseHeaderSize!

Item was added:
+ ----- Method: CogMethodSurrogate32>>blockSize: (in category 'accessing generated') -----
+ blockSize: aValue
+
+ | index delta |
+ index := address + baseHeaderSize + 5.
+ (delta := cogit codeToDataDelta) > 0 ifTrue:
+ [self assert: (cogit addressIsInCodeZone: address - delta).
+ memory
+ unsignedShortAt: index - delta
+ put: aValue].
+ ^memory
+ unsignedShortAt: index
+ put: aValue!

Item was changed:
  ----- Method: CogMethodSurrogate32>>methodHeader: (in category 'accessing generated') -----
  methodHeader: aValue
 
  | index delta |
  index := address + baseHeaderSize + 13.
  (delta := cogit codeToDataDelta) > 0 ifTrue:
  [self assert: (cogit addressIsInCodeZone: address - delta).
  memory
+ unsignedLongAt: index - delta
- unsignedLongAt: index
  put: aValue].
  ^memory
  unsignedLongAt: index
  put: aValue!

Item was changed:
  ----- Method: CogMethodSurrogate32>>methodObject: (in category 'accessing generated') -----
  methodObject: aValue
 
  | index delta |
  index := address + baseHeaderSize + 9.
  (delta := cogit codeToDataDelta) > 0 ifTrue:
  [self assert: (cogit addressIsInCodeZone: address - delta).
  memory
+ unsignedLongAt: index - delta
- unsignedLongAt: index
  put: aValue].
  ^memory
  unsignedLongAt: index
  put: aValue!

Item was changed:
  ----- Method: CogMethodSurrogate32>>selector: (in category 'accessing generated') -----
  selector: aValue
 
  | index delta |
  index := address + baseHeaderSize + 17.
  (delta := cogit codeToDataDelta) > 0 ifTrue:
  [self assert: (cogit addressIsInCodeZone: address - delta).
  memory
+ unsignedLongAt: index - delta
- unsignedLongAt: index
  put: aValue].
  ^memory
  unsignedLongAt: index
  put: aValue!

Item was changed:
  ----- Method: CogMethodSurrogate64>>blockEntryOffset: (in category 'accessing generated') -----
  blockEntryOffset: aValue
 
  | index delta |
  index := address + baseHeaderSize + 7.
  (delta := cogit codeToDataDelta) > 0 ifTrue:
  [self assert: (cogit addressIsInCodeZone: address - delta).
  memory
+ unsignedShortAt: index - delta
- unsignedShortAt: index
  put: aValue].
  ^memory
  unsignedShortAt: index
  put: aValue!

Item was changed:
  ----- Method: CogMethodSurrogate64>>blockSize: (in category 'accessing generated') -----
  blockSize: aValue
 
  | index delta |
  index := address + baseHeaderSize + 5.
  (delta := cogit codeToDataDelta) > 0 ifTrue:
  [self assert: (cogit addressIsInCodeZone: address - delta).
  memory
+ unsignedShortAt: index - delta
- unsignedShortAt: index
  put: aValue].
  ^memory
  unsignedShortAt: index
  put: aValue!

Item was changed:
  ----- Method: CogMethodSurrogate64>>methodHeader: (in category 'accessing generated') -----
  methodHeader: aValue
 
  | index delta |
  index := address + baseHeaderSize + 17.
  (delta := cogit codeToDataDelta) > 0 ifTrue:
  [self assert: (cogit addressIsInCodeZone: address - delta).
  memory
+ unsignedLong64At: index - delta
- unsignedLong64At: index
  put: aValue].
  ^memory
  unsignedLong64At: index
  put: aValue!

Item was changed:
  ----- Method: CogMethodSurrogate64>>methodObject: (in category 'accessing generated') -----
  methodObject: aValue
 
  | index delta |
  index := address + baseHeaderSize + 9.
  (delta := cogit codeToDataDelta) > 0 ifTrue:
  [self assert: (cogit addressIsInCodeZone: address - delta).
  memory
+ unsignedLong64At: index - delta
- unsignedLong64At: index
  put: aValue].
  ^memory
  unsignedLong64At: index
  put: aValue!

Item was changed:
  ----- Method: CogMethodSurrogate64>>selector: (in category 'accessing generated') -----
  selector: aValue
 
  | index delta |
  index := address + baseHeaderSize + 25.
  (delta := cogit codeToDataDelta) > 0 ifTrue:
  [self assert: (cogit addressIsInCodeZone: address - delta).
  memory
+ unsignedLong64At: index - delta
- unsignedLong64At: index
  put: aValue].
  ^memory
  unsignedLong64At: index
  put: aValue!

Item was changed:
  ----- Method: CogMethodZone>>addToUnpairedMethodList: (in category 'accessing') -----
  addToUnpairedMethodList: aCogMethod
  <option: #NewspeakVM>
  <var: #aCogMethod type: #'CogMethod *'>
  self assert: aCogMethod cmType = CMMethod.
  self assert: (cogit noAssertMethodClassAssociationOf: aCogMethod methodObject) = objectMemory nilObject.
  self assert: (unpairedMethodList == nil
  or: [(self cCoerceSimple: unpairedMethodList to: #'CogMethod *') cmType = CMMethod]).
+ cogit assertValidDualZoneWriteAddress: aCogMethod.
  aCogMethod nextMethodOrIRCs: unpairedMethodList.
  unpairedMethodList := aCogMethod asUnsignedInteger - cogit codeToDataDelta!

Item was changed:
  ----- Method: CogMethodZone>>addToYoungReferrers: (in category 'young referers') -----
  addToYoungReferrers: cogMethod
  <var: #cogMethod type: #'CogMethod *'>
  self cCode: '' inSmalltalk: [cogit assertValidDualZoneWriteAddress: cogMethod asInteger].
  self assert: youngReferrers <= limitAddress.
  self assert: (self occurrencesInYoungReferrers: cogMethod) = 0.
  self assert: cogMethod cmRefersToYoung.
  self assert: (youngReferrers <= limitAddress
  and: [youngReferrers >= (limitAddress - (methodCount * objectMemory wordSize))]).
  (self asserta: limitAddress - (methodCount * objectMemory wordSize) >= mzFreeStart) ifFalse:
  [self error: 'no room on youngReferrers list'].
+ cogit assertValidDualZoneWriteAddress: cogMethod.
  youngReferrers := youngReferrers - objectMemory wordSize.
  cogit
  codeLongAt: youngReferrers + cogit codeToDataDelta
  put: cogMethod asUnsignedInteger - cogit codeToDataDelta!

Item was changed:
  ----- Method: CogMethodZone>>ensureInYoungReferrers: (in category 'young referers') -----
  ensureInYoungReferrers: cogMethod
  <var: #cogMethod type: #'CogMethod *'>
- | writableMethod |
  cogit assertValidDualZoneReadAddress: cogMethod.
  cogMethod cmRefersToYoung ifFalse:
  [self assert: (self occurrencesInYoungReferrers: cogMethod) = 0.
+ (cogit writableMethodFor: cogMethod) cmRefersToYoung: true.
- writableMethod := cogit cCoerceSimple: cogMethod asUnsignedInteger - cogit codeToDataDelta
- to: #'CogMethod *'.
- writableMethod cmRefersToYoung: true.
  self addToYoungReferrers: cogMethod]!

Item was changed:
  ----- Method: CogSistaMethodSurrogate32>>counters: (in category 'accessing generated') -----
  counters: aValue
 
  | index delta |
  index := address + baseHeaderSize + 21.
  (delta := cogit codeToDataDelta) > 0 ifTrue:
  [self assert: (cogit addressIsInCodeZone: address - delta).
  memory
+ unsignedLongAt: index - delta
- unsignedLongAt: index
  put: aValue].
  ^memory
  unsignedLongAt: index
  put: aValue!

Item was changed:
  ----- Method: CogSistaMethodSurrogate64>>counters: (in category 'accessing generated') -----
  counters: aValue
 
  | index delta |
  index := address + baseHeaderSize + 33.
  (delta := cogit codeToDataDelta) > 0 ifTrue:
  [self assert: (cogit addressIsInCodeZone: address - delta).
  memory
+ unsignedLong64At: index - delta
- unsignedLong64At: index
  put: aValue].
  ^memory
  unsignedLong64At: index
  put: aValue!

Item was changed:
+ ----- Method: CogStackPageSurrogate32>>baseAddress (in category 'accessing generated') -----
- ----- Method: CogStackPageSurrogate32>>baseAddress (in category 'accessing') -----
  baseAddress
  ^memory unsignedLongAt: address + 17!

Item was changed:
+ ----- Method: CogStackPageSurrogate32>>baseAddress: (in category 'accessing generated') -----
- ----- Method: CogStackPageSurrogate32>>baseAddress: (in category 'accessing') -----
  baseAddress: aValue
  self assert: (address + 16 >= zoneBase and: [address + 19 < zoneLimit]).
  ^memory unsignedLongAt: address + 17 put: aValue!

Item was changed:
+ ----- Method: CogStackPageSurrogate32>>baseFP (in category 'accessing generated') -----
- ----- Method: CogStackPageSurrogate32>>baseFP (in category 'accessing') -----
  baseFP
  ^memory unsignedLongAt: address + 13!

Item was changed:
+ ----- Method: CogStackPageSurrogate32>>baseFP: (in category 'accessing generated') -----
- ----- Method: CogStackPageSurrogate32>>baseFP: (in category 'accessing') -----
  baseFP: aValue
  self assert: (address + 12 >= zoneBase and: [address + 15 < zoneLimit]).
  ^memory unsignedLongAt: address + 13 put: aValue!

Item was changed:
+ ----- Method: CogStackPageSurrogate32>>headFP (in category 'accessing generated') -----
- ----- Method: CogStackPageSurrogate32>>headFP (in category 'accessing') -----
  headFP
  ^memory unsignedLongAt: address + 9!

Item was changed:
+ ----- Method: CogStackPageSurrogate32>>headFP: (in category 'accessing generated') -----
- ----- Method: CogStackPageSurrogate32>>headFP: (in category 'accessing') -----
  headFP: aValue
  self assert: (address + 8 >= zoneBase and: [address + 11 < zoneLimit]).
  ^memory unsignedLongAt: address + 9 put: aValue!

Item was changed:
+ ----- Method: CogStackPageSurrogate32>>headSP (in category 'accessing generated') -----
- ----- Method: CogStackPageSurrogate32>>headSP (in category 'accessing') -----
  headSP
  ^memory unsignedLongAt: address + 5!

Item was changed:
+ ----- Method: CogStackPageSurrogate32>>headSP: (in category 'accessing generated') -----
- ----- Method: CogStackPageSurrogate32>>headSP: (in category 'accessing') -----
  headSP: aValue
  self assert: (address + 4 >= zoneBase and: [address + 7 < zoneLimit]).
  ^memory unsignedLongAt: address + 5 put: aValue!

Item was changed:
+ ----- Method: CogStackPageSurrogate32>>lastAddress (in category 'accessing generated') -----
- ----- Method: CogStackPageSurrogate32>>lastAddress (in category 'accessing') -----
  lastAddress
  ^memory unsignedLongAt: address + 25!

Item was changed:
+ ----- Method: CogStackPageSurrogate32>>lastAddress: (in category 'accessing generated') -----
- ----- Method: CogStackPageSurrogate32>>lastAddress: (in category 'accessing') -----
  lastAddress: aValue
  self assert: (address + 24 >= zoneBase and: [address + 27 < zoneLimit]).
  ^memory unsignedLongAt: address + 25 put: aValue!

Item was changed:
+ ----- Method: CogStackPageSurrogate32>>nextPage (in category 'accessing generated') -----
- ----- Method: CogStackPageSurrogate32>>nextPage (in category 'accessing') -----
  nextPage
  ^stackPages surrogateAtAddress: (memory unsignedLongAt: address + 33)!

Item was changed:
+ ----- Method: CogStackPageSurrogate32>>nextPage: (in category 'accessing generated') -----
- ----- Method: CogStackPageSurrogate32>>nextPage: (in category 'accessing') -----
  nextPage: aValue
  self assert: (address + 32 >= zoneBase and: [address + 35 < zoneLimit]).
  memory unsignedLongAt: address + 33 put: aValue asInteger.
  ^aValue!

Item was changed:
+ ----- Method: CogStackPageSurrogate32>>padToWord (in category 'accessing generated') -----
- ----- Method: CogStackPageSurrogate32>>padToWord (in category 'accessing') -----
  padToWord
  ^memory longAt: address + 33!

Item was changed:
+ ----- Method: CogStackPageSurrogate32>>padToWord: (in category 'accessing generated') -----
- ----- Method: CogStackPageSurrogate32>>padToWord: (in category 'accessing') -----
  padToWord: aValue
  self assert: (address + 32 >= zoneBase and: [address + 35 < zoneLimit]).
  ^memory longAt: address + 33 put: aValue!

Item was changed:
+ ----- Method: CogStackPageSurrogate32>>prevPage (in category 'accessing generated') -----
- ----- Method: CogStackPageSurrogate32>>prevPage (in category 'accessing') -----
  prevPage
  ^stackPages surrogateAtAddress: (memory unsignedLongAt: address + 37)!

Item was changed:
+ ----- Method: CogStackPageSurrogate32>>prevPage: (in category 'accessing generated') -----
- ----- Method: CogStackPageSurrogate32>>prevPage: (in category 'accessing') -----
  prevPage: aValue
  self assert: (address + 36 >= zoneBase and: [address + 39 < zoneLimit]).
  memory unsignedLongAt: address + 37 put: aValue asInteger.
  ^aValue!

Item was changed:
+ ----- Method: CogStackPageSurrogate32>>realStackLimit (in category 'accessing generated') -----
- ----- Method: CogStackPageSurrogate32>>realStackLimit (in category 'accessing') -----
  realStackLimit
  ^memory unsignedLongAt: address + 21!

Item was changed:
+ ----- Method: CogStackPageSurrogate32>>realStackLimit: (in category 'accessing generated') -----
- ----- Method: CogStackPageSurrogate32>>realStackLimit: (in category 'accessing') -----
  realStackLimit: aValue
  self assert: (address + 20 >= zoneBase and: [address + 23 < zoneLimit]).
  ^memory unsignedLongAt: address + 21 put: aValue!

Item was changed:
+ ----- Method: CogStackPageSurrogate32>>stackLimit (in category 'accessing generated') -----
- ----- Method: CogStackPageSurrogate32>>stackLimit (in category 'accessing') -----
  stackLimit
  ^memory unsignedLongAt: address + 1!

Item was changed:
+ ----- Method: CogStackPageSurrogate32>>stackLimit: (in category 'accessing generated') -----
- ----- Method: CogStackPageSurrogate32>>stackLimit: (in category 'accessing') -----
  stackLimit: aValue
  self assert: (address + 0 >= zoneBase and: [address + 3 < zoneLimit]).
  ^memory unsignedLongAt: address + 1 put: aValue!

Item was changed:
+ ----- Method: CogStackPageSurrogate32>>trace (in category 'accessing generated') -----
- ----- Method: CogStackPageSurrogate32>>trace (in category 'accessing') -----
  trace
  ^memory longAt: address + 29!

Item was changed:
+ ----- Method: CogStackPageSurrogate32>>trace: (in category 'accessing generated') -----
- ----- Method: CogStackPageSurrogate32>>trace: (in category 'accessing') -----
  trace: aValue
  self assert: (address + 28 >= zoneBase and: [address + 31 < zoneLimit]).
  ^memory longAt: address + 29 put: aValue!

Item was changed:
+ ----- Method: CogStackPageSurrogate64>>baseAddress (in category 'accessing generated') -----
- ----- Method: CogStackPageSurrogate64>>baseAddress (in category 'accessing') -----
  baseAddress
  ^memory unsignedLong64At: address + 33!

Item was changed:
+ ----- Method: CogStackPageSurrogate64>>baseAddress: (in category 'accessing generated') -----
- ----- Method: CogStackPageSurrogate64>>baseAddress: (in category 'accessing') -----
  baseAddress: aValue
  self assert: (address + 32 >= zoneBase and: [address + 39 < zoneLimit]).
  ^memory unsignedLong64At: address + 33 put: aValue!

Item was changed:
+ ----- Method: CogStackPageSurrogate64>>baseFP (in category 'accessing generated') -----
- ----- Method: CogStackPageSurrogate64>>baseFP (in category 'accessing') -----
  baseFP
  ^memory unsignedLong64At: address + 25!

Item was changed:
+ ----- Method: CogStackPageSurrogate64>>baseFP: (in category 'accessing generated') -----
- ----- Method: CogStackPageSurrogate64>>baseFP: (in category 'accessing') -----
  baseFP: aValue
  self assert: (address + 24 >= zoneBase and: [address + 31 < zoneLimit]).
  ^memory unsignedLong64At: address + 25 put: aValue!

Item was changed:
+ ----- Method: CogStackPageSurrogate64>>headFP (in category 'accessing generated') -----
- ----- Method: CogStackPageSurrogate64>>headFP (in category 'accessing') -----
  headFP
  ^memory unsignedLong64At: address + 17!

Item was changed:
+ ----- Method: CogStackPageSurrogate64>>headFP: (in category 'accessing generated') -----
- ----- Method: CogStackPageSurrogate64>>headFP: (in category 'accessing') -----
  headFP: aValue
  self assert: (address + 16 >= zoneBase and: [address + 23 < zoneLimit]).
  ^memory unsignedLong64At: address + 17 put: aValue!

Item was changed:
+ ----- Method: CogStackPageSurrogate64>>headSP (in category 'accessing generated') -----
- ----- Method: CogStackPageSurrogate64>>headSP (in category 'accessing') -----
  headSP
  ^memory unsignedLong64At: address + 9!

Item was changed:
+ ----- Method: CogStackPageSurrogate64>>headSP: (in category 'accessing generated') -----
- ----- Method: CogStackPageSurrogate64>>headSP: (in category 'accessing') -----
  headSP: aValue
  self assert: (address + 8 >= zoneBase and: [address + 15 < zoneLimit]).
  ^memory unsignedLong64At: address + 9 put: aValue!

Item was changed:
+ ----- Method: CogStackPageSurrogate64>>lastAddress (in category 'accessing generated') -----
- ----- Method: CogStackPageSurrogate64>>lastAddress (in category 'accessing') -----
  lastAddress
  ^memory unsignedLong64At: address + 49!

Item was changed:
+ ----- Method: CogStackPageSurrogate64>>lastAddress: (in category 'accessing generated') -----
- ----- Method: CogStackPageSurrogate64>>lastAddress: (in category 'accessing') -----
  lastAddress: aValue
  self assert: (address + 48 >= zoneBase and: [address + 55 < zoneLimit]).
  ^memory unsignedLong64At: address + 49 put: aValue!

Item was changed:
+ ----- Method: CogStackPageSurrogate64>>nextPage (in category 'accessing generated') -----
- ----- Method: CogStackPageSurrogate64>>nextPage (in category 'accessing') -----
  nextPage
  ^stackPages surrogateAtAddress: (memory unsignedLong64At: address + 65)!

Item was changed:
+ ----- Method: CogStackPageSurrogate64>>nextPage: (in category 'accessing generated') -----
- ----- Method: CogStackPageSurrogate64>>nextPage: (in category 'accessing') -----
  nextPage: aValue
  self assert: (address + 64 >= zoneBase and: [address + 71 < zoneLimit]).
  memory unsignedLong64At: address + 65 put: aValue asInteger.
  ^aValue!

Item was changed:
+ ----- Method: CogStackPageSurrogate64>>padToWord (in category 'accessing generated') -----
- ----- Method: CogStackPageSurrogate64>>padToWord (in category 'accessing') -----
  padToWord
  ^memory longAt: address + 61!

Item was changed:
+ ----- Method: CogStackPageSurrogate64>>padToWord: (in category 'accessing generated') -----
- ----- Method: CogStackPageSurrogate64>>padToWord: (in category 'accessing') -----
  padToWord: aValue
  self assert: (address + 60 >= zoneBase and: [address + 63 < zoneLimit]).
  ^memory longAt: address + 61 put: aValue!

Item was changed:
+ ----- Method: CogStackPageSurrogate64>>prevPage (in category 'accessing generated') -----
- ----- Method: CogStackPageSurrogate64>>prevPage (in category 'accessing') -----
  prevPage
  ^stackPages surrogateAtAddress: (memory unsignedLong64At: address + 73)!

Item was changed:
+ ----- Method: CogStackPageSurrogate64>>prevPage: (in category 'accessing generated') -----
- ----- Method: CogStackPageSurrogate64>>prevPage: (in category 'accessing') -----
  prevPage: aValue
  self assert: (address + 72 >= zoneBase and: [address + 79 < zoneLimit]).
  memory unsignedLong64At: address + 73 put: aValue asInteger.
  ^aValue!

Item was changed:
+ ----- Method: CogStackPageSurrogate64>>realStackLimit (in category 'accessing generated') -----
- ----- Method: CogStackPageSurrogate64>>realStackLimit (in category 'accessing') -----
  realStackLimit
  ^memory unsignedLong64At: address + 41!

Item was changed:
+ ----- Method: CogStackPageSurrogate64>>realStackLimit: (in category 'accessing generated') -----
- ----- Method: CogStackPageSurrogate64>>realStackLimit: (in category 'accessing') -----
  realStackLimit: aValue
  self assert: (address + 40 >= zoneBase and: [address + 47 < zoneLimit]).
  ^memory unsignedLong64At: address + 41 put: aValue!

Item was changed:
+ ----- Method: CogStackPageSurrogate64>>stackLimit (in category 'accessing generated') -----
- ----- Method: CogStackPageSurrogate64>>stackLimit (in category 'accessing') -----
  stackLimit
  ^memory unsignedLong64At: address + 1!

Item was changed:
+ ----- Method: CogStackPageSurrogate64>>stackLimit: (in category 'accessing generated') -----
- ----- Method: CogStackPageSurrogate64>>stackLimit: (in category 'accessing') -----
  stackLimit: aValue
  self assert: (address + 0 >= zoneBase and: [address + 7 < zoneLimit]).
  ^memory unsignedLong64At: address + 1 put: aValue!

Item was changed:
+ ----- Method: CogStackPageSurrogate64>>trace (in category 'accessing generated') -----
- ----- Method: CogStackPageSurrogate64>>trace (in category 'accessing') -----
  trace
  ^memory longAt: address + 57!

Item was changed:
+ ----- Method: CogStackPageSurrogate64>>trace: (in category 'accessing generated') -----
- ----- Method: CogStackPageSurrogate64>>trace: (in category 'accessing') -----
  trace: aValue
  self assert: (address + 56 >= zoneBase and: [address + 59 < zoneLimit]).
  ^memory longAt: address + 57 put: aValue!

Item was changed:
  ----- Method: CogVMSimulator>>initialize (in category 'initialization') -----
  initialize
  "Initialize the CogVMSimulator when running the interpreter inside Smalltalk.  The
  primary responsibility of this method is to allocate Smalltalk Arrays for variables
  that will be declared as statically-allocated global arrays in the translated code."
  super initialize.
 
  transcript := Transcript.
 
  objectMemory ifNil:
  [objectMemory := self class objectMemoryClass simulatorClass new].
  cogit ifNil:
  [cogit := self class cogitClass new setInterpreter: self].
  objectMemory coInterpreter: self cogit: cogit.
 
  (cogit numRegArgs > 0
  and: [VMClass initializationOptions at: #CheckStackDepth ifAbsent: [true]]) ifTrue:
  [debugStackDepthDictionary := Dictionary new].
 
  cogThreadManager ifNotNil:
  [super initialize].
 
  self assert: ConstMinusOne = (objectMemory integerObjectOf: -1).
 
  cogMethodZone := cogit methodZone. "Because Slang can't remove intermediate implicit receivers (cogit methodZone foo doesn't reduce to foo())"
  enableCog := true.
 
  methodCache := Array new: MethodCacheSize.
  nsMethodCache := Array new: NSMethodCacheSize.
  atCache := nil.
  self flushMethodCache.
  cogCompiledCodeCompactionCalledFor := false.
  gcSemaphoreIndex := 0.
  externalSemaphoreSignalRequests := externalSemaphoreSignalResponses := #().
  externalPrimitiveTable := CArrayAccessor on: (Array new: MaxExternalPrimitiveTableSize).
  externalPrimitiveTableFirstFreeIndex := 0.
  primitiveTable := self class primitiveTable copy.
  self initializePluginEntries.
+ desiredNumStackPages := InitializationOptions at: #desiredNumStackPages ifAbsent: [0].
+ desiredEdenBytes := InitializationOptions at: #desiredEdenBytes ifAbsent: [0].
+ desiredCogCodeSize  := InitializationOptions at: #desiredCogCodeSize ifAbsent: [0].
- desiredNumStackPages := desiredEdenBytes := desiredCogCodeSize := 0.
  "This is initialized on loading the image, but convenient for testing stack page values..."
  numStackPages := self defaultNumStackPages.
  startMicroseconds := lastYieldMicroseconds := self ioUTCStartMicroseconds.
  maxLiteralCountForCompile := MaxLiteralCountForCompile.
  minBackwardJumpCountForCompile := MinBackwardJumpCountForCompile.
  flagInterpretedMethods := false.
 
  "initialize InterpreterSimulator variables used for debugging"
  byteCount := lastPollCount := sendCount := lookupCount := 0.
  quitBlock := [^self close].
  traceOn := true.
  printSends := printFrameAtEachStep := printBytecodeAtEachStep := false.
  myBitBlt := BitBltSimulator new setInterpreter: self.
  displayForm := fakeForm := 'Display has not yet been installed' asDisplayText form.
  eventQueue := SharedQueue new.
  suppressHeartbeatFlag := deferSmash := deferredSmash := false.
  systemAttributes := Dictionary new.
  primTraceLog := CArrayAccessor on: (Array new: 256 withAll: 0).
  primTraceLogIndex := 0.
  traceLog := CArrayAccessor on: (Array new: TraceBufferSize withAll: 0).
  traceLogIndex := 0.
  traceSources := TraceSources.
  statCodeCompactionCount := 0.
  statCodeCompactionUsecs := 0.
  extSemTabSize := 256!

Item was changed:
  CogClass subclass: #Cogit
  instanceVariableNames: 'coInterpreter objectMemory objectRepresentation processor threadManager methodZone methodZoneBase codeBase minValidCallAddress lastNInstructions simulatedAddresses simulatedTrampolines simulatedVariableGetters simulatedVariableSetters printRegisters printInstructions compilationTrace clickConfirm breakPC breakBlock singleStep guardPageSize traceFlags traceStores breakMethod methodObj enumeratingCogMethod methodHeader initialPC endPC methodOrBlockNumArgs inBlock needsFrame hasYoungReferent hasMovableLiteral primitiveIndex backEnd literalsManager postCompileHook methodLabel stackCheckLabel blockEntryLabel blockEntryNoContextSwitch blockNoContextSwitchOffset stackOverflowCall sendMiss missOffset entryPointMask checkedEntryAlignment uncheckedEntryAlignment cmEntryOffset entry cmNoCheckEntryOffset noCheckEntry fullBlockEntry cbEntryOffset fullBlockNoContextSwitchEntry cbNoSwitchEntryOffset picMNUAbort picInterpretAbort endCPICCase0 endCPICCase1 firstCPICCaseOffs
 et cPICCaseSize cPICEndSize closedPICSize openPICSize fixups abstractOpcodes generatorTable byte0 byte1 byte2 byte3 bytecodePC bytecodeSetOffset opcodeIndex numAbstractOpcodes blockStarts blockCount labelCounter cStackAlignment expectedSPAlignment expectedFPAlignment codeModified maxLitIndex ceMethodAbortTrampoline cePICAbortTrampoline ceCheckForInterruptTrampoline ceCPICMissTrampoline ceReturnToInterpreterTrampoline ceBaseFrameReturnTrampoline ceReapAndResetErrorCodeTrampoline ceSendMustBeBooleanAddTrueTrampoline ceSendMustBeBooleanAddFalseTrampoline ceCannotResumeTrampoline ceEnterCogCodePopReceiverReg ceCallCogCodePopReceiverReg ceCallCogCodePopReceiverAndClassRegs cePrimReturnEnterCogCode cePrimReturnEnterCogCodeProfiling ceNonLocalReturnTrampoline ceFetchContextInstVarTrampoline ceStoreContextInstVarTrampoline ceEnclosingObjectTrampoline ceFlushICache ceCheckFeaturesFunction ceTraceLinkedSendTrampoline ceTraceBlockActivationTrampoline ceTraceStoreTrampoline ceGetFP ceGetSP ceCa
 ptureCStackPointers ordinarySendTrampolines superSendTrampolines directedSuperSendTrampolines directedSuperBindingSendTrampolines dynamicSuperSendTrampolines outerSendTrampolines selfSendTrampolines firstSend lastSend realCEEnterCogCodePopReceiverReg realCECallCogCodePopReceiverReg realCECallCogCodePopReceiverAndClassRegs trampolineTableIndex trampolineAddresses objectReferencesInRuntime runtimeObjectRefIndex cFramePointerInUse debugPrimCallStackOffset ceTryLockVMOwner ceUnlockVMOwner extA extB numExtB tempOop numIRCs indexOfIRC theIRCs receiverTags implicitReceiverSendTrampolines cogMethodSurrogateClass cogBlockMethodSurrogateClass nsSendCacheSurrogateClass cPICPrototype cPICEndOfCodeOffset cPICEndOfCodeLabel ceMallocTrampoline ceFreeTrampoline ceFFICalloutTrampoline debugBytecodePointers debugOpcodeIndices disassemblingMethod cogConstituentIndex directedSendUsesBinding ceCheckLZCNTFunction processorFrameValid codeToDataDelta'
  classVariableNames: 'AltBlockCreationBytecodeSize AltFirstSpecialSelector AltNSSendIsPCAnnotated AltNumSpecialSelectors AnnotationConstantNames AnnotationShift AnnotationsWithBytecodePCs BlockCreationBytecodeSize Debug DisplacementMask DisplacementX2N EagerInstructionDecoration FirstAnnotation FirstSpecialSelector HasBytecodePC IsAbsPCReference IsAnnotationExtension IsDirectedSuperBindingSend IsDirectedSuperSend IsDisplacementX2N IsNSDynamicSuperSend IsNSImplicitReceiverSend IsNSSelfSend IsNSSendCall IsObjectReference IsRelativeCall IsSendCall IsSuperSend MapEnd MaxCPICCases MaxCompiledPrimitiveIndex MaxStackAllocSize MaxX2NDisplacement NSCClassTagIndex NSCEnclosingObjectIndex NSCNumArgsIndex NSCSelectorIndex NSCTargetIndex NSSendIsPCAnnotated NumObjRefsInRuntime NumOopsPerNSC NumSpecialSelectors NumTrampolines ProcessorClass RRRName'
  poolDictionaries: 'CogAbstractRegisters CogCompilationConstants CogMethodConstants CogRTLOpcodes VMBasicConstants VMBytecodeConstants VMObjectIndices VMStackFrameOffsets'
  category: 'VMMaker-JIT'!
  Cogit class
  instanceVariableNames: 'generatorTable primitiveTable'!
 
+ !Cogit commentStamp: 'eem 1/28/2020 17:27' prior: 0!
- !Cogit commentStamp: 'eem 10/10/2019 09:40' prior: 0!
  I am the code generator for the Cog VM.  My job is to produce machine code versions of methods for faster execution and to manage inline caches for faster send performance.  I can be tested in the current image using my class-side in-image compilation facilities.  e.g. try
 
  StackToRegisterMappingCogit genAndDis: (Integer >> #benchFib)
 
  I have concrete subclasses that implement different levels of optimization:
  SimpleStackBasedCogit is the simplest code generator.
 
  StackToRegisterMappingCogit is the current production code generator  It defers pushing operands
  to the stack until necessary and implements a register-based calling convention for low-arity sends.
 
  SistaCogit is an experimental code generator with support for counting
  conditional branches, intended to support adaptive optimization.
 
  RegisterAllocatingCogit is an experimental code generator with support for allocating temporary variables
  to registers. It is inended to serve as the superclass to SistaCogit once it is working.
 
  SistaRegisterAllocatingCogit and SistaCogitClone are temporary classes that allow testing a clone of
  SistaCogit that inherits from RegisterAllocatingCogit.  Once things work these will be merged and
  will replace SistaCogit.
 
  coInterpreter <CoInterpreterSimulator>
  the VM's interpreter with which I cooperate
  methodZoneManager <CogMethodZoneManager>
  the manager of the machine code zone
  objectRepresentation <CogObjectRepresentation>
  the object used to generate object accesses
  processor <BochsIA32Alien|?>
  the simulator that executes the IA32/x86 machine code I generate when simulating execution in Smalltalk
  simulatedTrampolines <Dictionary of Integer -> MessageSend>
  the dictionary mapping trap jump addresses to run-time routines used to warp from simulated machine code in to the Smalltalk run-time.
  simulatedVariableGetters <Dictionary of Integer -> MessageSend>
  the dictionary mapping trap read addresses to variables in run-time objects used to allow simulated machine code to read variables in the Smalltalk run-time.
  simulatedVariableSetters <Dictionary of Integer -> MessageSend>
  the dictionary mapping trap write addresses to variables in run-time objects used to allow simulated machine code to write variables in the Smalltalk run-time.
  printRegisters printInstructions clickConfirm <Boolean>
  flags controlling debug printing and code simulation
+ codeToDataDelta <Integer>
+ if non-zero this is the delta between the read/execute method zone and the read/write mapping of the method zone.  On operating systems where it is entirely disallowed to execute code in a writable region this split is necessary to be able to modify code.  In this regime all writes are to the read/write mapped zone.
+ breakPC <Integer|UndefinedObject|Boolean|Array>
- breakPC <Integer>
  machine code pc breakpoint
  selectorOop <sqInt>
  the oop of the methodObj being compiled
  methodObj <sqInt>
  the bytecode method being compiled
  initialPC endPC <Integer>
  the start and end pcs of the methodObj being compiled
  methodOrBlockNumArgs <Integer>
  argument count of current method or block being compiled
  needsFrame <Boolean>
  whether methodObj or block needs a frame to execute
  primitiveIndex <Integer>
  primitive index of current method being compiled
  methodLabel <CogAbstractOpcode>
  label for the method header
  blockEntryLabel <CogAbstractOpcode>
  label for the start of the block dispatch code
  stackOverflowCall <CogAbstractOpcode>
  label for the call of ceStackOverflow in the method prolog
  sendMissCall <CogAbstractOpcode>
  label for the call of ceSICMiss in the method prolog
  entryOffset <Integer>
  offset of method entry code from start (header) of method
  entry <CogAbstractOpcode>
  label for the first instruction of the method entry code
  noCheckEntryOffset <Integer>
  offset of the start of a method proper (after the method entry code) from start (header) of method
  noCheckEntry <CogAbstractOpcode>
  label for the first instruction of start of a method proper
  fixups <Array of <AbstractOpcode Label | nil>>
  the labels for forward jumps that will be fixed up when reaching the relevant bytecode.  fixups has one element per byte in methodObj's bytecode; initialPC maps to fixups[0].
  abstractOpcodes <Array of <AbstractOpcode>>
  the code generated when compiling methodObj
  byte0 byte1 byte2 byte3 <Integer>
  individual bytes of current bytecode being compiled in methodObj
  bytecodePointer <Integer>
  bytecode pc (same as Smalltalk) of the current bytecode being compiled
  opcodeIndex <Integer>
  the index of the next free entry in abstractOpcodes (this code is translated into C where OrderedCollection et al do not exist)
  numAbstractOpcodes <Integer>
  the number of elements in abstractOpcocdes
  blockStarts <Array of <BlockStart>>
  the starts of blocks in the current method
  blockCount
  the index into blockStarts as they are being noted, and hence eventually the total number of blocks in the current method
  labelCounter <Integer>
  a nicety for numbering labels not needed in the production system but probably not expensive enough to worry about
  ceStackOverflowTrampoline <Integer>
  ceSend0ArgsTrampoline <Integer>
  ceSend1ArgsTrampoline <Integer>
  ceSend2ArgsTrampoline <Integer>
  ceSendNArgsTrampoline <Integer>
  ceSendSuper0ArgsTrampoline <Integer>
  ceSendSuper1ArgsTrampoline <Integer>
  ceSendSuper2ArgsTrampoline <Integer>
  ceSendSuperNArgsTrampoline <Integer>
  ceSICMissTrampoline <Integer>
  ceCPICMissTrampoline <Integer>
  ceStoreCheckTrampoline <Integer>
  ceReturnToInterpreterTrampoline <Integer>
  ceBaseFrameReturnTrampoline <Integer>
  ceSendMustBeBooleanTrampoline <Integer>
  ceClosureCopyTrampoline <Integer>
  the various trampolines (system-call-like jumps from machine code to the run-time).
  See Cogit>>generateTrampolines for the mapping from trampoline to run-time
  routine and then read the run-time routine for a funcitonal description.
  ceEnterCogCodePopReceiverReg <Integer>
  the enilopmart (jump from run-time to machine-code)
  methodZoneBase <Integer>
  !
  Cogit class
  instanceVariableNames: 'generatorTable primitiveTable'!

Item was changed:
  ----- Method: Cogit>>cPICCompactAndIsNowEmpty: (in category 'in-line cacheing') -----
  cPICCompactAndIsNowEmpty: cPIC
  "Scan the CPIC for target methods that have been freed and eliminate them.
  Since the first entry cannot be eliminated, answer that the PIC should be
  freed if the first entry is to a free target.  Answer if the PIC is now empty or should be freed."
  <var: #cPIC type: #'CogMethod *'>
+ | pc entryPoint targetMethod targets tags methods used |
- | pc entryPoint targetMethod targets tags methods used writablePIC |
  <var: #targetMethod type: #'CogMethod *'>
  <var: #tags declareC: 'int tags[MaxCPICCases]'>
  <var: #targets declareC: 'sqInt targets[MaxCPICCases]'>
  <var: #methods declareC: 'sqInt methods[MaxCPICCases]'>
  self cCode: [] inSmalltalk:
  [tags := CArrayAccessor on: (Array new: MaxCPICCases).
  targets := CArrayAccessor on: (Array new: MaxCPICCases).
  methods := CArrayAccessor on: (Array new: MaxCPICCases)].
  used := 0.
  1 to: cPIC cPICNumCases do:
  [:i| | valid |
  pc := self addressOfEndOfCase: i inCPIC: cPIC.
  entryPoint := i = 1
  ifTrue: [backEnd jumpLongTargetBeforeFollowingAddress: pc]
  ifFalse: [backEnd jumpLongConditionalTargetBeforeFollowingAddress: pc].
  valid := true.
  "Collect all target triples except for triples whose entry-point is a freed method"
  (cPIC containsAddress: entryPoint) ifFalse:
  [targetMethod := self cCoerceSimple: entryPoint - cmNoCheckEntryOffset to: #'CogMethod *'.
  self assert: (targetMethod cmType = CMMethod or: [targetMethod cmType = CMFree]).
  targetMethod cmType = CMFree ifTrue:
  [i = 1 ifTrue: [^true]. "cannot filter out the first entry cuz classTag is at point of send."
  valid := false]].
  valid ifTrue:
  [tags at: used put: (i > 1 ifTrue: [backEnd literal32BeforeFollowingAddress: pc - backEnd jumpLongConditionalByteSize]).
  targets at: used put: entryPoint.
  methods at: used put: (backEnd literalBeforeFollowingAddress: pc - (i = 1
  ifTrue: [backEnd jumpLongByteSize]
  ifFalse: [backEnd jumpLongConditionalByteSize + backEnd cmpC32RTempByteSize])).
  used := used + 1]].
  used = cPIC cPICNumCases ifTrue:
  [^false].
  used = 0 ifTrue:
  [^true].
 
+ (self writableMethodFor: cPIC) cPICNumCases: used.
- writablePIC := self cCoerceSimple: cPIC asUnsignedInteger + codeToDataDelta to: #'CogMethod *'.
- writablePIC cPICNumCases: used.
  used = 1 ifTrue:
  [pc := self addressOfEndOfCase: 2 inCPIC: cPIC.
  self rewriteCPIC: cPIC caseJumpTo: pc.
  ^false].
  "the first entry cannot change..."
  1 to: used - 1 do:
  [:i|
  pc := self addressOfEndOfCase: i + 1 inCPIC: cPIC.
  self rewriteCPICCaseAt: pc tag: (tags at: i) objRef: (methods at: i) target: (targets at: i)].
 
  "finally, rewrite the jump 3 instr before firstCPICCaseOffset to jump to the beginning of this new case"
  self rewriteCPIC: cPIC caseJumpTo: pc - cPICCaseSize.
  ^false!

Item was changed:
  ----- Method: Cogit>>codeToDataDelta (in category 'accessing') -----
  codeToDataDelta
+ "If non-zero this is the delta between the read/execute method zone and the
+ read/write mapping of the method zone.  On operating systems where it is
+ entirely disallowed to execute code in a writable region this split is necessary
+ to be able to modify code.  In this regime all writes must be made to the
+ read/write mapped zone."
  ^codeToDataDelta!

Item was changed:
  ----- Method: Cogit>>cogExtendPIC:CaseNMethod:tag:isMNUCase: (in category 'in-line cacheing') -----
  cogExtendPIC: cPIC CaseNMethod: caseNMethod tag: caseNTag isMNUCase: isMNUCase
  "Extend the cPIC with the supplied case.  If caseNMethod is cogged dispatch direct to
  its unchecked entry-point.  If caseNMethod is not cogged, jump to the fast interpreter
  dispatch, and if isMNUCase then dispatch to fast MNU invocation and mark the cPIC as
  having the MNU case for cache flushing."
    <var: #cPIC type: #'CogMethod *'>
+ | operand target address |
- | operand target address writablePIC |
 
  coInterpreter
  compilationBreak: cPIC selector
  point: (objectMemory numBytesOf: cPIC selector)
  isMNUCase: isMNUCase.
 
  self assert: (objectRepresentation inlineCacheTagIsYoung: caseNTag) not.
  "Caller patches to open pic if caseNMethod is young."
  self assert: (caseNMethod notNil and: [(objectMemory isYoung: caseNMethod) not]).
  (isMNUCase not and: [coInterpreter methodHasCogMethod: caseNMethod])
  ifTrue: "this isn't an MNU and we have an already cogged method to jump to"
  [operand := 0.
  target := (coInterpreter cogMethodOf: caseNMethod) asInteger + cmNoCheckEntryOffset]
  ifFalse:
  [operand := caseNMethod.
  isMNUCase
  ifTrue: "this is an MNU so tag the CPIC header and setup a jump to the MNUAbort"
  [cPIC cpicHasMNUCase: true.
  target := cPIC asInteger + (self sizeof: CogMethod)]
  ifFalse: "setup a jump to the interpretAborth so we can cog the target method"
  [target := cPIC asInteger + self picInterpretAbortOffset]].
 
  "find the end address of the new case"
  address := self addressOfEndOfCase: cPIC cPICNumCases +1 inCPIC: cPIC.
 
  self rewriteCPICCaseAt: address tag: caseNTag objRef: operand target: target.
 
  "finally, rewrite the jump 3 instr  before firstCPICCaseOffset to jump to the beginning of this new case"
  self rewriteCPIC: cPIC caseJumpTo: address - cPICCaseSize.
 
  backEnd flushICacheFrom: cPIC asUnsignedInteger to: cPIC asUnsignedInteger + closedPICSize.
  "update the header flag for the number of cases"
+ (self writableMethodFor: cPIC) cPICNumCases: cPIC cPICNumCases + 1.
- writablePIC := self cCoerceSimple: cPIC asUnsignedInteger + codeToDataDelta to: #'CogMethod *'.
- writablePIC cPICNumCases: cPIC cPICNumCases + 1.
  self assertValidDualZoneFrom: cPIC asUnsignedInteger to: cPIC asUnsignedInteger + closedPICSize!

Item was changed:
  ----- Method: Cogit>>cogMNUPICSelector:receiver:methodOperand:numArgs: (in category 'in-line cacheing') -----
  cogMNUPICSelector: selector receiver: rcvr methodOperand: methodOperand numArgs: numArgs
  <api>
  "Attempt to create a one-case PIC for an MNU.
  The tag for the case is at the send site and so doesn't need to be generated."
  <returnTypeC: #'CogMethod *'>
  | startAddress writablePIC actualPIC |
  ((objectMemory isYoung: selector)
  or: [(objectRepresentation inlineCacheTagForInstance: rcvr) = self picAbortDiscriminatorValue]) ifTrue:
  [^0].
  coInterpreter
  compilationBreak: selector
  point: (objectMemory numBytesOf: selector)
  isMNUCase: true.
  self assert: endCPICCase0 notNil.
 
  "get memory in the code zone for the CPIC; if that fails we return an error code for the sender to use to work out how to blow up"
  startAddress := methodZone allocate: closedPICSize.
  startAddress = 0 ifTrue:
  [coInterpreter callForCogCompiledCodeCompaction.
  ^0].
  self maybeBreakGeneratingFrom: startAddress to: startAddress + closedPICSize - 1.
 
+ writablePIC := self writableMethodFor: startAddress.
- writablePIC := self cCoerceSimple: startAddress + codeToDataDelta to: #'CogMethod *'.
  "memcpy the prototype across to our allocated space; because anything else would be silly"
  self codeMemcpy: writablePIC
  _: (self cCoerceSimple: cPICPrototype to: #'CogMethod *')
  _: closedPICSize.
 
  self
  fillInCPICHeader: writablePIC
  numArgs: numArgs
  numCases: 1
  hasMNUCase: true
  selector: selector.
 
  self configureMNUCPIC: (actualPIC := self cCoerceSimple: startAddress to: #'CogMethod *')
  methodOperand: methodOperand
  numArgs: numArgs
  delta: startAddress - cPICPrototype.
 
  self assert: (backEnd callTargetFromReturnAddress: startAddress + missOffset) = (self picAbortTrampolineFor: numArgs).
  self assertValidDualZoneFrom: startAddress to: startAddress + closedPICSize.
  backEnd flushICacheFrom: startAddress to: startAddress + closedPICSize.
 
  ^actualPIC!

Item was changed:
  ----- Method: Cogit>>cogOpenPICSelector:numArgs: (in category 'in-line cacheing') -----
  cogOpenPICSelector: selector numArgs: numArgs
  "Create an Open PIC.  Temporarily create a direct call of ceSendFromOpenPIC:.
  Should become a probe of the first-level method lookup cache followed by a
  call of ceSendFromOpenPIC: if the probe fails."
  <returnTypeC: #'CogMethod *'>
  | startAddress codeSize mapSize end |
  coInterpreter
  compilationBreak: selector
  point: (objectMemory numBytesOf: selector)
  isMNUCase: false.
  startAddress := methodZone allocate: openPICSize.
  startAddress = 0 ifTrue:
  [^self cCoerceSimple: InsufficientCodeSpace to: #'CogMethod *'].
  methodLabel
  address: startAddress;
  dependent: nil.
  "stack allocate the various collections so that they
  are effectively garbage collected on return."
  self allocateOpcodes: 100 bytecodes: 0.
  self compileOpenPIC: selector numArgs: numArgs.
  self computeMaximumSizes.
  methodLabel concretizeAt: startAddress.
  codeSize := self generateInstructionsAt: startAddress + (self sizeof: CogMethod).
  mapSize := self generateMapAt: startAddress + openPICSize - 1 start: startAddress + cmNoCheckEntryOffset.
  self assert: entry address - startAddress = cmEntryOffset.
  self assert: (methodZone roundUpLength: (self sizeof: CogMethod) + codeSize) + (methodZone roundUpLength: mapSize) <= openPICSize.
  end := self outputInstructionsAt: startAddress + (self sizeof: CogMethod).
  self
+ fillInOPICHeader: (self writableMethodFor: startAddress)
- fillInOPICHeader: (self cCoerceSimple: startAddress + codeToDataDelta to: #'CogMethod *')
  numArgs: numArgs
  selector: selector.
  ^self cCoerceSimple: startAddress to: #'CogMethod *'!

Item was changed:
  ----- Method: Cogit>>cogPICSelector:numArgs:Case0Method:Case1Method:tag:isMNUCase: (in category 'in-line cacheing') -----
  cogPICSelector: selector numArgs: numArgs Case0Method: case0CogMethod Case1Method: case1MethodOrNil tag: case1Tag isMNUCase: isMNUCase
  "Attempt to create a two-case PIC for case0CogMethod and  case1Method,case1Tag.
  The tag for case0CogMethod is at the send site and so doesn't need to be generated.
  case1Method may be any of
  - a Cog method; link to its unchecked entry-point
  - a CompiledMethod; link to ceInterpretMethodFromPIC:
  - a CompiledMethod; link to ceMNUFromPICMNUMethod:receiver:"
  <var: #case0CogMethod type: #'CogMethod *'>
  <returnTypeC: #'CogMethod *'>
  | startAddress writablePIC actualPIC |
  (objectMemory isYoung: selector) ifTrue:
  [^self cCoerceSimple: YoungSelectorInPIC to: #'CogMethod *'].
  coInterpreter
  compilationBreak: selector
  point: (objectMemory numBytesOf: selector)
  isMNUCase: isMNUCase.
 
  "get memory in the code zone for the CPIC; if that fails we return an error code for the sender to use to work out how to blow up"
  startAddress := methodZone allocate: closedPICSize.
  startAddress = 0 ifTrue:
  [^self cCoerceSimple: InsufficientCodeSpace to: #'CogMethod *'].
  self maybeBreakGeneratingFrom: startAddress to: startAddress + closedPICSize - 1.
 
+ writablePIC := self writableMethodFor: startAddress.
- writablePIC := self cCoerceSimple: startAddress + codeToDataDelta to: #'CogMethod *'.
  "memcpy the prototype across to our allocated space; because anything else would be silly"
  self codeMemcpy: writablePIC
  _: (self cCoerceSimple: cPICPrototype to: #'CogMethod *')
  _: closedPICSize.
 
  self
  fillInCPICHeader: writablePIC
  numArgs: numArgs
  numCases: 2
  hasMNUCase: isMNUCase
  selector: selector.
 
  self configureCPIC: (actualPIC := self cCoerceSimple: startAddress to: #'CogMethod *')
  Case0: case0CogMethod
  Case1Method: case1MethodOrNil
  tag: case1Tag
  isMNUCase: isMNUCase
  numArgs: numArgs
  delta: startAddress - cPICPrototype.
 
  self assert: (backEnd callTargetFromReturnAddress: startAddress + missOffset) = (self picAbortTrampolineFor: numArgs).
  self assertValidDualZoneFrom: startAddress to: startAddress + closedPICSize.
  backEnd flushICacheFrom: startAddress to: startAddress + closedPICSize.
 
  ^actualPIC!

Item was changed:
  ----- Method: Cogit>>compactCogCompiledCode (in category 'jit - api') -----
  compactCogCompiledCode
  <api>
+ self assertValidDualZone.
- self assert: self assertValidDualZone.
  self assert: self noCogMethodsMaximallyMarked.
 
  coInterpreter markActiveMethodsAndReferents.
  methodZone freeOlderMethodsForCompaction.
  self compactPICsWithFreedTargets.
  methodZone planCompaction.
  coInterpreter updateStackZoneReferencesToCompiledCodePreCompaction.
  methodZone relocateMethodsPreCompaction.
  methodZone compactCompiledCode.
 
  backEnd
  stopsFrom: methodZone freeStart to: methodZone youngReferrers - 1;
  flushICacheFrom: methodZoneBase asUnsignedInteger
  to: methodZone youngReferrers asUnsignedInteger.
 
  self assert: self allMethodsHaveCorrectHeader.
  self assert: methodZone kosherYoungReferrers.
+ self assertValidDualZone!
- self assert: self assertValidDualZone!

Item was changed:
  ----- Method: Cogit>>fillInBlockHeadersAt: (in category 'generate machine code') -----
  fillInBlockHeadersAt: startAddress
  "Fill in the block headers now we know the exact layout of the code."
  | blockStart blockHeader |
  <var: #blockStart type: #'BlockStart *'>
  <var: #blockHeader type: #'CogBlockMethod *'>
 
  (needsFrame and: [blockCount > 0]) ifFalse:
  [^nil].
  blockNoContextSwitchOffset = nil
  ifTrue: [blockNoContextSwitchOffset := blockEntryLabel address - blockEntryNoContextSwitch address]
  ifFalse: [self assert: blockNoContextSwitchOffset = (blockEntryLabel address - blockEntryNoContextSwitch address)].
  0 to: blockCount - 1 do:
  [:i|
  blockStart := self blockStartAt: i.
+ blockHeader := self writableBlockMethodFor: blockStart fakeHeader address.
- blockHeader := self cCoerceSimple: blockStart fakeHeader address + codeToDataDelta
- to: #'CogBlockMethod *'.
  blockHeader
  homeOffset: (blockStart fakeHeader address - startAddress);
  startpc: blockStart startpc;
  cmType: CMBlock;
  cmNumArgs: blockStart numArgs;
  cbUsesInstVars: blockStart hasInstVarRef;
  stackCheckOffset: (blockStart stackCheckLabel = nil
  ifTrue: [0]
  ifFalse: [blockStart stackCheckLabel address - blockStart fakeHeader address])]!

Item was changed:
  ----- Method: Cogit>>generateCogFullBlock (in category 'generate machine code') -----
  generateCogFullBlock
  "We handle jump sizing simply.  First we make a pass that asks each
  instruction to compute its maximum size.  Then we make a pass that
  sizes jumps based on the maxmimum sizes.  Then we make a pass
  that fixes up jumps.  When fixing up a jump the jump is not allowed to
  choose a smaller offset but must stick to the size set in the second pass."
  <returnTypeC: #'CogMethod *'>
  <option: #SistaV1BytecodeSet>
  | codeSize headerSize mapSize totalSize startAddress result method |
  <var: #method type: #'CogMethod *'>
  headerSize := self sizeof: CogMethod.
  methodLabel address: methodZone freeStart.
  self computeMaximumSizes.
  methodLabel concretizeAt: methodZone freeStart.
  codeSize := self generateInstructionsAt: methodLabel address + headerSize.
  mapSize := self generateMapAt: nil start: methodLabel address + cbNoSwitchEntryOffset.
  .
  totalSize := methodZone roundUpLength: headerSize + codeSize + mapSize.
  totalSize > MaxMethodSize ifTrue:
  [^self cCoerceSimple: MethodTooBig to: #'CogMethod *'].
  startAddress := methodZone allocate: totalSize.
  startAddress = 0 ifTrue:
  [^self cCoerceSimple: InsufficientCodeSpace to: #'CogMethod *'].
  self assert: startAddress + cbEntryOffset = fullBlockEntry address.
  self assert: startAddress + cbNoSwitchEntryOffset = fullBlockNoContextSwitchEntry address.
  result := self outputInstructionsAt: startAddress + headerSize.
  self assert: startAddress + headerSize + codeSize = result.
  backEnd padIfPossibleWithStopsFrom: result to: startAddress + totalSize - mapSize - 1.
  self generateMapAt: startAddress + totalSize - 1 start: startAddress + cbNoSwitchEntryOffset.
  self flag: #TOCHECK. "It's not clear we want the same header than regular methods.
  It could be of the same size, but maybe the cmType could be different and the selector could be ignored."
+ method := self writableMethodFor: startAddress.
- method := self cCoerceSimple: startAddress + codeToDataDelta to: #'CogMethod *'.
  self fillInMethodHeader: method size: totalSize selector: objectMemory nilObject.
  method cpicHasMNUCaseOrCMIsFullBlock: true.
  method := self cCoerceSimple: startAddress to: #'CogMethod *'.
  postCompileHook ifNotNil:
  [self perform: postCompileHook with: method.
  postCompileHook := nil].
  ^method!

Item was changed:
  ----- Method: Cogit>>generateCogMethod: (in category 'generate machine code') -----
  generateCogMethod: selector
  "We handle jump sizing simply.  First we make a pass that asks each
  instruction to compute its maximum size.  Then we make a pass that
  sizes jumps based on the maxmimum sizes.  Then we make a pass
  that fixes up jumps.  When fixing up a jump the jump is not allowed to
  choose a smaller offset but must stick to the size set in the second pass."
  <returnTypeC: #'CogMethod *'>
  | codeSize headerSize mapSize totalSize startAddress result method |
  <var: #method type: #'CogMethod *'>
  headerSize := self sizeof: CogMethod.
  methodLabel address: methodZone freeStart.
  self computeMaximumSizes.
  methodLabel concretizeAt: methodZone freeStart.
  codeSize := self generateInstructionsAt: methodLabel address + headerSize.
  mapSize := self generateMapAt: nil start: methodLabel address + cmNoCheckEntryOffset.
  totalSize := methodZone roundUpLength: headerSize + codeSize + mapSize.
  totalSize > MaxMethodSize ifTrue:
  [^self cCoerceSimple: MethodTooBig to: #'CogMethod *'].
  startAddress := methodZone allocate: totalSize.
  startAddress = 0 ifTrue:
  [^self cCoerceSimple: InsufficientCodeSpace to: #'CogMethod *'].
  self assert: startAddress + cmEntryOffset = entry address.
  self assert: startAddress + cmNoCheckEntryOffset = noCheckEntry address.
  result := self outputInstructionsAt: startAddress + headerSize.
  self assert: startAddress + headerSize + codeSize = result.
  backEnd padIfPossibleWithStopsFrom: result to: startAddress + totalSize - mapSize - 1.
  self generateMapAt: startAddress + totalSize - 1 start: startAddress + cmNoCheckEntryOffset.
  self fillInBlockHeadersAt: startAddress.
+ self fillInMethodHeader: (self writableMethodFor: startAddress)
- self fillInMethodHeader: (self cCoerceSimple: startAddress + codeToDataDelta to: #'CogMethod *')
  size: totalSize
  selector: selector.
  method := self cCoerceSimple: startAddress to: #'CogMethod *'.
  postCompileHook ifNotNil:
  [self perform: postCompileHook with: method.
  postCompileHook := nil].
  ^method!

Item was changed:
  ----- Method: Cogit>>markMethodAndReferents: (in category 'jit - api') -----
  markMethodAndReferents: aCogMethod
  <api>
  <var: #aCogMethod type: #'CogBlockMethod *'>
+ | cogMethod writableMethod |
- | cogMethod |
- <var: #cogMethod type: #'CogMethod *'>
  self assert: (aCogMethod cmType = CMMethod
  or: [aCogMethod cmType = CMBlock]).
  cogMethod := aCogMethod cmType = CMMethod
  ifTrue: [self cCoerceSimple: aCogMethod to: #'CogMethod *']
  ifFalse: [aCogMethod cmHomeMethod].
+ writableMethod := self writableMethodFor: cogMethod.
+ writableMethod cmUsageCount: CMMaxUsageCount.
- cogMethod cmUsageCount: CMMaxUsageCount.
  self mapFor: cogMethod
  performUntil: #incrementUsageOfTargetIfLinkedSend:mcpc:ignored:
  arg: 0!

Item was changed:
  ----- Method: Cogit>>setSelectorOf:to: (in category 'jit - api') -----
  setSelectorOf: cogMethod to: aSelectorOop
  <api>
  "If a method is compiled to machine code via a block entry it won't have a selector.
  A subsequent send can find the method and hence fill in the selector."
  <var: #cogMethod type: #'CogMethod *'>
  "self disassembleMethod: cogMethod"
- | writableMethod |
  coInterpreter
  compilationBreak: aSelectorOop
  point: (objectMemory numBytesOf: aSelectorOop)
  isMNUCase: false.
  self assert: cogMethod cmType = CMMethod.
+ (self writableMethodFor: cogMethod) selector: aSelectorOop.
- writableMethod := self cCoerceSimple: cogMethod asUnsignedInteger + codeToDataDelta to: #'CogMethod *'.
- writableMethod selector: aSelectorOop.
  (objectMemory isYoung: aSelectorOop) ifTrue:
  [methodZone ensureInYoungReferrers: cogMethod]!

Item was added:
+ ----- Method: Cogit>>writableBlockMethodFor: (in category 'generate machine code') -----
+ writableBlockMethodFor: aCogMethodOrInteger
+ <inline: #always>
+ ^self cCoerceSimple: aCogMethodOrInteger asUnsignedInteger + codeToDataDelta to: #'CogBlockMethod *'!

Item was added:
+ ----- Method: Cogit>>writableMethodFor: (in category 'generate machine code') -----
+ writableMethodFor: aCogMethodOrInteger
+ <inline: #always>
+ ^self cCoerceSimple: aCogMethodOrInteger asUnsignedInteger + codeToDataDelta to: #'CogMethod *'!

Item was changed:
+ ----- Method: NSSendCacheSurrogate32>>classTag (in category 'accessing generated') -----
- ----- Method: NSSendCacheSurrogate32>>classTag (in category 'accessing') -----
  classTag
  ^memory unsignedLongAt: address + 1!

Item was changed:
+ ----- Method: NSSendCacheSurrogate32>>classTag: (in category 'accessing generated') -----
- ----- Method: NSSendCacheSurrogate32>>classTag: (in category 'accessing') -----
  classTag: aValue
  ^memory
  unsignedLongAt: address + 1
  put: aValue!

Item was changed:
+ ----- Method: NSSendCacheSurrogate32>>depth (in category 'accessing generated') -----
- ----- Method: NSSendCacheSurrogate32>>depth (in category 'accessing') -----
  depth
  ^memory unsignedLongAt: address + 21!

Item was changed:
+ ----- Method: NSSendCacheSurrogate32>>depth: (in category 'accessing generated') -----
- ----- Method: NSSendCacheSurrogate32>>depth: (in category 'accessing') -----
  depth: aValue
  ^memory
  unsignedLongAt: address + 21
  put: aValue!

Item was changed:
+ ----- Method: NSSendCacheSurrogate32>>enclosingObject (in category 'accessing generated') -----
- ----- Method: NSSendCacheSurrogate32>>enclosingObject (in category 'accessing') -----
  enclosingObject
  ^memory unsignedLongAt: address + 5!

Item was changed:
+ ----- Method: NSSendCacheSurrogate32>>enclosingObject: (in category 'accessing generated') -----
- ----- Method: NSSendCacheSurrogate32>>enclosingObject: (in category 'accessing') -----
  enclosingObject: aValue
  ^memory
  unsignedLongAt: address + 5
  put: aValue!

Item was changed:
+ ----- Method: NSSendCacheSurrogate32>>numArgs (in category 'accessing generated') -----
- ----- Method: NSSendCacheSurrogate32>>numArgs (in category 'accessing') -----
  numArgs
  ^memory unsignedLongAt: address + 17!

Item was changed:
+ ----- Method: NSSendCacheSurrogate32>>numArgs: (in category 'accessing generated') -----
- ----- Method: NSSendCacheSurrogate32>>numArgs: (in category 'accessing') -----
  numArgs: aValue
  ^memory
  unsignedLongAt: address + 17
  put: aValue!

Item was changed:
+ ----- Method: NSSendCacheSurrogate32>>selector (in category 'accessing generated') -----
- ----- Method: NSSendCacheSurrogate32>>selector (in category 'accessing') -----
  selector
  ^memory unsignedLongAt: address + 13!

Item was changed:
+ ----- Method: NSSendCacheSurrogate32>>selector: (in category 'accessing generated') -----
- ----- Method: NSSendCacheSurrogate32>>selector: (in category 'accessing') -----
  selector: aValue
  ^memory
  unsignedLongAt: address + 13
  put: aValue!

Item was changed:
+ ----- Method: NSSendCacheSurrogate32>>target (in category 'accessing generated') -----
- ----- Method: NSSendCacheSurrogate32>>target (in category 'accessing') -----
  target
  ^memory unsignedLongAt: address + 9!

Item was changed:
+ ----- Method: NSSendCacheSurrogate32>>target: (in category 'accessing generated') -----
- ----- Method: NSSendCacheSurrogate32>>target: (in category 'accessing') -----
  target: aValue
  ^memory
  unsignedLongAt: address + 9
  put: aValue!

Item was changed:
+ ----- Method: NSSendCacheSurrogate64>>classTag (in category 'accessing generated') -----
- ----- Method: NSSendCacheSurrogate64>>classTag (in category 'accessing') -----
  classTag
  ^memory unsignedLong64At: address + 1!

Item was changed:
+ ----- Method: NSSendCacheSurrogate64>>classTag: (in category 'accessing generated') -----
- ----- Method: NSSendCacheSurrogate64>>classTag: (in category 'accessing') -----
  classTag: aValue
  ^memory
  unsignedLong64At: address + 1
  put: aValue!

Item was changed:
+ ----- Method: NSSendCacheSurrogate64>>depth (in category 'accessing generated') -----
- ----- Method: NSSendCacheSurrogate64>>depth (in category 'accessing') -----
  depth
  ^memory unsignedLong64At: address + 41!

Item was changed:
+ ----- Method: NSSendCacheSurrogate64>>depth: (in category 'accessing generated') -----
- ----- Method: NSSendCacheSurrogate64>>depth: (in category 'accessing') -----
  depth: aValue
  ^memory
  unsignedLong64At: address + 41
  put: aValue!

Item was changed:
+ ----- Method: NSSendCacheSurrogate64>>enclosingObject (in category 'accessing generated') -----
- ----- Method: NSSendCacheSurrogate64>>enclosingObject (in category 'accessing') -----
  enclosingObject
  ^memory unsignedLong64At: address + 9!

Item was changed:
+ ----- Method: NSSendCacheSurrogate64>>enclosingObject: (in category 'accessing generated') -----
- ----- Method: NSSendCacheSurrogate64>>enclosingObject: (in category 'accessing') -----
  enclosingObject: aValue
  ^memory
  unsignedLong64At: address + 9
  put: aValue!

Item was changed:
+ ----- Method: NSSendCacheSurrogate64>>numArgs (in category 'accessing generated') -----
- ----- Method: NSSendCacheSurrogate64>>numArgs (in category 'accessing') -----
  numArgs
  ^memory unsignedLong64At: address + 33!

Item was changed:
+ ----- Method: NSSendCacheSurrogate64>>numArgs: (in category 'accessing generated') -----
- ----- Method: NSSendCacheSurrogate64>>numArgs: (in category 'accessing') -----
  numArgs: aValue
  ^memory
  unsignedLong64At: address + 33
  put: aValue!

Item was changed:
+ ----- Method: NSSendCacheSurrogate64>>selector (in category 'accessing generated') -----
- ----- Method: NSSendCacheSurrogate64>>selector (in category 'accessing') -----
  selector
  ^memory unsignedLong64At: address + 25!

Item was changed:
+ ----- Method: NSSendCacheSurrogate64>>selector: (in category 'accessing generated') -----
- ----- Method: NSSendCacheSurrogate64>>selector: (in category 'accessing') -----
  selector: aValue
  ^memory
  unsignedLong64At: address + 25
  put: aValue!

Item was changed:
+ ----- Method: NSSendCacheSurrogate64>>target (in category 'accessing generated') -----
- ----- Method: NSSendCacheSurrogate64>>target (in category 'accessing') -----
  target
  ^memory unsignedLong64At: address + 17!

Item was changed:
+ ----- Method: NSSendCacheSurrogate64>>target: (in category 'accessing generated') -----
- ----- Method: NSSendCacheSurrogate64>>target: (in category 'accessing') -----
  target: aValue
  ^memory
  unsignedLong64At: address + 17
  put: aValue!

Item was changed:
  ----- Method: VMStructType class>>checkGenerateSurrogate:bytesPerWord: (in category 'code generation') -----
  checkGenerateSurrogate: surrogateClass bytesPerWord: bytesPerWord
  "Check the accessor methods for the fields of the receiver and if necessary install new
  or updated versions in the surrogate class alpng with the alignedByteSize class method."
 
  "self withAllSubclasses do:
  [:cogMethodClass| (cogMethodClass class includesSelector: #initialize) ifTrue: [cogMethodClass initialize]]"
 
  "CogBlockMethod checkGenerateSurrogate: CogBlockMethodSurrogate32 bytesPerWord: 4.
  CogMethod checkGenerateSurrogate: CogMethodSurrogate32 bytesPerWord: 4.
  CogBlockMethod checkGenerateSurrogate: CogBlockMethodSurrogate64 bytesPerWord: 8.
  CogMethod checkGenerateSurrogate: CogMethodSurrogate64 bytesPerWord: 8"
  | accessors oldBytesPerWord |
  oldBytesPerWord := BytesPerWord.
  accessors := [self fieldAccessorSourceFor: surrogateClass bytesPerWord: (BytesPerWord := bytesPerWord)]
  ensure: [BytesPerWord := oldBytesPerWord].
 
  "All methods which are the same in 32 and 64 bit versions should be compiled in the superclass iff the superclass is not of a specific word size."
  (self dualForSurrogateClass: surrogateClass) ifNotNil:
  [:dual| | duals |
+ surrogateClass superclass name last isDigit ifFalse:
+ [duals := [self fieldAccessorSourceFor: dual bytesPerWord: (BytesPerWord := bytesPerWord = 4 ifTrue: [8] ifFalse: [4])]
+ ensure: [BytesPerWord := oldBytesPerWord].
- duals := [self fieldAccessorSourceFor: dual bytesPerWord: (BytesPerWord := bytesPerWord = 4 ifTrue: [8] ifFalse: [4])]
- ensure: [BytesPerWord := oldBytesPerWord].
 
+ (accessors keys select: [:key| (accessors at: key) = (duals at: {key first isMeta ifTrue: [dual class] ifFalse: [dual]. key last} ifAbsent: ['missing'])]) do:
+ [:key| | source class selector |
+ class := key first.
+ selector := key last.
+ source := accessors removeKey: key.
+ (class includesSelector: selector) ifTrue:
+ [class removeSelector: selector].
+ (class superclass sourceCodeAt: selector ifAbsent: ['']) asString ~= source ifTrue:
+ [class superclass compile: source classified: 'accessing generated']]]].
- (accessors keys select: [:key| (accessors at: key) = (duals at: {key first isMeta ifTrue: [dual class] ifFalse: [dual]. key last} ifAbsent: ['missing'])]) do:
- [:key| | source class selector |
- class := key first.
- selector := key last.
- source := accessors removeKey: key.
- (class includesSelector: selector) ifTrue:
- [class removeSelector: selector].
- (class superclass sourceCodeAt: selector ifAbsent: ['']) asString ~= source ifTrue:
- [class superclass compile: source classified: 'accessing generated']]].
 
  accessors keysAndValuesDo:
+ [:key :source| | class selector ancestor |
- [:key :source| | class selector |
  class := key first.
  selector := key last.
+ ((ancestor := class superclass whichClassIncludesSelector: selector) notNil
+ and: [source = (ancestor sourceCodeAt: selector ifAbsent: ['']) asString])
+ ifTrue: [class removeSelector: selector]
+ ifFalse:
+ [source ~= (class sourceCodeAt: selector ifAbsent: ['']) asString ifTrue:
+ [class compile: source classified: 'accessing generated']]]!
- source ~= (class sourceCodeAt: selector ifAbsent: ['']) asString ifTrue:
- [class compile: source classified: 'accessing generated']]!

Item was changed:
  ----- Method: VMStructType class>>fieldAccessorSourceFor:bytesPerWord: (in category 'code generation') -----
  fieldAccessorSourceFor: surrogateClass bytesPerWord: bytesPerWord
  "Answer a Dictionary of MethodReference to source for the accessors of the inst vars of the
  receiver and the alignedByteSize class method in surrogateClass with the given word size."
 
  "{CogBlockMethod fieldAccessorSourceFor: CogBlockMethodSurrogate32 bytesPerWord: 4.
  CogMethod fieldAccessorSourceFor: CogMethodSurrogate32 bytesPerWord: 4.
  CogBlockMethod fieldAccessorSourceFor: CogBlockMethodSurrogate64 bytesPerWord: 8.
  CogMethod fieldAccessorSourceFor: CogMethodSurrogate64 bytesPerWord: 8}"
  | methods bitPosition alignedByteSize currentOffset |
  methods := Dictionary new.
  bitPosition := 0.
  (self fieldAccessorsForBytesPerWord: bytesPerWord) do:
  [:spec|
  "reset the bitPosition if the offset expression changes."
  currentOffset ~= (self offsetForInstVar: spec first) ifTrue:
  [bitPosition := 0.
  currentOffset := self offsetForInstVar: spec first].
+ spec first ~= #unused ifTrue:
- "If the accessor is already defined in a superclass don't redefine it in the subclass.
- We assume it is correctly defined in the superclass."
- (spec first ~= #unused
- and: [(surrogateClass whichClassIncludesSelector: spec first asSymbol)
- ifNil: [true]
- ifNotNil: [:implementingClass|
- self assert: (implementingClass inheritsFrom: Object).
- implementingClass == surrogateClass]]) ifTrue:
  [methods
  at: {surrogateClass. spec first asSymbol}
  put: (self getter: spec first
  bitPosition: bitPosition
  bitWidth: spec second
  type: (spec at: 3 ifAbsent: []));
  at: {surrogateClass. (spec first, ':') asSymbol}
  put: (self setter: spec first
  bitPosition: bitPosition
  bitWidth: spec second
  type: (spec at: 3 ifAbsent: []))].
  bitPosition := bitPosition + spec second].
  alignedByteSize := (self roundUpBitPosition: bitPosition toWordBoundary: bytesPerWord) / 8.
  self assert: alignedByteSize isInteger.
  methods
  at: {surrogateClass class. #alignedByteSize}
  put: #alignedByteSize
  , (String with: Character cr with: Character tab with: $^)
  , alignedByteSize printString,
  (currentOffset ifNil: [''] ifNotNil: [' + self ', currentOffset]).
  ^methods!

Item was changed:
  ----- Method: VMStructType class>>setter:bitPosition:bitWidth:type: (in category 'code generation') -----
  setter: getter bitPosition: bitPosition bitWidth: bitWidth type: typeOrNil
  ^String streamContents:
+ [:s| | startByte endByte shift indexExpr accessor alignedPowerOf2 mask |
- [:s| | startByte endByte shift alignedPowerOf2 accessor mask |
  startByte := bitPosition // 8.
  endByte := bitPosition + bitWidth - 1 // 8.
  shift := bitPosition \\ 8.
+ s nextPutAll: getter; nextPutAll: ': aValue'; crtab: 1.
+ indexExpr := 'address + ',
+ ((self offsetForInstVar: getter) ifNotNil: [:offsetExpr| offsetExpr, ' + '] ifNil: ['']),
+ (startByte + 1) printString.
- alignedPowerOf2 := (#(8 16 32 64) includes: bitWidth) and: [shift = 0].
  accessor := 'unsigned'
  , (#('Byte' 'Short' 'Long' 'Long')
  at: endByte - startByte + 1
  ifAbsent: ['Long64'])
+ , 'At: '.
+ (alignedPowerOf2 := (#(8 16 32 64) includes: bitWidth) and: [shift = 0])
+ ifTrue: "index used once; no point using a temp to hold it"
+ [accessor := accessor, indexExpr]
+ ifFalse: "index used twice; cache it"
+ [s nextPutAll: '| index |'; crtab: 1; nextPutAll: 'index := '; nextPutAll: indexExpr; nextPut: $.; crtab: 1.
+ accessor := accessor, 'index'].
- , 'At: index'.
  mask := #(16rFF 16rFFFF 16rFFFFFFFF 16rFFFFFFFF)
  at: endByte - startByte + 1
  ifAbsent: [(2 raisedTo: 64) - 1].
- s nextPutAll: getter; nextPutAll: ': aValue'; crtab: 1.
- s nextPutAll: '| index |'; crtab: 1.
- s nextPutAll: 'index := address + '.
- (self offsetForInstVar: getter) ifNotNil:
- [:offsetExpr| s nextPutAll: offsetExpr, ' + '].
- s print: startByte + 1; nextPut: $.; crtab: 1.
  (typeOrNil notNil or: [alignedPowerOf2]) ifFalse:
  [s nextPutAll: 'self assert: (aValue between: 0 and: '; nextPutAll:  ((1 << bitWidth) - 1) hex; nextPutAll: ').'; crtab: 1].
  alignedPowerOf2 ifTrue:
  [s nextPut: $^].
  self putAtPut: accessor
  type: typeOrNil
  mask: (alignedPowerOf2 ifFalse: [mask - ((1 << bitWidth - 1) << shift)])
  shift: shift
  on: s
  indent: 2.
  alignedPowerOf2 ifFalse:
  [s nextPut: $.; crtab: 1; nextPutAll: '^aValue']]!