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

commits at source.squeak.org commits at source.squeak.org
Tue Jan 28 03:36:28 UTC 2020


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

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

Name: VMMaker.oscog-eem.2680
Author: eem
Time: 27 January 2020, 7:36:15.399576 pm
UUID: eb86c14b-1baf-43aa-807e-efd5f423bb27
Ancestors: VMMaker.oscog-eem.2679

Cogit:
More progress with dual mapped zone simulaiton.  Hide the dual write within the setters for the CogBlockMethod and subclass surrogates.  To this end extract the core at put generator in setter:bitPosition:bitWidth:type: into putAtPut:type:mask:shift:at:on:indent: so it can be used twice in the CogBlockMethod surrogates.

Adapt the assert for the full block bit in bitAndByteOffsetOfIsFullBlockBitInto: to the dual mapped regime via a dummy class (CogitFaker).

Nuke the unused and obsolete usesTempRegForAbsoluteLoads.

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

Item was changed:
  SystemOrganization addCategory: #'VMMaker-Building'!
  SystemOrganization addCategory: #'VMMaker-Interpreter'!
  SystemOrganization addCategory: #'VMMaker-InterpreterSimulation'!
  SystemOrganization addCategory: #'VMMaker-JIT'!
  SystemOrganization addCategory: #'VMMaker-JITSimulation'!
  SystemOrganization addCategory: #'VMMaker-Multithreading'!
  SystemOrganization addCategory: #'VMMaker-Plugins'!
  SystemOrganization addCategory: #'VMMaker-Plugins-FFI'!
  SystemOrganization addCategory: #'VMMaker-Plugins-IOS'!
  SystemOrganization addCategory: #'VMMaker-PostProcessing'!
  SystemOrganization addCategory: #'VMMaker-SmartSyntaxPlugins'!
  SystemOrganization addCategory: #'VMMaker-SpurMemoryManager'!
  SystemOrganization addCategory: #'VMMaker-SpurMemoryManagerSimulation'!
  SystemOrganization addCategory: #'VMMaker-Support'!
  SystemOrganization addCategory: #'VMMaker-Tests'!
  SystemOrganization addCategory: #'VMMaker-Translation to C'!
  SystemOrganization addCategory: #'VMMaker-Utilities'!
+ SystemOrganization addCategory: #'VMMaker-JIT-Simulation'!

Item was removed:
- ----- Method: CogAbstractInstruction>>usesTempRegForAbsoluteLoads (in category 'testing') -----
- usesTempRegForAbsoluteLoads
- 	"Answer if TempReg is used in absolute memory loads (as it is on x64).  By default answer false, allowing subclasses to override."
- 	<inline: true>
- 	^false!

Item was changed:
  ----- Method: CogBlockMethod class>>initialize (in category 'class initialization') -----
  initialize
  	"CogBlockMethod initialize"
+ 	"self withAllSubclasses do:
+ 		[:cogMethodClass| (cogMethodClass class includesSelector: #initialize) ifTrue: [cogMethodClass initialize]]"
- 	"CogBlockMethod initialize. CogMethod initialize"
  	(Smalltalk classNamed: #CogBlockMethodSurrogate32) ifNotNil:
  		[:cbms32|
  		self checkGenerateSurrogate: cbms32 bytesPerWord: 4].
  	(Smalltalk classNamed: #CogBlockMethodSurrogate64) ifNotNil:
  		[:cbms64|
  		self checkGenerateSurrogate: cbms64 bytesPerWord: 8].
  
  	"see instVarNamesAndTypesForTranslationDo:"
  	CMMaxUsageCount		:= (2 raisedTo: 3) - 1.
  	MaxStackCheckOffset	:= (2 raisedTo: 12) - 1.
  	MaxMethodSize		:= (2 raisedTo: 16) - 1
  
  	"{ CogBlockMethodSurrogate32 selectors reject: [:s| CogBlockMethod includesSelector: s].
  	    CogBlockMethodSurrogate64 selectors reject: [:s| CogBlockMethod includesSelector: s].
  	    CogMethodSurrogate32 selectors reject: [:s| CogMethod includesSelector: s].
  	    CogMethodSurrogate64 selectors reject: [:s| CogMethod includesSelector: s]. }"!

Item was added:
+ ----- 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: 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'.
+ 		s crtab: 1; nextPutAll: '| delta |'.
+ 		(typeOrNil notNil or: [alignedPowerOf2]) ifFalse:
+ 			[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 changed:
  ----- 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: [1] ifFalse: [0]) bitShift: 1))].
  	memory
