[Vm-dev] VM Maker: VMMaker.oscog-eem.2683.mcz

commits at source.squeak.org commits at source.squeak.org
Tue Jan 28 19:16:15 UTC 2020


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

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

Name: VMMaker.oscog-eem.2683
Author: eem
Time: 28 January 2020, 11:16:00.291898 am
UUID: 22e732f1-20f2-4ef3-949d-145190a4007a
Ancestors: VMMaker.oscog-eem.2682

Simulation:
Generate more concise setters by precomputing the index.
Put accessors that are the same in 32 and 63 bits in CogMethodSurrogate, the abstract superclass.
Recategorize in 'accessing generated'.
Fix some comment typos.

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

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'.
- 					, 'At: address + '.
- 		(self offsetForInstVar: getter) ifNotNil:
- 			[:offsetExpr| accessor := accessor, offsetExpr, ' + '].
  		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.
- 		s nextPutAll: getter; nextPutAll: ': aValue'.
- 		s crtab: 1; nextPutAll: '| delta |'.
  		(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.
- 			[s crtab: 1; nextPutAll: 'self assert: (aValue between: 0 and: '; nextPutAll:  ((1 << bitWidth) - 1) hex; nextPutAll: ').'].
- 		s crtab: 1; nextPutAll: '(delta := cogit codeToDataDelta) > 0 ifTrue:'.
- 		s crtab: 2; nextPutAll: '[self assert: (cogit addressIsInCodeZone: address - delta).'.
- 		s crtab: 2; space.
  		self putAtPut: accessor
  			type: typeOrNil
  			mask: (alignedPowerOf2 ifFalse: [mask - ((1 << bitWidth - 1) << shift)])
  			shift: shift
- 			at: startByte
  			on: s
  			indent: 3.
  		s nextPutAll: '].'; crtab: 1.
  		alignedPowerOf2 ifTrue:
  			[s nextPut: $^].
  		self putAtPut: (accessor copyReplaceAll: 'address' with: 'address - delta')
  			type: typeOrNil
  			mask: (alignedPowerOf2 ifFalse: [mask - ((1 << bitWidth - 1) << shift)])
  			shift: shift
- 			at: startByte
  			on: s
  			indent: 2.
  		alignedPowerOf2 ifFalse:
  			[s nextPut: $.; crtab: 1; nextPutAll: '^aValue']]!

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

Item was added:
+ ----- 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 added:
+ ----- Method: CogBlockMethodSurrogate32>>blockSize (in category 'accessing generated') -----
+ blockSize
+ 	^memory unsignedShortAt: address + 5 + baseHeaderSize!

Item was added:
+ ----- 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 removed:
- ----- Method: CogBlockMethodSurrogate32>>cbUsesInstVars (in category 'accessing') -----
- cbUsesInstVars
- 	^(((memory unsignedByteAt: address + 3 + baseHeaderSize) bitShift: -1) bitAnd: 16r1) ~= 0!

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

Item was removed:
- ----- Method: CogBlockMethodSurrogate32>>cmHasMovableLiteral (in category 'accessing') -----
- cmHasMovableLiteral
- 	^(((memory unsignedByteAt: address + 3 + baseHeaderSize) bitShift: -2) bitAnd: 16r1) ~= 0!

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

Item was changed:
+ ----- Method: CogBlockMethodSurrogate32>>cmIsUnlinked (in category 'accessing generated') -----
- ----- Method: CogBlockMethodSurrogate32>>cmIsUnlinked (in category 'accessing') -----
  cmIsUnlinked
  	^(((memory unsignedByteAt: address + 6) bitShift: -4) bitAnd: 16r1) ~= 0!

