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

commits at source.squeak.org commits at source.squeak.org
Wed Jan 29 18:33:14 UTC 2020


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

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

Name: VMMaker.oscog-eem.2686
Author: eem
Time: 29 January 2020, 10:33:01.901821 am
UUID: d013b384-4d10-4b6e-bded-6dafcf0b455e
Ancestors: VMMaker.oscog-eem.2685

Cogit: We're back in business.  Get the dual mapped zone scheme to a point where it is again worth trying the production VM on ARMv8 in a linux that disallows any form of code execution in writable memory.

Use writableMethodFor: when updating various lists during code compaction, or when adding methods to the youngReferrers list.

Was able to evaluate 3+4! TestRunner open! (Delay forMilliseconds: 5) wait! correctly with DUAL_MAPPED_CODE_ZONE true desiredCogCodeSize 262144, which causes constant code compactions.

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

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

Item was changed:
  ----- Method: CogMethodZone>>compactCompiledCode (in category 'compaction') -----
  compactCompiledCode
+ 	| objectHeaderValue source dest writableVersion bytes |
- 	| objectHeaderValue source dest bytes |
  	<var: #source type: #'CogMethod *'>
  	<var: #dest type: #'CogMethod *'>
  	compactionInProgress := true.
  	methodCount := 0.
  	objectHeaderValue := objectMemory nullHeaderForMachineCodeMethod.
  	source := coInterpreter cCoerceSimple: baseAddress to: #'CogMethod *'.
  	self voidOpenPICList. "The(se) list(s) will be rebuilt with the current live set"
  	self voidUnpairedMethodList.
  	[source < self limitZony
  	 and: [source cmType ~= CMFree]] whileTrue:
  		[self assert: (cogit cogMethodDoesntLookKosher: source) = 0.
+ 		 writableVersion := cogit writableMethodFor: source. 
+ 		 writableVersion objectHeader: objectHeaderValue.
- 		 source objectHeader: objectHeaderValue.
  		 source cmUsageCount > 0 ifTrue:
+ 			[writableVersion cmUsageCount: source cmUsageCount // 2].
- 			[source cmUsageCount: source cmUsageCount // 2].
  		 self maybeLinkOnUnpairedMethodList: source.
+ 		 self clearSavedPICUsageCount: writableVersion.
- 		 self clearSavedPICUsageCount: source.
  		 source cmType = CMOpenPIC ifTrue:
+ 			[self addToOpenPICList: writableVersion].
- 			[self addToOpenPICList: source].
  		 methodCount := methodCount + 1.
  		 source := self methodAfter: source].
  	source >= self limitZony ifTrue:
  		[^self halt: 'no free methods; cannot compact.'].
  	dest := source.
  	[source < self limitZony] whileTrue:
  		[self assert: (cogit maybeFreeCogMethodDoesntLookKosher: source) = 0.
  		 bytes := source blockSize.
  		 source cmType ~= CMFree ifTrue:
  			[methodCount := methodCount + 1.
+ 			 cogit codeMemmove: dest _: source _: bytes.
+ 			 (writableVersion := cogit writableMethodFor: dest) objectHeader: objectHeaderValue.
- 			 objectMemory memmove: dest _: source _: bytes.
- 			 dest objectHeader: objectHeaderValue.
  			 dest cmType = CMMethod
  				ifTrue:
  					["For non-Newspeak there should be a one-to-one mapping between bytecoded and
  					  cog methods.  For Newspeak not necessarily, but only for anonymous accessors."
  					"Only update the original method's header if it is referring to this CogMethod."
  					 (coInterpreter rawHeaderOf: dest methodObject) asInteger = source asInteger
  						ifTrue:
  							[coInterpreter rawHeaderOf: dest methodObject put: dest asInteger]
  						ifFalse:
  							[self assert: (cogit noAssertMethodClassAssociationOf: dest methodObject) = objectMemory nilObject.
  							 self linkOnUnpairedMethodList: dest]]
  				ifFalse:
+ 					[self clearSavedPICUsageCount: writableVersion.
- 					[self clearSavedPICUsageCount: dest.
  					 dest cmType = CMOpenPIC ifTrue:
+ 						[self addToOpenPICList: writableVersion]].
- 						[self addToOpenPICList: dest]].
  			 dest cmUsageCount > 0 ifTrue:
+ 				[writableVersion cmUsageCount: dest cmUsageCount // 2].
- 				[dest cmUsageCount: dest cmUsageCount // 2].
  			 dest := coInterpreter cCoerceSimple: dest asUnsignedInteger + bytes to: #'CogMethod *'].
  		 source := coInterpreter cCoerceSimple: source asUnsignedInteger + bytes to: #'CogMethod *'].
  	mzFreeStart := dest asUnsignedInteger.
  	methodBytesFreedSinceLastCompaction := 0.
  	compactionInProgress := false!

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

Item was changed:
  ----- Method: CogMethodZone>>freeMethod: (in category 'compaction') -----
  freeMethod: cogMethod
  	<api>
  	<var: #cogMethod type: #'CogMethod *'>
  	<inline: false>
  	| writableMethod |
  	self assert: cogMethod cmType ~= CMFree.
  	self assert: (cogit cogMethodDoesntLookKosher: cogMethod) = 0.
  	cogMethod cmType = CMMethod ifTrue:
  		["For non-Newspeak there should be a one-to-one mapping between bytecoded and
  		  cog methods.  For Newspeak not necessarily, but only for anonymous accessors."
  		"Only reset the original method's header if it is referring to this CogMethod."
  		 (coInterpreter rawHeaderOf: cogMethod methodObject) asInteger = cogMethod asInteger
  			ifTrue:
  				[coInterpreter rawHeaderOf: cogMethod methodObject put: cogMethod methodHeader.
  				 NewspeakVM ifTrue:
  					[(objectRepresentation canPinObjects and: [cogMethod nextMethodOrIRCs > self zoneEnd]) ifTrue:
  						[objectRepresentation freeIRCs: cogMethod nextMethodOrIRCs]]]
  			ifFalse:
  				[self cCode: [self assert: (cogit noAssertMethodClassAssociationOf: cogMethod methodObject) = objectMemory nilObject]
  					inSmalltalk: [self assert: ((cogit noAssertMethodClassAssociationOf: cogMethod methodObject) = objectMemory nilObject
  											or: [coInterpreter isKindOf: CurrentImageCoInterpreterFacade])].
  				 NewspeakVM ifTrue:
  					[self removeFromUnpairedMethodList: cogMethod]].
  		 cogit maybeFreeCountersOf: cogMethod].
  	cogMethod cmType = CMOpenPIC ifTrue:
  		[self removeFromOpenPICList: cogMethod].
+ 	writableMethod := cogit writableMethodFor: cogMethod.
- 	writableMethod := self writableMethodFor: cogMethod.
  	writableMethod cmRefersToYoung: false.
  	writableMethod cmType: CMFree.
  	methodBytesFreedSinceLastCompaction := methodBytesFreedSinceLastCompaction
  												+ cogMethod blockSize!

Item was changed:
  ----- Method: CogMethodZone>>maybeLinkOnUnpairedMethodList: (in category 'compaction') -----
  maybeLinkOnUnpairedMethodList: cogMethod
  	NewspeakVM ifTrue:
  		[(cogMethod cmType = CMMethod
  		  and: [(coInterpreter rawHeaderOf: cogMethod methodObject) asInteger ~= cogMethod asInteger]) ifTrue:
+ 			[(cogit writableMethodFor: cogMethod) nextMethodOrIRCs: unpairedMethodList.
- 			[cogMethod nextMethodOrIRCs: unpairedMethodList.
  			 unpairedMethodList := cogMethod asUnsignedInteger]]!

Item was changed:
  ----- Method: CogMethodZone>>planCompaction (in category 'compaction') -----
  planCompaction
  	"Some methods have been freed.  Compute how much each survivor needs to
  	 move during the ensuing compaction and record it in the objectHeader field.
  
  	 For Sista, where we want PICs to last so they can be observed, we need to keep PICs unless
  	 they are definitely unused.  So we need to identify unused PICs.  So in planCompact, zero the
  	 usage counts of all PICs, saving the actual usage count in blockEntryOffset.  Then in
  	 relocateMethodsPreCompaction (actually in relocateIfCallOrMethodReference:mcpc:delta:)
  	 restore the usage counts of used PICs.  Finally in compactCompiledCode, clear the blockEntryOffset
  	 of the unused PICs; they will then have a zero count and be reclaimed in the next code compaction."
  	| delta cogMethod |
  	<var: #cogMethod type: #'CogMethod *'>
  	delta := 0.
  	cogMethod := cogit cCoerceSimple: baseAddress to: #'CogMethod *'.
  	[cogMethod asUnsignedInteger < mzFreeStart] whileTrue:
  		[cogMethod cmType = CMFree
  			ifTrue: [delta := delta - cogMethod blockSize]
  			ifFalse:
  				[self assert: (cogit cogMethodDoesntLookKosher: cogMethod) = 0.
+ 				 (cogit writableMethodFor: cogMethod) objectHeader: delta.
- 				 cogMethod objectHeader: delta.
  				 SistaVM ifTrue:
  					[self savePICUsageCount: cogMethod]].
  		 cogMethod := self methodAfter: cogMethod]!

Item was changed:
  ----- Method: CogMethodZone>>pruneYoungReferrers (in category 'young referers') -----
  pruneYoungReferrers
  	| source dest next |
  	<api>
  	<var: #source type: #usqInt>
  	<var: #dest type: #usqInt>
  	<var: #next type: #usqInt>
  	<inline: false>
  
  	self assert: youngReferrers <= limitAddress.
  	youngReferrers = limitAddress ifTrue:
  		[^nil].
  	dest := limitAddress.
  	[next := dest - objectMemory wordSize.
  	 next >= youngReferrers
  	 and: [(coInterpreter cCoerceSimple: (objectMemory longAt: next) to: #'CogMethod *') cmRefersToYoung]] whileTrue:
  		[dest := next].
  	self assert: dest >= youngReferrers.
  	source := dest - objectMemory wordSize.
  	[source >= youngReferrers] whileTrue:
  		[(coInterpreter cCoerceSimple: (objectMemory longAt: source) to: #'CogMethod *') cmRefersToYoung ifTrue:
  			[self assert: source < (dest - objectMemory wordSize).
+ 			 cogit codeLongAt: (dest := dest - objectMemory wordSize) put: (objectMemory longAt: source)].
- 			 objectMemory longAt: (dest := dest - objectMemory wordSize) put: (objectMemory longAt: source)].
  		 source := source - objectMemory wordSize].
  	youngReferrers := dest.
  	self assert: self kosherYoungReferrers!

Item was changed:
  ----- Method: CogMethodZone>>relocateAndPruneYoungReferrers (in category 'young referers') -----
  relocateAndPruneYoungReferrers
  	| source dest next cogMethod |
  	<var: #source type: #usqInt>
  	<var: #dest type: #usqInt>
  	<var: #next type: #usqInt>
  	<var: #cogMethod type: #'CogMethod *'>
  	<inline: false>
  
  	self assert: youngReferrers <= limitAddress.
  	youngReferrers = limitAddress ifTrue:
  		[^nil].
  	dest := limitAddress.
  	[next := dest - objectMemory wordSize.
  	 next >= youngReferrers
  	 and: [(cogMethod := coInterpreter cCoerceSimple: (objectMemory longAt: next) to: #'CogMethod *') cmType ~= CMFree
  	 and: [cogMethod cmRefersToYoung]]] whileTrue:
  		[cogMethod objectHeader ~= 0 ifTrue:
+ 			[cogit codeLongAt: next put: cogMethod asInteger + cogMethod objectHeader].
- 			[coInterpreter longAt: next put: cogMethod asInteger + cogMethod objectHeader].
  		 dest := next].
  	self assert: dest >= youngReferrers.
  	source := dest - objectMemory wordSize.
  	[source >= youngReferrers] whileTrue:
  		[cogMethod := coInterpreter cCoerceSimple: (objectMemory longAt: source) to: #'CogMethod *'.
  		 (cogMethod cmType ~= CMFree
  		  and: [cogMethod cmRefersToYoung]) ifTrue:
  			[self assert: source < (dest - objectMemory wordSize).
  			 cogMethod objectHeader ~= 0 ifTrue:
  				[cogMethod := coInterpreter
  									cCoerceSimple: cogMethod asInteger + cogMethod objectHeader asInteger
  									to: #'CogMethod *'].
+ 			 cogit codeLongAt: (dest := dest - objectMemory wordSize) put: cogMethod asInteger].
- 			 objectMemory longAt: (dest := dest - objectMemory wordSize) put: cogMethod asInteger].
  		 source := source - objectMemory wordSize].
  	youngReferrers := dest.
  	"this assert must be deferred until after compaction.  See the end of compactCogCompiledCode"
  	"self assert: self kosherYoungReferrers"!

Item was changed:
  ----- Method: CogMethodZone>>removeFromOpenPICList: (in category 'accessing') -----
  removeFromOpenPICList: anOpenPIC
  	<var: #anOpenPIC type: #'CogMethod *'>
  	| prevPIC |
  	<var: #prevPIC type: #'CogMethod *'>
  	self assert: anOpenPIC cmType = CMOpenPIC.
  	openPICList ifNil: [^nil]. "As it is when compacting or unlinking all sends"
  	self assert: (openPICList cmType = CMOpenPIC
  				and: [openPICList nextOpenPIC isNil
  					or: [(self cCoerceSimple: openPICList nextOpenPIC to: #'CogMethod *') cmType = CMOpenPIC]]).
  	anOpenPIC = openPICList ifTrue:
  		["N.B. Use self rather than coInterpreter to avoid attempting to cast nil.
  		  Conversion to CogMethod done in the nextOpenPIC accessor."
  		 openPICList := self cCoerceSimple: anOpenPIC nextOpenPIC to: #'CogMethod *'.
  		 ^nil].
  	prevPIC := openPICList.
  	[self assert: (prevPIC ~~ nil
  				and: [prevPIC cmType = CMOpenPIC]).
  	 prevPIC nextOpenPIC = anOpenPIC asUnsignedInteger ifTrue:
+ 		[(cogit writableMethodFor: prevPIC) nextOpenPIC: anOpenPIC nextOpenPIC.
- 		[prevPIC nextOpenPIC: anOpenPIC nextOpenPIC.
  		 ^nil].
  	  prevPIC := self cCoerceSimple: prevPIC nextOpenPIC to: #'CogMethod *'.
  	  true] whileTrue!

Item was changed:
  ----- 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)"
+ 	<cmacro: '(address) 0'>
  	self assert: (address asInteger between: methodZoneBase and: methodZone zoneEnd)!

Item was changed:
  ----- 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)"
+ 	<cmacro: '(address) 0'>
  	self assert: (address asInteger - codeToDataDelta between: methodZoneBase and: methodZone zoneEnd)!

Item was changed:
+ ----- Method: Cogit>>codeByteAt:put: (in category 'generate machine code - dual mapped zone support') -----
- ----- Method: Cogit>>codeByteAt:put: (in category 'generate machine code') -----
  codeByteAt: address put: aByte
  	"production uses the macro..."
  	<cmacro: '(adress,value) byteAtput((address) + codeToDataDelta, value)'>
  	self codeWriteBreakpoint: address.
  	"simulation writes twice if simulating dual mapping..."
  	codeToDataDelta ~= 0 ifTrue:
  		[objectMemory byteAt: address + codeToDataDelta put: aByte].
  	^objectMemory byteAt: address put: aByte!

Item was changed:
+ ----- Method: Cogit>>codeLong32At:put: (in category 'generate machine code - dual mapped zone support') -----
- ----- Method: Cogit>>codeLong32At:put: (in category 'generate machine code') -----
  codeLong32At: address put: anInt
  	"production uses the macro..."
  	<cmacro: '(address,value) long32Atput((address) + codeToDataDelta, value)'>
  	self codeWriteBreakpoint: address.
  	"simulation writes twice if simulating dual mapping..."
  	codeToDataDelta ~= 0 ifTrue:
  		[objectMemory long32At: address + codeToDataDelta put: anInt].
  	^objectMemory long32At: address put: anInt!

Item was changed:
+ ----- Method: Cogit>>codeLong64At:put: (in category 'generate machine code - dual mapped zone support') -----
- ----- Method: Cogit>>codeLong64At:put: (in category 'generate machine code') -----
  codeLong64At: address put: anInt
  	"production uses the macro..."
  	<cmacro: '(address,value) long64Atput((address) + codeToDataDelta, value)'>
  	self codeWriteBreakpoint: address.
  	"simulation writes twice if simulating dual mapping..."
  	codeToDataDelta ~= 0 ifTrue:
  		[objectMemory long64At: address + codeToDataDelta put: anInt].
  	^objectMemory long64At: address put: anInt!

Item was changed:
+ ----- Method: Cogit>>codeLongAt:put: (in category 'generate machine code - dual mapped zone support') -----
- ----- Method: Cogit>>codeLongAt:put: (in category 'generate machine code') -----
  codeLongAt: address put: aLong
  	"production uses the macro..."
  	<cmacro: '(adress,value) longAtput((address) + codeToDataDelta, value)'>
  	self codeWriteBreakpoint: address.
  	"simulation writes twice if simulating dual mapping..."
  	codeToDataDelta ~= 0 ifTrue:
  		[objectMemory longAt: address + codeToDataDelta put: aLong].
  	^objectMemory longAt: address put: aLong!

Item was changed:
+ ----- Method: Cogit>>codeMemcpy:_:_: (in category 'generate machine code - dual mapped zone support') -----
- ----- Method: Cogit>>codeMemcpy:_:_: (in category 'generate machine code') -----
  codeMemcpy: dest _: src _: bytes
+ 	"Copy memory applying the codeToDataDelta.  This is used for creating PICs and so
+ 	 works on writable addresses (no delta required)."
  	"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 asInteger - codeToDataDelta _: src _: bytes].
  	objectMemory memcpy: dest _: src _: bytes!

Item was added:
+ ----- Method: Cogit>>codeMemmove:_:_: (in category 'generate machine code - dual mapped zone support') -----
+ codeMemmove: dest _: src _: bytes
+ 	"Move memory (copy allowing for overlap), applying the codeToDataDelta.
+ 	 This is used for code compaction and so works on readable addresses (delta is required)."
+ 	"production uses the macro..."
+ 	<cmacro: '(dest,src,bytes) memmove((dest)+codeToDataDelta,src,bytes)'>
+ 	self codeWriteBreakpoint: dest.
+ 	"simulation writes twice if simulating dual mapping..."
+ 	codeToDataDelta ~= 0 ifTrue:
+ 		[objectMemory memmove: dest asUnsignedInteger + codeToDataDelta _: src _: bytes].
+ 	objectMemory memmove: dest _: src _: bytes!

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

Item was changed:
+ ----- Method: Cogit>>codeWriteBreakpoint: (in category 'generate machine code - dual mapped zone support') -----
- ----- Method: Cogit>>codeWriteBreakpoint: (in category 'generate machine code') -----
  codeWriteBreakpoint: address
  	"(address = 16r520) ifTrue:
  		[self halt]"
  	"(address between: 16r2398 and: 16r23B0) ifTrue:
  		[self halt]"!

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

Item was changed:
  ----- Method: Cogit>>compactPICsWithFreedTargets (in category 'compaction') -----
  compactPICsWithFreedTargets
  	| cogMethod count |
  	<var: #cogMethod type: #'CogMethod *'>
  	cogMethod := self cCoerceSimple: methodZoneBase to: #'CogMethod *'.
  	count := 0.
  	[cogMethod < methodZone limitZony] whileTrue:
  		[(cogMethod cmType = CMClosedPIC
  		  and: [self cPICCompactAndIsNowEmpty: cogMethod]) ifTrue:
+ 			[(self writableMethodFor: cogMethod) cmType: CMFree].
- 			[cogMethod cmType: CMFree].
  		 cogMethod := methodZone methodAfter: cogMethod.
  		 count := count + 1].
  	self assert: count = methodZone numMethods!

Item was changed:
  ----- Method: Cogit>>mapObjectReferencesInMachineCodeForYoungGC (in category 'garbage collection') -----
  mapObjectReferencesInMachineCodeForYoungGC
  	"Update all references to objects in machine code for either a Spur scavenging gc
  	 or a Squeak V3 incremental GC.  Avoid scanning all code by using the youngReferrers
  	 list.  In a young gc a method referring to young may no longer refer to young, but a
  	 method not referring to young cannot and will not refer to young afterwards."
  	| pointer cogMethod hasYoungObj hasYoungObjPtr |
  	<var: #cogMethod type: #'CogMethod *'>
  	hasYoungObj := false.
  	hasYoungObjPtr := (self addressOf: hasYoungObj put: [:val| hasYoungObj := val]) asInteger.
  	codeModified := false.
  	pointer := methodZone youngReferrers.
  	[pointer < methodZone zoneEnd] whileTrue:
  		[self assert: hasYoungObj not.
  		 cogMethod := coInterpreter cCoerceSimple: (objectMemory longAt: pointer) to: #'CogMethod *'.
  		 cogMethod cmType = CMFree
  			ifTrue: [self assert: cogMethod cmRefersToYoung not]
  			ifFalse:
  				[self assert: (self cogMethodDoesntLookKosher: cogMethod) = 0.
  				 cogMethod cmRefersToYoung ifTrue:
+ 					[| writableVersion |
+ 					 self assert: (cogMethod cmType = CMMethod
- 					[self assert: (cogMethod cmType = CMMethod
  								or: [cogMethod cmType = CMOpenPIC]).
+ 					 writableVersion := self writableMethodFor: cogMethod.
+ 					 writableVersion selector: (objectRepresentation remapOop: cogMethod selector).
- 					 cogMethod selector: (objectRepresentation remapOop: cogMethod selector).
  					 (objectMemory isYoung: cogMethod selector) ifTrue:
  						[hasYoungObj := true].
  					 cogMethod cmType = CMMethod ifTrue:
  						[self assert: cogMethod objectHeader = objectMemory nullHeaderForMachineCodeMethod.
+ 						 writableVersion methodObject: (objectRepresentation remapOop: cogMethod methodObject).
- 						 cogMethod methodObject: (objectRepresentation remapOop: cogMethod methodObject).
  						 (objectMemory isYoung: cogMethod methodObject) ifTrue:
  							[hasYoungObj := true]].
  					 self mapFor: cogMethod
  						 performUntil: #remapIfObjectRef:pc:hasYoung:
  						 arg: hasYoungObjPtr.
  					 hasYoungObj
  						ifTrue: [hasYoungObj := false]
+ 						ifFalse: [writableVersion cmRefersToYoung: false]]].
- 						ifFalse: [cogMethod cmRefersToYoung: false]]].
  		 pointer := pointer + objectMemory wordSize].
  	methodZone pruneYoungReferrers.
  	codeModified ifTrue: "After updating oops in inline caches we need to flush the icache."
  		[backEnd flushICacheFrom: methodZoneBase asUnsignedInteger to: methodZone limitZony asUnsignedInteger]!

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

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



More information about the Vm-dev mailing list