+ 		unsignedByteAt: address - delta + baseHeaderSize + 3
+ 		put: (((memory unsignedByteAt: address - delta + baseHeaderSize + 3) bitAnd: 16rFD) + ((aValue ifTrue: [1] ifFalse: [0]) bitShift: 1)).
- 		unsignedByteAt: address + baseHeaderSize + 3
- 		put: (((memory unsignedByteAt: address + baseHeaderSize + 3) bitAnd: 16rFD) + ((aValue ifTrue: [1] ifFalse: [0]) bitShift: 1)).
  	^aValue!

Item was changed:
  ----- 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: [1] ifFalse: [0]) bitShift: 2))].
  	memory
+ 		unsignedByteAt: address - delta + baseHeaderSize + 3
+ 		put: (((memory unsignedByteAt: address - delta + baseHeaderSize + 3) bitAnd: 16rFB) + ((aValue ifTrue: [1] ifFalse: [0]) bitShift: 2)).
- 		unsignedByteAt: address + baseHeaderSize + 3
- 		put: (((memory unsignedByteAt: address + baseHeaderSize + 3) bitAnd: 16rFB) + ((aValue ifTrue: [1] ifFalse: [0]) bitShift: 2)).
  	^aValue!

Item was changed:
  ----- 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
- 		unsignedByteAt: address + baseHeaderSize + 1
  		put: aValue!

Item was changed:
  ----- 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: [1] ifFalse: [0]) bitShift: 3))].
  	memory
+ 		unsignedByteAt: address - delta + baseHeaderSize + 2
+ 		put: (((memory unsignedByteAt: address - delta + baseHeaderSize + 2) bitAnd: 16rF7) + ((aValue ifTrue: [1] ifFalse: [0]) bitShift: 3)).
- 		unsignedByteAt: address + baseHeaderSize + 2
- 		put: (((memory unsignedByteAt: address + baseHeaderSize + 2) bitAnd: 16rF7) + ((aValue ifTrue: [1] ifFalse: [0]) bitShift: 3)).
  	^aValue!

Item was changed:
  ----- 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.
- 		unsignedByteAt: address + baseHeaderSize + 2
- 		put: ((memory unsignedByteAt: address + baseHeaderSize + 2) bitAnd: 16rF8) + aValue.
  	^aValue!

Item was changed:
  ----- 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).
- 		unsignedByteAt: address + baseHeaderSize + 2
- 		put: ((memory unsignedByteAt: address + baseHeaderSize + 2) bitAnd: 16r1F) + (aValue bitShift: 5).
  	^aValue!

Item was changed:
  ----- 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])).
- 		unsignedByteAt: address + baseHeaderSize + 3
- 		put: (((memory unsignedByteAt: address + baseHeaderSize + 3) bitAnd: 16rFE) + (aValue ifTrue: [1] ifFalse: [0])).
  	^aValue!

Item was changed:
  ----- 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: [1] ifFalse: [0]) bitShift: 4))].
  	memory
+ 		unsignedByteAt: address - delta + baseHeaderSize + 2
+ 		put: (((memory unsignedByteAt: address - delta + baseHeaderSize + 2) bitAnd: 16rEF) + ((aValue ifTrue: [1] ifFalse: [0]) bitShift: 4)).
- 		unsignedByteAt: address + baseHeaderSize + 2
- 		put: (((memory unsignedByteAt: address + baseHeaderSize + 2) bitAnd: 16rEF) + ((aValue ifTrue: [1] ifFalse: [0]) bitShift: 4)).
  	^aValue!

Item was changed:
  ----- 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
- 		unsignedShortAt: address + 1
  		put: aValue!

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

Item was changed:
  ----- 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).
- 		unsignedShortAt: address + baseHeaderSize + 3
- 		put: ((memory unsignedShortAt: address + baseHeaderSize + 3) bitAnd: 16rF) + (aValue bitShift: 4).
  	^aValue!

Item was changed:
  ----- 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
- 		unsignedShortAt: address + 3
  		put: aValue!

Item was changed:
  ----- 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: [1] ifFalse: [0]) bitShift: 1))].
  	memory