Item was changed:
+ ----- Method: CogBlockMethodSurrogate32>>cmIsUnlinked: (in category 'accessing generated') -----
- ----- Method: CogBlockMethodSurrogate32>>cmIsUnlinked: (in category 'accessing') -----
  cmIsUnlinked: aValue
  	memory
  		unsignedByteAt: address + 6
  		put: (((memory unsignedByteAt: address + 6) bitAnd: 16rEF) + ((aValue ifTrue: [1] ifFalse: [0]) bitShift: 4)).
  	^aValue!

Item was removed:
- ----- Method: CogBlockMethodSurrogate32>>cmNumArgs (in category 'accessing') -----
- cmNumArgs
- 	^memory unsignedByteAt: address + 1 + baseHeaderSize!

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

Item was removed:
- ----- Method: CogBlockMethodSurrogate32>>cmRefersToYoung (in category 'accessing') -----
- cmRefersToYoung
- 	^(((memory unsignedByteAt: address + 2 + baseHeaderSize) bitShift: -3) bitAnd: 16r1) ~= 0!

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

Item was removed:
- ----- Method: CogBlockMethodSurrogate32>>cmType (in category 'accessing') -----
- cmType
- 	^(memory unsignedByteAt: address + 2 + baseHeaderSize) bitAnd: 16r7!

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

Item was removed:
- ----- Method: CogBlockMethodSurrogate32>>cmUsageCount (in category 'accessing') -----
- cmUsageCount
- 	^((memory unsignedByteAt: address + 2 + baseHeaderSize) bitShift: -5) bitAnd: 16r7!

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

Item was removed:
- ----- Method: CogBlockMethodSurrogate32>>cmUsesPenultimateLit (in category 'accessing') -----
- cmUsesPenultimateLit
- 	^((memory unsignedByteAt: address + 3 + baseHeaderSize) bitAnd: 16r1) ~= 0!

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

Item was removed:
- ----- Method: CogBlockMethodSurrogate32>>cpicHasMNUCaseOrCMIsFullBlock (in category 'accessing') -----
- cpicHasMNUCaseOrCMIsFullBlock
- 	^(((memory unsignedByteAt: address + 2 + baseHeaderSize) bitShift: -4) bitAnd: 16r1) ~= 0!

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

Item was removed:
- ----- Method: CogBlockMethodSurrogate32>>homeOffset (in category 'accessing') -----
- homeOffset
- 	^memory unsignedShortAt: address + 1!

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

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

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

Item was removed:
- ----- Method: CogBlockMethodSurrogate32>>stackCheckOffset (in category 'accessing') -----
- stackCheckOffset
- 	^((memory unsignedShortAt: address + 3 + baseHeaderSize) bitShift: -4) bitAnd: 16rFFF!

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

Item was removed:
- ----- Method: CogBlockMethodSurrogate32>>startpc (in category 'accessing') -----
- startpc
- 	^memory unsignedShortAt: address + 3!

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

Item was removed:
- ----- Method: CogBlockMethodSurrogate64>>cbUsesInstVars (in category 'accessing') -----
- cbUsesInstVars
- 	^(((memory unsignedByteAt: address + 3 + baseHeaderSize) bitShift: -1) bitAnd: 16r1) ~= 0!

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

Item was removed:
- ----- Method: CogBlockMethodSurrogate64>>cmHasMovableLiteral (in category 'accessing') -----
- cmHasMovableLiteral
- 	^(((memory unsignedByteAt: address + 3 + baseHeaderSize) bitShift: -2) bitAnd: 16r1) ~= 0!

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

Item was changed:
+ ----- Method: CogBlockMethodSurrogate64>>cmIsUnlinked (in category 'accessing generated') -----
- ----- Method: CogBlockMethodSurrogate64>>cmIsUnlinked (in category 'accessing') -----
  cmIsUnlinked
  	^(((memory unsignedByteAt: address + 10) bitShift: -4) bitAnd: 16r1) ~= 0!

Item was changed:
+ ----- Method: CogBlockMethodSurrogate64>>cmIsUnlinked: (in category 'accessing generated') -----
- ----- Method: CogBlockMethodSurrogate64>>cmIsUnlinked: (in category 'accessing') -----
  cmIsUnlinked: aValue
  	memory
  		unsignedByteAt: address + 10
  		put: (((memory unsignedByteAt: address + 10) bitAnd: 16rEF) + ((aValue ifTrue: [1] ifFalse: [0]) bitShift: 4)).
  	^aValue!

Item was removed:
- ----- Method: CogBlockMethodSurrogate64>>cmNumArgs (in category 'accessing') -----
- cmNumArgs
- 	^memory unsignedByteAt: address + 1 + baseHeaderSize!

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

Item was removed:
- ----- Method: CogBlockMethodSurrogate64>>cmRefersToYoung (in category 'accessing') -----
- cmRefersToYoung
- 	^(((memory unsignedByteAt: address + 2 + baseHeaderSize) bitShift: -3) bitAnd: 16r1) ~= 0!

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

Item was removed:
- ----- Method: CogBlockMethodSurrogate64>>cmType (in category 'accessing') -----
- cmType
- 	^(memory unsignedByteAt: address + 2 + baseHeaderSize) bitAnd: 16r7!

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

Item was removed:
- ----- Method: CogBlockMethodSurrogate64>>cmUsageCount (in category 'accessing') -----
- cmUsageCount
- 	^((memory unsignedByteAt: address + 2 + baseHeaderSize) bitShift: -5) bitAnd: 16r7!

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

Item was removed:
- ----- Method: CogBlockMethodSurrogate64>>cmUsesPenultimateLit (in category 'accessing') -----
- cmUsesPenultimateLit
- 	^((memory unsignedByteAt: address + 3 + baseHeaderSize) bitAnd: 16r1) ~= 0!

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

Item was removed:
- ----- Method: CogBlockMethodSurrogate64>>cpicHasMNUCaseOrCMIsFullBlock (in category 'accessing') -----
- cpicHasMNUCaseOrCMIsFullBlock
- 	^(((memory unsignedByteAt: address + 2 + baseHeaderSize) bitShift: -4) bitAnd: 16r1) ~= 0!

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

Item was removed:
- ----- Method: CogBlockMethodSurrogate64>>homeOffset (in category 'accessing') -----
- homeOffset
- 	^memory unsignedShortAt: address + 1!

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

Item was changed:
+ ----- Method: CogBlockMethodSurrogate64>>padToWord (in category 'accessing generated') -----
- ----- Method: CogBlockMethodSurrogate64>>padToWord (in category 'accessing') -----
  padToWord
  	^memory unsignedLong64At: address + 5!

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

Item was removed:
- ----- Method: CogBlockMethodSurrogate64>>stackCheckOffset (in category 'accessing') -----
- stackCheckOffset
- 	^((memory unsignedShortAt: address + 3 + baseHeaderSize) bitShift: -4) bitAnd: 16rFFF!

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

Item was removed:
- ----- Method: CogBlockMethodSurrogate64>>startpc (in category 'accessing') -----
- startpc
- 	^memory unsignedShortAt: address + 3!

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

Item was changed:
  ----- Method: CogMethodSurrogate>>asInteger (in category 'accessing') -----
  asInteger
+ 	"Answer the surrogate's address. This is equivalent to a C cast to sqInt,
- 	"Answer the surrogate's adress. This is equivalent to a C cast to sqInt,
  	 which is precisely what Slang generates for asInteger"
  	^address!

Item was changed:
  ----- Method: CogMethodSurrogate>>asIntegerPtr (in category 'accessing') -----
  asIntegerPtr
+ 	"Answer the surrogate's address. This is equivalent to a C cast to usqIntptr_t,
- 	"Answer the surrogate's adress. This is equivalent to a C cast to usqIntptr_t,
  	 which is precisely what Slang generates for asIntegerPtr"
  	^address!