+ 		unsignedByteAt: address - delta + baseHeaderSize + 3
+ 		put: (((memory unsignedByteAt: address - delta + baseHeaderSize + 3) bitAnd: 16rFD) + ((aValue ifTrue: [1] ifFalse: [0]) bitShift: 1)).
- 		unsignedByteAt: address + baseHeaderSize + 3
- 		put: (((memory unsignedByteAt: address + baseHeaderSize + 3) bitAnd: 16rFD) + ((aValue ifTrue: [1] ifFalse: [0]) bitShift: 1)).
  	^aValue!

Item was changed:
  ----- 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: [1] ifFalse: [0]) bitShift: 2))].
  	memory
+ 		unsignedByteAt: address - delta + baseHeaderSize + 3
+ 		put: (((memory unsignedByteAt: address - delta + baseHeaderSize + 3) bitAnd: 16rFB) + ((aValue ifTrue: [1] ifFalse: [0]) bitShift: 2)).
- 		unsignedByteAt: address + baseHeaderSize + 3
- 		put: (((memory unsignedByteAt: address + baseHeaderSize + 3) bitAnd: 16rFB) + ((aValue ifTrue: [1] ifFalse: [0]) bitShift: 2)).
  	^aValue!

Item was changed:
  ----- 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
- 		unsignedByteAt: address + baseHeaderSize + 1
  		put: aValue!

Item was changed:
  ----- 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: [1] ifFalse: [0]) bitShift: 3))].
  	memory
+ 		unsignedByteAt: address - delta + baseHeaderSize + 2
+ 		put: (((memory unsignedByteAt: address - delta + baseHeaderSize + 2) bitAnd: 16rF7) + ((aValue ifTrue: [1] ifFalse: [0]) bitShift: 3)).
- 		unsignedByteAt: address + baseHeaderSize + 2
- 		put: (((memory unsignedByteAt: address + baseHeaderSize + 2) bitAnd: 16rF7) + ((aValue ifTrue: [1] ifFalse: [0]) bitShift: 3)).
  	^aValue!

Item was changed:
  ----- 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.
- 		unsignedByteAt: address + baseHeaderSize + 2
- 		put: ((memory unsignedByteAt: address + baseHeaderSize + 2) bitAnd: 16rF8) + aValue.
  	^aValue!

Item was changed:
  ----- 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).
- 		unsignedByteAt: address + baseHeaderSize + 2
- 		put: ((memory unsignedByteAt: address + baseHeaderSize + 2) bitAnd: 16r1F) + (aValue bitShift: 5).
  	^aValue!

Item was changed:
  ----- 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])).
- 		unsignedByteAt: address + baseHeaderSize + 3
- 		put: (((memory unsignedByteAt: address + baseHeaderSize + 3) bitAnd: 16rFE) + (aValue ifTrue: [1] ifFalse: [0])).
  	^aValue!

Item was changed:
  ----- 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: [1] ifFalse: [0]) bitShift: 4))].
  	memory
+ 		unsignedByteAt: address - delta + baseHeaderSize + 2
+ 		put: (((memory unsignedByteAt: address - delta + baseHeaderSize + 2) bitAnd: 16rEF) + ((aValue ifTrue: [1] ifFalse: [0]) bitShift: 4)).
- 		unsignedByteAt: address + baseHeaderSize + 2
- 		put: (((memory unsignedByteAt: address + baseHeaderSize + 2) bitAnd: 16rEF) + ((aValue ifTrue: [1] ifFalse: [0]) bitShift: 4)).
  	^aValue!

Item was changed:
  ----- 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
- 		unsignedShortAt: address + 1
  		put: aValue!

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

Item was changed:
  ----- 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).
- 		unsignedShortAt: address + baseHeaderSize + 3
- 		put: ((memory unsignedShortAt: address + baseHeaderSize + 3) bitAnd: 16rF) + (aValue bitShift: 4).
  	^aValue!

Item was changed:
  ----- 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
- 		unsignedShortAt: address + 3
  		put: aValue!

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 + 1 put: aValue]
+ 			ifFalse: [memory longAt: address + 1 put: aValue]].
  	^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]!

Item was changed:
  ----- 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
- 		unsignedShortAt: address + baseHeaderSize + 7
  		put: aValue!

Item was changed:
  ----- 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
- 		unsignedShortAt: address + baseHeaderSize + 5
  		put: aValue!

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

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

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

Item was changed:
  ----- Method: CogMethodSurrogate64>>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