Item was changed:
  ----- Method: CogMethodSurrogate>>asUnsignedInteger (in category 'accessing') -----
  asUnsignedInteger
+ 	"Answer the surrogate's address. This is equivalent to a C cast to usqInt,
- 	"Answer the surrogate's adress. This is equivalent to a C cast to usqInt,
  	 which is precisely what Slang generates for asUnsignedInteger"
  	^address!

Item was changed:
  ----- Method: CogMethodSurrogate>>asUnsignedIntegerPtr (in category 'accessing') -----
  asUnsignedIntegerPtr
+ 	"Answer the surrogate's address. This is equivalent to a C cast to usqIntptr_t,
- 	"Answer the surrogate's adress. This is equivalent to a C cast to usqIntptr_t,
  	 which is precisely what Slang generates for asUnsignedIntegerPtr"
  	^address!

Item was added:
+ ----- Method: CogMethodSurrogate>>cbUsesInstVars (in category 'accessing generated') -----
+ cbUsesInstVars
+ 	^(((memory unsignedByteAt: address + 3 + baseHeaderSize) bitShift: -1) bitAnd: 16r1) ~= 0!

Item was added:
+ ----- 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
+ 			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 added:
+ ----- Method: CogMethodSurrogate>>cmHasMovableLiteral (in category 'accessing generated') -----
+ cmHasMovableLiteral
+ 	^(((memory unsignedByteAt: address + 3 + baseHeaderSize) bitShift: -2) bitAnd: 16r1) ~= 0!

Item was added:
+ ----- 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
+ 			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 added:
+ ----- Method: CogMethodSurrogate>>cmNumArgs (in category 'accessing generated') -----
+ cmNumArgs
+ 	^memory unsignedByteAt: address + 1 + baseHeaderSize!

Item was added:
+ ----- 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
+ 			put: aValue].
+ 	^memory
+ 		unsignedByteAt: index
+ 		put: aValue!

Item was added:
+ ----- Method: CogMethodSurrogate>>cmRefersToYoung (in category 'accessing generated') -----
+ cmRefersToYoung
+ 	^(((memory unsignedByteAt: address + 2 + baseHeaderSize) bitShift: -3) bitAnd: 16r1) ~= 0!

Item was added:
+ ----- 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
+ 			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 added:
+ ----- Method: CogMethodSurrogate>>cmType (in category 'accessing generated') -----
+ cmType
+ 	^(memory unsignedByteAt: address + 2 + baseHeaderSize) bitAnd: 16r7!

Item was added:
+ ----- 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
+ 			put: ((memory unsignedByteAt: index) bitAnd: 16rF8) + aValue].
+ 	memory
+ 		unsignedByteAt: index
+ 		put: ((memory unsignedByteAt: index) bitAnd: 16rF8) + aValue.
+ 	^aValue!

Item was added:
+ ----- Method: CogMethodSurrogate>>cmUsageCount (in category 'accessing generated') -----
+ cmUsageCount
+ 	^((memory unsignedByteAt: address + 2 + baseHeaderSize) bitShift: -5) bitAnd: 16r7!

Item was added:
+ ----- 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
+ 			put: ((memory unsignedByteAt: index) bitAnd: 16r1F) + (aValue bitShift: 5)].
+ 	memory
+ 		unsignedByteAt: index
+ 		put: ((memory unsignedByteAt: index) bitAnd: 16r1F) + (aValue bitShift: 5).
+ 	^aValue!

Item was added:
+ ----- Method: CogMethodSurrogate>>cmUsesPenultimateLit (in category 'accessing generated') -----
+ cmUsesPenultimateLit
+ 	^((memory unsignedByteAt: address + 3 + baseHeaderSize) bitAnd: 16r1) ~= 0!

Item was added:
+ ----- 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
+ 			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 added:
+ ----- Method: CogMethodSurrogate>>cpicHasMNUCaseOrCMIsFullBlock (in category 'accessing generated') -----
+ cpicHasMNUCaseOrCMIsFullBlock
+ 	^(((memory unsignedByteAt: address + 2 + baseHeaderSize) bitShift: -4) bitAnd: 16r1) ~= 0!

Item was added:
+ ----- 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
+ 			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 added:
+ ----- Method: CogMethodSurrogate>>homeOffset (in category 'accessing generated') -----
+ homeOffset
+ 	^memory unsignedShortAt: address + 1!

Item was added:
+ ----- 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
+ 			put: aValue].
+ 	^memory
+ 		unsignedShortAt: index
+ 		put: aValue!

Item was added:
+ ----- Method: CogMethodSurrogate>>stackCheckOffset (in category 'accessing generated') -----
+ stackCheckOffset
+ 	^((memory unsignedShortAt: address + 3 + baseHeaderSize) bitShift: -4) bitAnd: 16rFFF!

Item was added:
+ ----- 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
+ 			put: ((memory unsignedShortAt: index) bitAnd: 16rF) + (aValue bitShift: 4)].
+ 	memory
+ 		unsignedShortAt: index
+ 		put: ((memory unsignedShortAt: index) bitAnd: 16rF) + (aValue bitShift: 4).
+ 	^aValue!

Item was added:
+ ----- Method: CogMethodSurrogate>>startpc (in category 'accessing generated') -----
+ startpc
+ 	^memory unsignedShortAt: address + 3!

Item was added:
+ ----- 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
+ 			put: aValue].
+ 	^memory
+ 		unsignedShortAt: index
+ 		put: aValue!

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

Item was added:
+ CogMethodSurrogate32 subclass: #CogNewspeakMethodSurrogate32
+ 	instanceVariableNames: ''
+ 	classVariableNames: ''
+ 	poolDictionaries: ''
+ 	category: 'VMMaker-JITSimulation'!

Item was added:
+ ----- Method: CogNewspeakMethodSurrogate32 class>>alignedByteSize (in category 'accessing') -----
+ alignedByteSize
+ 	^24 + self baseHeaderSize!

Item was added:
+ ----- Method: CogNewspeakMethodSurrogate32>>nextMethodOrIRCs (in category 'accessing generated') -----
+ nextMethodOrIRCs
+ 	^memory unsignedLongAt: address + 21 + baseHeaderSize!

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

Item was added:
+ CogMethodSurrogate64 subclass: #CogNewspeakMethodSurrogate64
+ 	instanceVariableNames: ''
+ 	classVariableNames: ''
+ 	poolDictionaries: ''
+ 	category: 'VMMaker-JITSimulation'!

Item was added:
+ ----- Method: CogNewspeakMethodSurrogate64 class>>alignedByteSize (in category 'accessing') -----
+ alignedByteSize
+ 	^40 + self baseHeaderSize!

Item was added:
+ ----- Method: CogNewspeakMethodSurrogate64>>nextMethodOrIRCs (in category 'accessing generated') -----
+ nextMethodOrIRCs
+ 	^memory unsignedLong64At: address + 33 + baseHeaderSize!

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

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

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

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

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

Item was changed:
  ----- Method: Cogit>>initialize (in category 'initialization') -----
  initialize
  	"Here we can initialize the variables C initialized to zero.  #initialize methods do /not/ get translated."
  	| wordSize |
  	initialPC := 0.
  	processorFrameValid := false.
  	codeToDataDelta := 0.
  	wordSize := self class objectMemoryClass wordSize.
  	cogMethodSurrogateClass := NewspeakVM
  									ifTrue:
  										[wordSize = 4
+ 											ifTrue: [CogNewspeakMethodSurrogate32]
+ 											ifFalse: [CogNewspeakMethodSurrogate64]]
- 											ifTrue: [NewspeakCogMethodSurrogate32]
- 											ifFalse: [NewspeakCogMethodSurrogate64]]
  									ifFalse:
  										[wordSize = 4
  											ifTrue: [CogMethodSurrogate32]
  											ifFalse: [CogMethodSurrogate64]].
  	cogBlockMethodSurrogateClass := wordSize = 4
  											ifTrue: [CogBlockMethodSurrogate32]
  											ifFalse: [CogBlockMethodSurrogate64].
  	nsSendCacheSurrogateClass := wordSize = 4
  											ifTrue: [NSSendCacheSurrogate32]
  											ifFalse: [NSSendCacheSurrogate64]!