- 		unsignedShortAt: address + baseHeaderSize + 7
  		put: aValue!

Item was changed:
  ----- Method: CogMethodSurrogate64>>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
- 		unsignedShortAt: address + baseHeaderSize + 5
  		put: aValue!

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

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

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

Item was changed:
  ----- Method: CogMethodZone>>addToOpenPICList: (in category 'accessing') -----
  addToOpenPICList: anOpenPIC
  	<var: #anOpenPIC type: #'CogMethod *'>
  	self assert: anOpenPIC cmType = CMOpenPIC.
  	self assert: (openPICList == nil
  				or: [openPICList cmType = CMOpenPIC]).
+ 	cogit assertValidDualZoneWriteAddress: anOpenPIC.
  	anOpenPIC nextOpenPIC: openPICList asUnsignedInteger.
+ 	openPICList := cogit cCoerceSimple: anOpenPIC asUnsignedInteger - cogit codeToDataDelta to: #'CogMethod *'.
+ 	self cCode: '' inSmalltalk: [self deny: openPICList isInteger]!
- 	openPICList := anOpenPIC - 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'].
  	youngReferrers := youngReferrers - objectMemory wordSize.
  	cogit
+ 		codeLongAt: youngReferrers + cogit codeToDataDelta
- 		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.
+ 		 writableMethod := cogit cCoerceSimple: cogMethod asUnsignedInteger - cogit codeToDataDelta
+ 								to: #'CogMethod *'.
+ 		 writableMethod cmRefersToYoung: true.
- 		 cogMethod cmRefersToYoung: true.
  		 self addToYoungReferrers: cogMethod]!

Item was changed:
  ----- Method: CogObjectRepresentationFor64BitSpur>>bitAndByteOffsetOfIsFullBlockBitInto: (in category 'in-line cacheing') -----
  bitAndByteOffsetOfIsFullBlockBitInto: aBlock
  	<inline: true>
  	"This supplies the bitmask for the isFullBlock bit, and the offset of the byte containing
  	 that bit in a CogMethod header to aBlock.  We don't have named variables holding this
  	 offset.  The following assert tests whether the values are correct by creating a surrogate
  	 on an empty ByteArray, setting the bit, and checking that the expected values are set
  	 in the ByteArray."
  	self cCode: [] inSmalltalk:
  		[| m |
  		m := ByteArray new: 16.
  		CogBlockMethodSurrogate64 new
+ 			at: 0 memory: m headerSize: 8 cogit: CogitFaker new;
- 			at: 0 memory: m headerSize: 8 cogit: nil;
  			cpicHasMNUCaseOrCMIsFullBlock: true.
  		self assert: m = #[0 0 0 0 0 0 0 0 0 16 0 0 0 0 0 0].
  		self assert: (m at: objectMemory baseHeaderSize + 2) = 16].
  	aBlock value: 16 value: objectMemory baseHeaderSize + 1 "zero-relative"!

Item was changed:
  ----- Method: CogSistaMethodSurrogate32>>counters: (in category 'accessing') -----
  counters: 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
- 		unsignedLongAt: address + baseHeaderSize + 21
  		put: aValue!

Item was changed:
  ----- Method: CogSistaMethodSurrogate64>>counters: (in category 'accessing') -----
  counters: 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
- 		unsignedLong64At: address + baseHeaderSize + 33
  		put: aValue!

Item was removed:
- ----- Method: CogX64Compiler>>usesTempRegForAbsoluteLoads (in category 'testing') -----
- usesTempRegForAbsoluteLoads
- 	"Answer if TempReg is used in absolute memory loads (as it is on x64).  By default answer false, allowing subclasses to override."
- 	<inline: true>
- 	^true!