Item was removed:
- CogMethodSurrogate32 subclass: #NewspeakCogMethodSurrogate32
- 	instanceVariableNames: ''
- 	classVariableNames: ''
- 	poolDictionaries: ''
- 	category: 'VMMaker-JITSimulation'!

Item was removed:
- ----- Method: NewspeakCogMethodSurrogate32 class>>alignedByteSize (in category 'accessing') -----
- alignedByteSize
- 	^24 + self baseHeaderSize!

Item was removed:
- ----- Method: NewspeakCogMethodSurrogate32>>nextMethodOrIRCs (in category 'accessing') -----
- nextMethodOrIRCs
- 	^memory unsignedLongAt: address + 21 + baseHeaderSize!

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

Item was removed:
- CogMethodSurrogate64 subclass: #NewspeakCogMethodSurrogate64
- 	instanceVariableNames: ''
- 	classVariableNames: ''
- 	poolDictionaries: ''
- 	category: 'VMMaker-JITSimulation'!

Item was removed:
- ----- Method: NewspeakCogMethodSurrogate64 class>>alignedByteSize (in category 'accessing') -----
- alignedByteSize
- 	^40 + self baseHeaderSize!

Item was removed:
- ----- Method: NewspeakCogMethodSurrogate64>>nextMethodOrIRCs (in category 'accessing') -----
- nextMethodOrIRCs
- 	^memory unsignedLong64At: address + 33 + baseHeaderSize!

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

Item was removed:
- ----- Method: VMStructType class>>changedAccesorsForSurrogate:bytesPerWord: (in category 'code generation') -----
- changedAccesorsForSurrogate: surrogateClass bytesPerWord: bytesPerWord
- 	"Answer the changed accessor methods for the fields of the receiver and the alignedByteSize class method."
- 
- 	"{CogBlockMethod changedAccesorsForSurrogate: CogBlockMethodSurrogate32 bytesPerWord: 4.
- 	 CogMethod changedAccesorsForSurrogate: CogMethodSurrogate32 bytesPerWord: 4.
- 	 CogBlockMethod changedAccesorsForSurrogate: CogBlockMethodSurrogate64 bytesPerWord: 8.
- 	 CogMethod changedAccesorsForSurrogate: CogMethodSurrogate64 bytesPerWord: 8}"
- 
- 	^Dictionary withAll: ((self fieldAccessorSourceFor: surrogateClass bytesPerWord: bytesPerWord) associationsSelect:
- 		[:a| a value ~= a key sourceString])!