Item was changed:
  ----- Method: Cogit>>armPrintDualZoneAnomalies (in category 'debugging') -----
  armPrintDualZoneAnomalies
  	<doNotGenerate>
  	| badRangeStart |
  	codeToDataDelta > 0 ifTrue:
  		[codeBase to: methodZone zoneEnd - 4 by: 4 do:
  			[:address|
  			(objectMemory long32At: address) = (objectMemory long32At: address + codeToDataDelta)
  				ifTrue:
  					[badRangeStart ifNotNil:
  						[coInterpreter transcript
+ 							ensureCr;
  							nextPutAll: 'anomaly '; nextPutAll: badRangeStart hex; nextPutAll: ' to: '; nextPutAll: (address - 4) hex;
  							nextPutAll: ' vs ';
  							nextPutAll: (badRangeStart + codeToDataDelta) hex; nextPutAll: ' to: '; nextPutAll: (address + codeToDataDelta - 4) hex;
  							cr; flush].
  					 badRangeStart := nil]
  				ifFalse:
  					[badRangeStart ifNil: [badRangeStart := address]]].
  		badRangeStart ifNotNil:
  			[coInterpreter transcript
+ 				ensureCr;
  				nextPutAll: 'anomaly '; nextPutAll: badRangeStart hex; nextPutAll: ' to: '; nextPutAll: (methodZone zoneEnd - 4) hex;
  				nextPutAll: ' vs ';
  				nextPutAll: (badRangeStart + codeToDataDelta) hex; nextPutAll: ' to: '; nextPutAll: (methodZone zoneEnd + codeToDataDelta - 4) hex;
  				cr; flush]].
  	^nil!

Item was changed:
  ----- Method: Cogit>>assertValidDualZone (in category 'debugging') -----
  assertValidDualZone
  	"{self firstInvalidDualZoneAddress. self firstInvalidDualZoneAddress + codeToDataDelta }"
  	"{self firstInvalidDualZoneAddress hex. (self firstInvalidDualZoneAddress + codeToDataDelta) hex }"
+ 	"{(objectMemory longAt: self firstInvalidDualZoneAddress) hex. (objectMemory longAt: self firstInvalidDualZoneAddress + codeToDataDelta) hex }"
  	"self armDisassembleDualZoneAnomalies"
  	"self armPrintDualZoneAnomalies"
  	self cCode: ''
  		inSmalltalk: [self assert: self firstInvalidDualZoneAddress isNil]!

Item was added:
+ ----- Method: Cogit>>assertValidDualZoneReadAddress: (in category 'simulation only') -----
+ assertValidDualZoneReadAddress: address
+ 	"Make sure that a surrogate is trying to read from the read/executable part of the code zone(s)"
+ 	self assert: (address asInteger between: methodZoneBase and: methodZone zoneEnd)!

Item was added:
+ ----- Method: Cogit>>assertValidDualZoneWriteAddress: (in category 'simulation only') -----
+ assertValidDualZoneWriteAddress: address
+ 	"Make sure that a surrogate is trying to write to the writable part of the code zone(s)"
+ 	self assert: (address asInteger - codeToDataDelta between: methodZoneBase and: methodZone zoneEnd)!

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 writablePIC |
- 	| pc entryPoint targetMethod targets tags methods used |
  	<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."