Item was added:
+ ----- Method: VMStructType class>>changedAccessorsForSurrogate:bytesPerWord: (in category 'code generation') -----
+ changedAccessorsForSurrogate: surrogateClass bytesPerWord: bytesPerWord
+ 	"Answer the changed accessor methods for the fields of the receiver and the alignedByteSize class method."
+ 
+ 	"{CogBlockMethod changedAccessorsForSurrogate: CogBlockMethodSurrogate32 bytesPerWord: 4.
+ 	 CogMethod changedAccessorsForSurrogate: CogMethodSurrogate32 bytesPerWord: 4.
+ 	 CogBlockMethod changedAccessorsForSurrogate: CogBlockMethodSurrogate64 bytesPerWord: 8.
+ 	 CogMethod changedAccessorsForSurrogate: CogMethodSurrogate64 bytesPerWord: 8}"
+ 
+ 	| dualOrNil |
+ 	dualOrNil := self dualForSurrogateClass: surrogateClass.
+ 	^Dictionary withAll: ((self fieldAccessorSourceFor: surrogateClass bytesPerWord: bytesPerWord) associationsSelect:
+ 		(dualOrNil
+ 			ifNotNil: "The source is changed if neither the class nor its superclass have a method with identical source? No; cuz if the subclass has it and the super doesn't then it has changed; but this is tedious to compute. checkGenerateSurrogate:bytesPerWord: does the computation."
+ 				[[:assoc| | class selector |
+ 				 class := assoc key first.
+ 				 selector := assoc key last.
+ 				 (class sourceCodeAt: selector ifAbsent: ['']) asString ~= assoc value
+ 				 and: [(class superclass sourceCodeAt: selector ifAbsent: ['']) asString ~= assoc value]]]
+ 			ifNil:
+ 				[[:assoc| (assoc key first sourceCodeAt: assoc key last ifAbsent: ['']) asString ~= assoc value]]))!

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 |
+ 		 duals := [self fieldAccessorSourceFor: dual bytesPerWord: (BytesPerWord := bytesPerWord = 4 ifTrue: [8] ifFalse: [4])]
+ 					ensure: [BytesPerWord := oldBytesPerWord].
- 	accessors keysAndValuesDo:
- 		[:mr :source|
- 		source ~= mr sourceStringOrNil ifTrue:
- 			[mr actualClass compile: source classified: #accessing]]
  
+ 		 (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 |
+ 		class := key first.
+ 		selector := key last.
+ 		source ~= (class sourceCodeAt: selector ifAbsent: ['']) asString ifTrue:
+ 			[class compile: source classified: 'accessing generated']]!
- 	"Dictionary withAll: ((self fieldAccessorSourceFor: surrogateClass bytesPerWord: bytesPerWord) associationsSelect:
- 		[:a| a value ~= a key sourceString])"!

Item was added:
+ ----- Method: VMStructType class>>dualForSurrogateClass: (in category 'code generation') -----
+ dualForSurrogateClass: surrogateClass
+ 	"Answer the corresponding class for a word size specific surrogate class, or nil if it is not, or has no dual."
+ 	^surrogateClass name last isDigit ifTrue:
+ 	 	[Smalltalk classNamed: ((surrogateClass name allButLast: 2), ((surrogateClass name endsWith: '32') ifTrue: ['64'] ifFalse: ['32']))]!

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].
  		"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}
- 				at: (MethodReference class: surrogateClass selector: spec first asSymbol)
  					put: (self getter: spec first
  							 bitPosition: bitPosition
  							 bitWidth: spec second
  							 type: (spec at: 3 ifAbsent: []));
+ 				at: {surrogateClass. (spec first, ':') asSymbol}
- 				at: (MethodReference class: surrogateClass selector: (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]).
- 		at: (MethodReference class: surrogateClass class selector: #alignedByteSize)
- 			put: #alignedByteSize
- 				, (String with: Character cr with: Character tab with: $^)
- 				, alignedByteSize printString,
- 				(currentOffset ifNil: [''] ifNotNil: [' + self ', currentOffset]).
  	^methods!

Item was removed:
- ----- Method: VMStructType class>>putAtPut:type:mask:shift:at:on:indent: (in category 'code generation') -----
- putAtPut: accessor type: typeOrNil mask: maskOrNil shift: shift at: startByte on: s indent: indent
- 	"This is the inner part of the ap:put: in a setter, abstracted to eliminate duplication
- 	 given the overrides in CogBlockMethod et al for dual zone write simulation."
- 	s nextPutAll: 'memory';
- 	  crtab: indent; nextPutAll: accessor; print: startByte + 1.
- 	s crtab: indent; nextPutAll: 'put: '.
- 	typeOrNil ifNotNil:
- 		[s nextPut: $(].
- 	maskOrNil ifNotNil:
- 		[s nextPutAll: '((memory '; nextPutAll: accessor; print: startByte + 1;
- 		    nextPutAll: ') bitAnd: '; nextPutAll: maskOrNil hex;
- 		    nextPutAll: ') + '].
- 	s nextPutAll: (typeOrNil
- 					caseOf: {
- 						[nil] -> [shift = 0 ifTrue: ['aValue'] ifFalse: ['(aValue bitShift: ', shift printString, ')']].
- 						[#Boolean] -> ['(aValue ifTrue: [', (1 << shift) printString, '] ifFalse: [0])'] }
- 					otherwise: ['(aValue ifNotNil: [aValue asUnsignedInteger', (shift = 0 ifTrue: [''] ifFalse: [' bitShift: ', shift printString]), '] ifNil: [0])']).
- 	typeOrNil ifNotNil:
- 		[s nextPut: $)]!

Item was added:
+ ----- Method: VMStructType class>>putAtPut:type:mask:shift:on:indent: (in category 'code generation') -----
+ putAtPut: accessor type: typeOrNil mask: maskOrNil shift: shift on: s indent: indent
+ 	"This is the inner part of the ap:put: in a setter, abstracted to eliminate duplication
+ 	 given the overrides in CogBlockMethod et al for dual zone write simulation."
+ 	s nextPutAll: 'memory';
+ 	  crtab: indent; nextPutAll: accessor.
+ 	s crtab: indent; nextPutAll: 'put: '.
+ 	typeOrNil ifNotNil:
+ 		[s nextPut: $(].
+ 	maskOrNil ifNotNil:
+ 		[s nextPutAll: '((memory '; nextPutAll: accessor;
+ 		    nextPutAll: ') bitAnd: '; nextPutAll: maskOrNil hex;
+ 		    nextPutAll: ') + '].
+ 	s nextPutAll: (typeOrNil
+ 					caseOf: {
+ 						[nil] -> [shift = 0 ifTrue: ['aValue'] ifFalse: ['(aValue bitShift: ', shift printString, ')']].
+ 						[#Boolean] -> ['(aValue ifTrue: [', (1 << shift) printString, '] ifFalse: [0])'] }
+ 					otherwise: ['(aValue ifNotNil: [aValue asUnsignedInteger', (shift = 0 ifTrue: [''] ifFalse: [' bitShift: ', shift printString]), '] ifNil: [0])']).
+ 	typeOrNil ifNotNil:
+ 		[s nextPut: $)]!

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 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'.
- 					, 'At: address + '.
- 		(self offsetForInstVar: getter) ifNotNil:
- 			[:offsetExpr| accessor := accessor, offsetExpr, ' + '].
  		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.
- 		s nextPutAll: getter; nextPutAll: ': aValue'.
  		(typeOrNil notNil or: [alignedPowerOf2]) ifFalse:
+ 			[s nextPutAll: 'self assert: (aValue between: 0 and: '; nextPutAll:  ((1 << bitWidth) - 1) hex; nextPutAll: ').'; crtab: 1].
- 			[s crtab: 1; nextPutAll: 'self assert: (aValue between: 0 and: '; nextPutAll:  ((1 << bitWidth) - 1) hex; nextPutAll: ').'].
- 		s crtab: 1.
  		alignedPowerOf2 ifTrue:
  			[s nextPut: $^].
  		self putAtPut: accessor
  			type: typeOrNil
  			mask: (alignedPowerOf2 ifFalse: [mask - ((1 << bitWidth - 1) << shift)])
  			shift: shift
- 			at: startByte
  			on: s
  			indent: 2.
  		alignedPowerOf2 ifFalse:
  			[s nextPut: $.; crtab: 1; nextPutAll: '^aValue']]!



More information about the Vm-dev mailing list