- 				[i = 1 ifTrue: [^true]. "cannot filter out the first entry cuz classTag is at pont 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].
+ 
+ 	writablePIC := self cCoerceSimple: cPIC asUnsignedInteger + codeToDataDelta to: #'CogMethod *'.
+ 	writablePIC cPICNumCases: used.
- 	cPIC 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"
- 	"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 added:
+ ----- Method: Cogit>>codeMemcpy:_:_: (in category 'generate machine code') -----
+ codeMemcpy: dest _: src _: bytes
+ 	"production uses the macro..."
+ 	<cmacro: '(dest,src,bytes) memcpy(dest,src,bytes)'>
+ 	self codeWriteBreakpoint: dest.
+ 	"simulation writes twice if simulating dual mapping..."
+ 	codeToDataDelta ~= 0 ifTrue:
+ 		[objectMemory memcpy: dest + codeToDataDelta _: src _: bytes].
+ 	objectMemory memcpy: dest _: src _: bytes!

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 writablePIC |
- 	| operand target address |
  
  	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"
+ 	writablePIC := self cCoerceSimple: cPIC asUnsignedInteger + codeToDataDelta to: #'CogMethod *'.
+ 	writablePIC cPICNumCases: cPIC cPICNumCases + 1.
+ 	self assertValidDualZone!
- 	cPIC cPICNumCases: cPIC cPICNumCases + 1.
- 	^0!

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 |
- 	| startAddress writableMethod |
  	((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 cCoerceSimple: startAddress + codeToDataDelta to: #'CogMethod *'.
- 	writableMethod := self cCoerceSimple: startAddress + codeToDataDelta to: #'CogMethod *'.
  	"memcpy the prototype across to our allocated space; because anything else would be silly"
+ 	self codeMemcpy: writablePIC
- 	objectMemory
- 		memcpy: writableMethod
  		_: (self cCoerceSimple: cPICPrototype to: #'CogMethod *')
  		_: closedPICSize.
+ 
- 	
- 	self configureMNUCPIC: writableMethod
- 		methodOperand: methodOperand
- 		numArgs: numArgs
- 		delta: startAddress - cPICPrototype.
  	self
+ 		fillInCPICHeader: writablePIC
- 		fillInCPICHeader: writableMethod
  		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 assertValidDualZone.
+ 	backEnd flushICacheFrom: startAddress to: startAddress + closedPICSize.
+ 
+ 	^actualPIC!
- 	^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 |
- 	| startAddress writableMethod |
  	(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 cCoerceSimple: startAddress + codeToDataDelta to: #'CogMethod *'.
- 	writableMethod := self cCoerceSimple: startAddress + codeToDataDelta to: #'CogMethod *'.
  	"memcpy the prototype across to our allocated space; because anything else would be silly"
+ 	self codeMemcpy: writablePIC
- 	objectMemory
- 		memcpy: writableMethod
  		_: (self cCoerceSimple: cPICPrototype to: #'CogMethod *')
  		_: closedPICSize.
- 	
- 	self configureCPIC: writableMethod
- 		Case0: case0CogMethod
- 		Case1Method: case1MethodOrNil
- 		tag: case1Tag
- 		isMNUCase: isMNUCase
- 		numArgs: numArgs
- 		delta: startAddress - cPICPrototype .
  
  	self
+ 		fillInCPICHeader: writablePIC
- 		fillInCPICHeader: writableMethod
  		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 cCode: '' inSmalltalk:
- 		[codeToDataDelta > 0 ifTrue:
- 			[objectMemory memmove: startAddress _: writableMethod asUnsignedInteger _: closedPICSize]].
  	self assertValidDualZone.
+ 	backEnd flushICacheFrom: startAddress to: startAddress + closedPICSize.
+ 
+ 	^actualPIC!
- 	^self cCoerceSimple: startAddress to: #'CogMethod *'!

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 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])]!
- 								ifFalse: [blockStart stackCheckLabel address - blockStart fakeHeader address]).
- 		self simulateDualCodeZoneWriteFor: blockHeader]!

Item was changed:
  ----- Method: Cogit>>fillInCPICHeader:numArgs:numCases:hasMNUCase:selector: (in category 'generate machine code') -----
  fillInCPICHeader: pic numArgs: numArgs numCases: numCases hasMNUCase: hasMNUCase selector: selector
  	"Fill in the header for the ClosedPIC pic.  This may be located at the writable mapping."
  	<var: #pic type: #'CogMethod *'>
  	<inline: true>
  	self assert: (objectMemory isYoung: selector) not.
  	pic cmType: CMClosedPIC.
  	pic objectHeader: 0.
  	pic blockSize: closedPICSize.
  	pic methodObject: 0.
  	pic methodHeader: 0.
  	pic selector: selector.
  	pic cmNumArgs: numArgs.
  	pic cmHasMovableLiteral: false.
  	pic cmRefersToYoung: false.
  	pic cmUsageCount: self initialClosedPICUsageCount.
  	pic cpicHasMNUCase: hasMNUCase.
  	pic cPICNumCases: numCases.
  	pic blockEntryOffset: 0.
  	self assert: pic cmType = CMClosedPIC.
  	self assert: pic selector = selector.
  	self assert: pic cmNumArgs = numArgs.
  	self assert: pic cPICNumCases = numCases.
- 	self assert: (backEnd callTargetFromReturnAddress: pic asInteger + missOffset) = (self picAbortTrampolineFor: numArgs).
  	self assert: closedPICSize = (methodZone roundUpLength: closedPICSize).
- 	backEnd flushICacheFrom: pic asUnsignedInteger - codeToDataDelta to: pic asUnsignedInteger - codeToDataDelta + closedPICSize.
  	self maybeEnableSingleStep
  	"No simulateDualCodeZoneWriteFor:; we do all the simulated copying in the sender..."!

Item was changed:
  ----- Method: Cogit>>fillInMethodHeader:size:selector: (in category 'generate machine code') -----
  fillInMethodHeader: method size: size selector: selector
  	"Fill in the header for theCogMehtod method.  This may be located at the writable mapping."
  	<var: #method type: #'CogMethod *'>
  	| originalMethod rawHeader actualMethodLocation |
  	<var: #originalMethod type: #'CogMethod *'>
  	actualMethodLocation := method asUnsignedInteger - codeToDataDelta.
  	method cmType: CMMethod.
  	method objectHeader: objectMemory nullHeaderForMachineCodeMethod.
  	method blockSize: size.
  	method methodObject: methodObj.
  	rawHeader := coInterpreter rawHeaderOf: methodObj.
  	"If the method has already been cogged (e.g. Newspeak accessors) then
  	 leave the original method attached to its cog method, but get the right header."
  	(coInterpreter isCogMethodReference: rawHeader)
  		ifTrue:
  			[originalMethod := self cCoerceSimple: rawHeader to: #'CogMethod *'.
  			self assert: originalMethod blockSize = size.
  			self assert: methodHeader = originalMethod methodHeader.
  			NewspeakVM ifTrue:
  				[methodZone addToUnpairedMethodList: method]]
  		ifFalse:
  			[coInterpreter rawHeaderOf: methodObj put: actualMethodLocation.
  			 NewspeakVM ifTrue:
  				[method nextMethodOrIRCs: theIRCs]].
  	method methodHeader: methodHeader.
  	method selector: selector.
  	method cmNumArgs: (coInterpreter argumentCountOfMethodHeader: methodHeader).
  	method cmHasMovableLiteral: hasMovableLiteral.
  	(method cmRefersToYoung: hasYoungReferent) ifTrue:
  		[methodZone addToYoungReferrers: method].
  	method cmUsageCount: self initialMethodUsageCount.
  	method cpicHasMNUCase: false.
  	method cmUsesPenultimateLit: maxLitIndex >= ((objectMemory literalCountOfMethodHeader: methodHeader) - 2).
  	method blockEntryOffset: (blockEntryLabel notNil
  								ifTrue: [blockEntryLabel address - actualMethodLocation]
  								ifFalse: [0]).
  	"This can be an error check since a large stackCheckOffset is caused by compiling
  	 a machine-code primitive, and hence depends on the Cogit, not the input method."
  	needsFrame ifTrue:
  		[stackCheckLabel address - actualMethodLocation <= MaxStackCheckOffset ifFalse:
  			[self error: 'too much code for stack check offset']].
  	method stackCheckOffset: (needsFrame
  								ifTrue: [stackCheckLabel address - actualMethodLocation]
  								ifFalse: [0]).
- 	self simulateDualCodeZoneWriteFor: method.
  	self assert: (backEnd callTargetFromReturnAddress: actualMethodLocation + missOffset)
  				= (self methodAbortTrampolineFor: method cmNumArgs).
  	self assert: size = (methodZone roundUpLength: size).
  	backEnd flushICacheFrom: actualMethodLocation to: actualMethodLocation + size.
  	self assertValidDualZone.
  	self maybeEnableSingleStep!

Item was changed:
  ----- Method: Cogit>>fillInOPICHeader:numArgs:selector: (in category 'generate machine code') -----
  fillInOPICHeader: pic numArgs: numArgs selector: selector
  	"Fill in the header for the OpenPIC pic.  This may be located at the writable mapping."
  	<var: #pic type: #'CogMethod *'>
  	<inline: true>
  	pic cmType: CMOpenPIC.
  	pic objectHeader: 0.
  	pic blockSize: openPICSize.
  	"pic methodObject: 0.""This is also the nextOpenPIC link so don't initialize it"
  	methodZone addToOpenPICList: pic.
  	pic methodHeader: 0.
  	pic selector: selector.
  	pic cmNumArgs: numArgs.
  	pic cmHasMovableLiteral: (objectMemory isNonImmediate: selector).
  	(pic cmRefersToYoung: (objectMemory isYoung: selector)) ifTrue:
  		[methodZone addToYoungReferrers: pic].
  	pic cmUsageCount: self initialOpenPICUsageCount.
  	pic cpicHasMNUCase: false.
  	pic cPICNumCases: 0.
  	pic blockEntryOffset: 0.
  	self assert: pic cmType = CMOpenPIC.
  	self assert: pic selector = selector.
  	self assert: pic cmNumArgs = numArgs.
+ 	self assert: (backEnd callTargetFromReturnAddress: pic asInteger - codeToDataDelta + missOffset) = (self picAbortTrampolineFor: numArgs).
- 	self assert: (backEnd callTargetFromReturnAddress: pic asInteger + missOffset) = (self picAbortTrampolineFor: numArgs).
  	self assert: openPICSize = (methodZone roundUpLength: openPICSize).
  	backEnd flushICacheFrom: pic asUnsignedInteger - codeToDataDelta to: pic asUnsignedInteger - codeToDataDelta + openPICSize.
- 	self simulateDualCodeZoneWriteFor: pic.
  	self assertValidDualZone.
  	self maybeEnableSingleStep!

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.
+ 	writableMethod := self cCoerceSimple: cogMethod asUnsignedInteger + codeToDataDelta to: #'CogMethod *'.
+ 	writableMethod selector: aSelectorOop.
- 	cogMethod selector: aSelectorOop.
  	(objectMemory isYoung: aSelectorOop) ifTrue:
  		[methodZone ensureInYoungReferrers: cogMethod]!

Item was removed:
- ----- Method: Cogit>>simulateDualCodeZoneWriteFor: (in category 'simulation only') -----
- simulateDualCodeZoneWriteFor: method
- 	self cCode: '' inSmalltalk:
- 		[codeToDataDelta ~= 0 ifTrue:
- 			[objectMemory memmove: method asInteger - codeToDataDelta _: method asInteger _: method class alignedByteSize]]!

Item was added:
+ Object subclass: #CogitFaker
+ 	instanceVariableNames: ''
+ 	classVariableNames: ''
+ 	poolDictionaries: ''
+ 	category: 'VMMaker-JIT-Simulation'!

Item was added:
+ ----- Method: CogitFaker>>assertValidDualZoneWriteAddress: (in category 'accessing') -----
+ assertValidDualZoneWriteAddress: address!

Item was added:
+ ----- Method: CogitFaker>>codeToDataDelta (in category 'accessing') -----
+ codeToDataDelta
+ 	^0!

Item was changed:
  ----- 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
- 		unsignedLongAt: address + baseHeaderSize + 21
  		put: aValue!

Item was changed:
  ----- 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
- 		unsignedLong64At: address + baseHeaderSize + 33
  		put: aValue!

Item was added:
+ ----- 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."
+ 	| expr |
+ 	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: ') + '].
+ 	expr := typeOrNil caseOf: {
+ 					[nil] -> ['aValue'].
+ 					[#Boolean] -> ['(aValue ifTrue: [1] ifFalse: [0])'] }
+ 				otherwise: ['(aValue ifNotNil: [aValue asUnsignedInteger] ifNil: [0])'].
+ 	shift = 0
+ 		ifTrue: [s nextPutAll: expr]
+ 		ifFalse: [s nextPut: $(; nextPutAll: expr; nextPutAll: ' bitShift: '; print: shift; nextPut: $)].
+ 	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 |
- 		[:s| | startByte endByte shift alignedPowerOf2 accessor mask expr |
  		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: 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'.
  		(typeOrNil notNil or: [alignedPowerOf2]) ifFalse:
  			[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.
- 		s nextPutAll: 'memory';
- 		  crtab: 2; nextPutAll: accessor; print: startByte + 1.
- 		s crtab: 2; nextPutAll: 'put: '.
- 		typeOrNil ifNotNil:
- 			[s nextPut: $(].
  		alignedPowerOf2 ifFalse:
- 			[s nextPutAll: '((memory '; nextPutAll: accessor; print: startByte + 1;
- 			    nextPutAll: ') bitAnd: '; nextPutAll: (mask - ((1 << bitWidth - 1) << shift)) hex;
- 			    nextPutAll: ') + '].
- 		expr := typeOrNil caseOf: {
- 						[nil] -> ['aValue'].
- 						[#Boolean] -> ['(aValue ifTrue: [1] ifFalse: [0])'] }
- 					otherwise: ['(aValue ifNotNil: [aValue asUnsignedInteger] ifNil: [0])'].
- 		shift = 0
- 			ifTrue:
- 				[s nextPutAll: expr]
- 			ifFalse:
- 				[s nextPut: $(; nextPutAll: expr; nextPutAll: ' bitShift: '; print: shift; nextPut: $)].
- 		typeOrNil notNil ifTrue:
- 			[s nextPut: $)].
- 		alignedPowerOf2 ifFalse:
  			[s nextPut: $.; crtab: 1; nextPutAll: '^aValue']]!



More information about the Vm-dev mailing list