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

commits at source.squeak.org commits at source.squeak.org
Tue Aug 5 01:40:40 UTC 2014


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

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

Name: VMMaker.oscog-eem.841
Author: eem
Time: 4 August 2014, 6:38:10.42 pm
UUID: 6b9e05e0-8058-4d62-9349-faff621ab0e6
Ancestors: VMMaker.oscog-eem.840

Spur:
Fix two become bugs surfaced when adding/removing
inst vars to/from Association, Binding et al.
First, the class table must be scanned to ensure there are
no forwarders to classes (much cheaper than the full
hierarchy walk to follow method dictionaries etc that was
done).  Second, machine code methods that gain a
new reference through become must get added to
the youngReferrers.  Add a new become effect flag,
OldBecameNew that captures this and respond to it in
CoInterpreter>>postBecomeAction: by adding all methods
to youngReferrers so that on the next scavenge all will be
made right.

Fix GC of machine code, which must follow forwarders when
doign markAndTraceLiteral: and again add to
youngReferrers if following gains a new ref.  Refactoring of
markAndTraceLiteral: into markAndTraceLiteral:in:at: et al
required.

Fix assert in addFreeSubTree:.

General:
Support the alternate bytecode set header in all VMs
to ease testing of multiple bytecode sets.  This means
methods with the sign bit set have no primitive field and
a larger num literals field, but no more.

Fix longPrintOop: (actually printOopShortInner:) for
global variable printing in face of new Environments.

Cogit:
Clean up adding to the youngReferrers by providing
CogMethodZone>>ensureInYoungReferrers:.  Since there
always is room on youngReferrers, nuke
roomOnYoungReferrersList, canLinkToYoungClasses and
caller code, simplifying ceSend:super:to:numArgs: et al.

Fix assert in followForwardedLiteralsIn:

Simulator:
Fix debugStackPointersFor: for alternate bytecode sets.

Add two Sista bytecodes to StackDepthFinder.

Define Sista's BytecodeEncoderClassName when defining
its bytecode table.

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

Item was added:
+ ----- Method: CCodeGenerator>>generateAsAddress:on:indent: (in category 'C translation') -----
+ generateAsAddress: msgNode on: aStream indent: level
+ 	"Generate the C code for this message onto the given stream."
+ 
+ 	self emitCExpression: msgNode args first on: aStream!

Item was changed:
  ----- Method: CCodeGenerator>>initializeCTranslationDictionary (in category 'C translation') -----
  initializeCTranslationDictionary 
  	"Initialize the dictionary mapping message names to actions for C code generation."
  
  	| pairs |
  	
  	translationDict := Dictionary new: 200.
  	pairs := #(
  	#&				#generateAnd:on:indent:
  	#|				#generateOr:on:indent:
  	#and:			#generateSequentialAnd:on:indent:
  	#or:			#generateSequentialOr:on:indent:
  	#not			#generateNot:on:indent:
  
  	#+				#generatePlus:on:indent:
  	#-				#generateMinus:on:indent:
  	#negated		#generateNegated:on:indent:
  	#*				#generateTimes:on:indent:
  	#/				#generateDivide:on:indent:
  	#//				#generateDivide:on:indent:
  	#\\				#generateModulo:on:indent:
  	#<<			#generateShiftLeft:on:indent:
  	#>>			#generateShiftRight:on:indent:
  	#min:			#generateMin:on:indent:
  	#max:			#generateMax:on:indent:
  	#between:and:	#generateBetweenAnd:on:indent:
  
  	#bitAnd:			#generateBitAnd:on:indent:
  	#bitOr:				#generateBitOr:on:indent:
  	#bitXor:			#generateBitXor:on:indent:
  	#bitShift:			#generateBitShift:on:indent:
  	#signedBitShift:	#generateSignedBitShift:on:indent:
  	#bitInvert32		#generateBitInvert32:on:indent:
  	#bitClear:			#generateBitClear:on:indent:
  	#truncateTo:		#generateTruncateTo:on:indent:
  	#rounded			#generateRounded:on:indent:
  
  	#<				#generateLessThan:on:indent:
  	#<=			#generateLessThanOrEqual:on:indent:
  	#=				#generateEqual:on:indent:
  	#>				#generateGreaterThan:on:indent:
  	#>=			#generateGreaterThanOrEqual:on:indent:
  	#~=			#generateNotEqual:on:indent:
  	#==			#generateEqual:on:indent:
  	#~~			#generateNotEqual:on:indent:
  	#isNil			#generateIsNil:on:indent:
  	#notNil			#generateNotNil:on:indent:
  
  	#whileTrue: 	#generateWhileTrue:on:indent:
  	#whileFalse:	#generateWhileFalse:on:indent:
  	#whileTrue 	#generateDoWhileTrue:on:indent:
  	#whileFalse		#generateDoWhileFalse:on:indent:
  	#to:do:			#generateToDo:on:indent:
  	#to:by:do:		#generateToByDo:on:indent:
  	#repeat 		#generateRepeat:on:indent:
  
  	#ifTrue:			#generateIfTrue:on:indent:
  	#ifFalse:		#generateIfFalse:on:indent:
  	#ifTrue:ifFalse:	#generateIfTrueIfFalse:on:indent:
  	#ifFalse:ifTrue:	#generateIfFalseIfTrue:on:indent:
  
  	#ifNotNil:		#generateIfNotNil:on:indent:
  	#ifNil:			#generateIfNil:on:indent:
  	#ifNotNil:ifNil:	#generateIfNotNilIfNil:on:indent:
  	#ifNil:ifNotNil:	#generateIfNilIfNotNil:on:indent:
  
  	#at:				#generateAt:on:indent:
  	#at:put:			#generateAtPut:on:indent:
  	#basicAt:		#generateAt:on:indent:
  	#basicAt:put:	#generateAtPut:on:indent:
  
  	#integerValueOf:			#generateIntegerValueOf:on:indent:
  	#integerObjectOf:			#generateIntegerObjectOf:on:indent:
  	#isIntegerObject: 			#generateIsIntegerObject:on:indent:
  	#cCode:					#generateInlineCCode:on:indent:
  	#cCode:inSmalltalk:			#generateInlineCCode:on:indent:
  	#cPreprocessorDirective:	#generateInlineCPreprocessorDirective:on:indent:
  	#cppIf:ifTrue:ifFalse:		#generateInlineCppIfElse:on:indent:
  	#cppIf:ifTrue:				#generateInlineCppIfElse:on:indent:
  	#cCoerce:to:				#generateCCoercion:on:indent:
  	#cCoerceSimple:to:			#generateCCoercion:on:indent:
  	#addressOf:				#generateAddressOf:on:indent:
  	#addressOf:put:			#generateAddressOf:on:indent:
+ 	#aaAddress:put:			#generateAsAddress:on:indent:
  	#signedIntFromLong		#generateSignedIntFromLong:on:indent:
  	#signedIntToLong			#generateSignedIntToLong:on:indent:
  	#signedIntFromShort		#generateSignedIntFromShort:on:indent:
  	#signedIntToShort			#generateSignedIntToShort:on:indent:
  	#preIncrement				#generatePreIncrement:on:indent:
  	#preDecrement			#generatePreDecrement:on:indent:
  	#inline:						#generateInlineDirective:on:indent:
  	#asFloat					#generateAsFloat:on:indent:
  	#asInteger					#generateAsInteger:on:indent:
  	#asUnsignedInteger		#generateAsUnsignedInteger:on:indent:
  	#asLong					#generateAsLong:on:indent:
  	#asUnsignedLong			#generateAsUnsignedLong:on:indent:
  	#asVoidPointer				#generateAsVoidPointer:on:indent:
  	#asSymbol					#generateAsSymbol:on:indent:
  	#flag:						#generateFlag:on:indent:
  	#anyMask:					#generateBitAnd:on:indent:
  	#noMask:					#generateNoMask:on:indent:
  	#raisedTo:					#generateRaisedTo:on:indent:
  	#touch:						#generateTouch:on:indent:
  
  	#bytesPerWord 			#generateBytesPerWord:on:indent:
  	#baseHeaderSize			#generateBaseHeaderSize:on:indent:
  	
  	#sharedCodeNamed:inCase:		#generateSharedCodeDirective:on:indent:
  
  	#perform:							#generatePerform:on:indent:
  	#perform:with:						#generatePerform:on:indent:
  	#perform:with:with:					#generatePerform:on:indent:
  	#perform:with:with:with:				#generatePerform:on:indent:
  	#perform:with:with:with:with:		#generatePerform:on:indent:
  	#perform:with:with:with:with:with:	#generatePerform:on:indent:
  
  	#value								#generateValue:on:indent:
  	#value:								#generateValue:on:indent:
  	#value:value:						#generateValue:on:indent:
  	#value:value:value:					#generateValue:on:indent:
  
  	#deny:								#generateDeny:on:indent:
  
  	#shouldNotImplement				#generateSmalltalkMetaError:on:indent:
  	#shouldBeImplemented			#generateSmalltalkMetaError:on:indent:
  	#subclassResponsibility			#generateSmalltalkMetaError:on:indent:
  	).
  
  	1 to: pairs size by: 2 do: [:i |
  		translationDict at: (pairs at: i) put: (pairs at: i + 1)].
  
  	pairs := #(
  	#ifTrue:					#generateIfTrueAsArgument:on:indent:	
  	#ifFalse:				#generateIfFalseAsArgument:on:indent:
  	#ifTrue:ifFalse:			#generateIfTrueIfFalseAsArgument:on:indent:
  	#ifFalse:ifTrue:			#generateIfFalseIfTrueAsArgument:on:indent:
  	#ifNotNil:				#generateIfNotNilAsArgument:on:indent:	
  	#ifNil:					#generateIfNilAsArgument:on:indent:
  	#ifNotNil:ifNil:			#generateIfNotNilIfNilAsArgument:on:indent:
  	#ifNil:ifNotNil:			#generateIfNilIfNotNilAsArgument:on:indent:
  	#cCode:				#generateInlineCCodeAsArgument:on:indent:
  	#cCode:inSmalltalk:		#generateInlineCCodeAsArgument:on:indent:
  	#cppIf:ifTrue:ifFalse:	#generateInlineCppIfElseAsArgument:on:indent:
  	#cppIf:ifTrue:			#generateInlineCppIfElseAsArgument:on:indent:
  
  	#value					#generateValueAsArgument:on:indent:
  	#value:					#generateValueAsArgument:on:indent:
  	#value:value:			#generateValueAsArgument:on:indent:
  	).
  
  	asArgumentTranslationDict := Dictionary new: 8.
  	1 to: pairs size by: 2 do: [:i |
  		asArgumentTranslationDict at: (pairs at: i) put: (pairs at: i + 1)].
  !

Item was changed:
  ----- Method: CoInterpreter>>ceDynamicSuperSend:to:numArgs: (in category 'trampolines') -----
  ceDynamicSuperSend: selector to: rcvr numArgs: numArgs
  	"Entry-point for an unlinked dynamic super send in a CogMethod.  Smalltalk stack looks like
  					receiver
  					args
  		head sp ->	sender return pc
  		
  	If an MNU then defer to handleMNUInMachineCodeTo:... which will dispatch the MNU and
  	may choose to allocate a closed PIC with a fast MNU dispatch for this send.  Otherwise
  	attempt to link the send site as efficiently as possible.  All link attempts may fail; e.g.
  	because we're out of code memory.
  
  	Continue execution via either executeMethod or interpretMethodFromMachineCode:
  	depending on whether the target method is cogged or not."
  	<api>
  	<option: #NewspeakVM>
+ 	| classTag errSelIdx cogMethod mClassMixin mixinApplication |
- 	| class classTag canLinkCacheTag errSelIdx cogMethod mClassMixin mixinApplication |
  	<inline: false>
  	<var: #cogMethod type: #'CogMethod *'>
  	<var: #newCogMethod type: #'CogMethod *'>
  	"self printExternalHeadFrame"
  	"self printStringOf: selector"
  	cogit assertCStackWellAligned.
  	self assert: (objectMemory addressCouldBeOop: rcvr).
  	self sendBreakpoint: selector receiver: rcvr.
  	mClassMixin := self mMethodClass.
  	mixinApplication := self 
  							findApplicationOfTargetMixin: mClassMixin
  							startingAtBehavior: (objectMemory fetchClassOf: rcvr).
  	self assert: (objectMemory lengthOf: mixinApplication) > (InstanceSpecificationIndex + 1).
  	classTag := objectMemory classTagForClass: (self superclassOf: mixinApplication).
- 	class := objectMemory fetchClassOf: rcvr. "what about the read barrier??"
- 	canLinkCacheTag := (objectMemory isYoungObject: class) not or: [cogit canLinkToYoungClasses].
  	argumentCount := numArgs.
  	(self lookupInMethodCacheSel: selector classTag: classTag)
  		ifTrue:"check for coggability because method is in the cache"
  			[self
  				ifAppropriateCompileToNativeCode: newMethod
  				selector: selector]
  		ifFalse:
  			[(objectMemory isOopForwarded: selector) ifTrue:
  				[^self
  					ceDynamicSuperSend: (self handleForwardedSelectorFaultFor: selector)
  					to: rcvr
  					numArgs: numArgs].
  			 (objectMemory isForwardedClassTag: classTag) ifTrue:
  				[^self
  					ceDynamicSuperSend: selector
  					to: (self handleForwardedSendFaultForReceiver: rcvr stackDelta: 1 "skip return pc")
  					numArgs: numArgs].
  			 messageSelector := selector.
  			 (errSelIdx := self lookupMethodNoMNUEtcInClass: (objectMemory classForClassTag: classTag)) ~= 0 ifTrue:
  				[self handleMNU: errSelIdx InMachineCodeTo: rcvr classForMessage: (objectMemory classForClassTag: classTag).
  				self assert: false "NOTREACHED"]].
  	"Method found and has a cog method.  Attempt to link to it."
  	(self maybeMethodHasCogMethod: newMethod) ifTrue:
  		[cogMethod := self cogMethodOf: newMethod.
  		 cogMethod selector = objectMemory nilObject
  			ifTrue: [cogit setSelectorOf: cogMethod to: selector]
  			ifFalse:
  				["Deal with anonymous accessors, e.g. in Newspeak.  The cogMethod may not have the correct
  				  selector.  If not, try and compile a new method with the correct selector."
  				 cogMethod selector ~= selector ifTrue:
  					[(cogit cog: newMethod selector: selector) ifNotNil:
  						[:newCogMethod| cogMethod := newCogMethod]]].
+ 		 cogMethod selector = selector ifTrue:
- 		 (cogMethod selector = selector
- 		 and: [canLinkCacheTag]) ifTrue:
  			[cogit
  				linkSendAt: (stackPages longAt: stackPointer)
  				in: (self mframeHomeMethod: framePointer)
  				to: cogMethod
  				offset: cogit dynSuperEntryOffset
  				receiver: rcvr].
  		 instructionPointer := self popStack.
  		 self executeNewMethod.
  		 self assert: false "NOTREACHED"].
  	instructionPointer := self popStack.
  	^self interpretMethodFromMachineCode
  	"NOTREACHED"!

Item was changed:
  ----- Method: CoInterpreter>>ceSend:super:to:numArgs: (in category 'trampolines') -----
  ceSend: selector super: superNormalBar to: rcvr numArgs: numArgs
  	"Entry-point for an unlinked send in a CogMethod.  Smalltalk stack looks like
  					receiver
  					args
  		head sp ->	sender return pc
  		
  	If an MNU then defer to handleMNUInMachineCodeTo:... which will dispatch the MNU and
  	may choose to allocate a closed PIC with a fast MNU dispatch for this send.  Otherwise
  	attempt to link the send site as efficiently as possible.  All link attempts may fail; e.g.
  	because we're out of code memory.
  
  	Continue execution via either executeMethod or interpretMethodFromMachineCode:
  	depending on whether the target method is cogged or not."
  	<api>
+ 	| classTag errSelIdx cogMethod |
- 	| classTag canLinkCacheTag errSelIdx cogMethod |
  	<inline: false>
  	<var: #cogMethod type: #'CogMethod *'>
  	<var: #newCogMethod type: #'CogMethod *'>
  	"self printExternalHeadFrame"
  	"self printStringOf: selector"
  	cogit assertCStackWellAligned.
  	self assert: (objectMemory addressCouldBeOop: rcvr).
  	self sendBreakpoint: selector receiver: rcvr.
  	superNormalBar = 0
  		ifTrue: [classTag := objectMemory fetchClassTagOf: rcvr]
  		ifFalse: [classTag := objectMemory classTagForClass: (self superclassOf: (self methodClassOf: (self frameMethodObject: framePointer)))].
- 	canLinkCacheTag := cogit canLinkToYoungClasses or: [(objectMemory isYoungObject: classTag) not].
  	argumentCount := numArgs.
  	(self lookupInMethodCacheSel: selector classTag: classTag)
  		ifTrue:"check for coggability because method is in the cache"
  			[self
  				ifAppropriateCompileToNativeCode: newMethod
  				selector: selector]
  		ifFalse:
  			[(objectMemory isOopForwarded: selector) ifTrue:
  				[^self
  					ceSend: (self handleForwardedSelectorFaultFor: selector)
  					super: superNormalBar
  					to: rcvr
  					numArgs: numArgs].
  			 (objectMemory isForwardedClassTag: classTag) ifTrue:
  				[self assert: superNormalBar = 0.
  				^self
  					ceSend: selector
  					super: superNormalBar
  					to: (self handleForwardedSendFaultForReceiver: rcvr stackDelta: 1 "skip return pc")
  					numArgs: numArgs].
  			 messageSelector := selector.
  			 (errSelIdx := self lookupMethodNoMNUEtcInClass: (objectMemory classForClassTag: classTag)) ~= 0 ifTrue:
+ 				[(errSelIdx = SelectorDoesNotUnderstand
- 				[(canLinkCacheTag
- 				  and: [errSelIdx = SelectorDoesNotUnderstand
  				  and: [(cogMethod := cogit cogMNUPICSelector: messageSelector
  											methodOperand: (self mnuMethodOrNilFor: rcvr)
  											numArgs: argumentCount) asUnsignedInteger
+ 						> cogit minCogMethodAddress]) ifTrue:
- 						> cogit minCogMethodAddress]]) ifTrue:
  						[cogit
  							linkSendAt: (stackPages longAt: stackPointer)
  							in: (self mframeHomeMethod: framePointer)
  							to: cogMethod
  							offset: (superNormalBar = 0
  									ifTrue: [cogit entryOffset]
  									ifFalse: [cogit noCheckEntryOffset])
  							receiver: rcvr].
  				self handleMNU: errSelIdx
  					InMachineCodeTo: rcvr
  					classForMessage: (objectMemory classForClassTag: classTag).
  				self assert: false "NOTREACHED"]].
  	"Method found and has a cog method.  Attempt to link to it.  The receiver's class may be young.
  	 If the Cogit can't store young classes in inline caches we can link to an open PIC instead."
  	(self maybeMethodHasCogMethod: newMethod) ifTrue:
  		[cogMethod := self cogMethodOf: newMethod.
  		 cogMethod selector = objectMemory nilObject
  			ifTrue: [cogit setSelectorOf: cogMethod to: selector]
  			ifFalse:
  				["Deal with anonymous accessors, e.g. in Newspeak.  The cogMethod may not have the
  				  correct selector.  If not, try and compile a new method with the correct selector."
  				 cogMethod selector ~= selector ifTrue:
  					[(cogit cog: newMethod selector: selector) ifNotNil:
  						[:newCogMethod| cogMethod := newCogMethod]]].
+ 		 cogMethod selector = selector
- 		 (cogMethod selector = selector
- 		  and: [canLinkCacheTag])
  			ifTrue:
  				[cogit
  					linkSendAt: (stackPages longAt: stackPointer)
  					in: (self mframeHomeMethod: framePointer)
  					to: cogMethod
  					offset: (superNormalBar = 0
  								ifTrue: [cogit entryOffset]
  								ifFalse: [cogit noCheckEntryOffset])
  					receiver: rcvr]
  			ifFalse: "If patchToOpenPICFor:.. returns we're out of code memory"
  				[cogit
  					patchToOpenPICFor: selector
  					numArgs: numArgs
  					receiver: rcvr].
  		 instructionPointer := self popStack.
  		 self executeNewMethod.
  		 self assert: false "NOTREACHED"].
  	instructionPointer := self popStack.
  	^self interpretMethodFromMachineCode
  	"NOTREACHED"!

Item was changed:
  ----- Method: CoInterpreter>>postBecomeAction: (in category 'object memory support') -----
  postBecomeAction: theBecomeEffectsFlags
  	"Clear the gcMode var and let the Cogit do its post GC checks."
  	super postBecomeAction: theBecomeEffectsFlags.
  
+ 	(objectMemory hasSpurMemoryManagerAPI
+ 	 and: [theBecomeEffectsFlags anyMask: OldBecameNewFlag]) ifTrue:
+ 		[cogit addAllToYoungReferrers].
  	cogit cogitPostGCAction: gcMode.
  
  	lastCoggableInterpretedBlockMethod := lastUncoggableInterpretedBlockMethod := nil.
  
  	gcMode := 0!

Item was added:
+ ----- Method: CogMethodZone>>addAllToYoungReferrers (in category 'young referers') -----
+ addAllToYoungReferrers
+ 	<api>
+ 	<returnTypeC: #void>
+ 	| cogMethod |
+ 	<var: #cogMethod type: #'CogMethod *'>
+ 	cogMethod := coInterpreter cCoerceSimple: baseAddress to: #'CogMethod *'.
+ 	[cogMethod < self limitZony] whileTrue:
+ 		[(cogMethod cmType = CMMethod
+ 		  or: [cogMethod cmType = CMOpenPIC]) ifTrue:
+ 			[self ensureInYoungReferrers: cogMethod].
+ 		 cogMethod := self methodAfter: cogMethod]!

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

Item was changed:
  ----- Method: CogMethodZone>>allocate: (in category 'allocating') -----
  allocate: numBytes
  	| roundedBytes allocation |
  	roundedBytes := numBytes + 7 bitAnd: -8.
  	mzFreeStart + roundedBytes >= (limitAddress - (methodCount * BytesPerWord)) ifTrue:
  		[^0].
  	allocation := mzFreeStart.
  	mzFreeStart := mzFreeStart + roundedBytes.
  	methodCount := methodCount + 1.
- 	self assert: self roomOnYoungReferrersList.
  	self cCode: '' inSmalltalk:
  		[(cogit breakPC isInteger
  		   and: [cogit breakPC between: allocation and: mzFreeStart]) ifTrue:
  			[cogit singleStep: true]].
  	^allocation!

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

Item was removed:
- ----- Method: CogMethodZone>>roomOnYoungReferrersList (in category 'young referers') -----
- roomOnYoungReferrersList
- 	"The youngReferrers list holds methods that may contain a reference to a young
- 	 object and hence need to be visited during young-space garbage collection.  The
- 	 list saves walking through all of code space to do so, as in typical circumstances
- 	 there are no methods that refer to young objects.However, events like become:
- 	 can potentially cause every method to refer to a new object (becomming true for
- 	 example).  So there needs to be room on the list for as many methods as exist."
- 	self assert: (youngReferrers <= limitAddress
- 				and: [youngReferrers >= (limitAddress - (methodCount * BytesPerWord))]).
- 	^limitAddress - (methodCount * BytesPerWord) >= mzFreeStart!

Item was removed:
- ----- Method: CogObjectRepresentation>>canLinkToYoungClasses (in category 'in-line cacheing') -----
- canLinkToYoungClasses
- 	^self subclassResponsibility!

Item was added:
+ ----- Method: CogObjectRepresentation>>markAndTraceCacheTagLiteral:in:atpc: (in category 'garbage collection') -----
+ markAndTraceCacheTagLiteral: literal in: cogMethodOrNil atpc: address
+ 	"Mark and trace a literal in an inline cache preceeding address in cogMethodOrNil.
+ 	 Answer if code was modified."
+ 	<var: #cogMethodOrNil type: #'CogMethod *'>
+ 	<var: #address type: #usqInt>
+ 	self subclassResponsibility!

Item was added:
+ ----- Method: CogObjectRepresentation>>markAndTraceLiteral:in:at: (in category 'garbage collection') -----
+ markAndTraceLiteral: literal in: cogMethod at: address
+ 	"Mark and trace a literal in a sqInt variable of cogMethod."
+ 	<var: #cogMethod type: #'CogMethod *'>
+ 	<var: #address type: #'sqInt *'>
+ 	self subclassResponsibility!

Item was added:
+ ----- Method: CogObjectRepresentation>>markAndTraceLiteral:in:atpc: (in category 'garbage collection') -----
+ markAndTraceLiteral: literal in: cogMethodOrNil atpc: address
+ 	"Mark and trace a literal in a machine code instruction preceeding address in cogMethodOrNil.
+ 	 Answer if code was modified."
+ 	<var: #cogMethodOrNil type: #'CogMethod *'>
+ 	<var: #address type: #usqInt>
+ 	self subclassResponsibility!

Item was removed:
- ----- Method: CogObjectRepresentationForSpur>>canLinkToYoungClasses (in category 'in-line cacheing') -----
- canLinkToYoungClasses
- 	<api>
- 	<cmacro: '() true'>
- 	^true!

Item was added:
+ ----- Method: CogObjectRepresentationForSpur>>markAndTraceCacheTagLiteral:in:atpc: (in category 'garbage collection') -----
+ markAndTraceCacheTagLiteral: literal in: cogMethodOrNil atpc: address
+ 	"Mark and trace a literal in an inline cache preceeding address in cogMethodOrNil.
+ 	 Answer if code was modified."
+ 	<var: #cogMethodOrNil type: #'CogMethod *'>
+ 	<var: #address type: #usqInt>
+ 	| objOop |
+ 	(self couldBeObject: literal) ifFalse:
+ 		[^false].
+ 	self assert: (objectMemory addressCouldBeObj: literal).
+ 	(objectMemory isForwarded: literal) ifFalse:
+ 		[objectMemory markAndTrace: literal.
+ 		 ^false].
+ 	objOop := objectMemory followForwarded: literal.
+ 	cogit backEnd rewriteInlineCacheTag: objOop at: address.
+ 	self markAndTraceUpdatedLiteral: objOop in: cogMethodOrNil.
+ 	^true!

Item was added:
+ ----- Method: CogObjectRepresentationForSpur>>markAndTraceLiteral:in:at: (in category 'garbage collection') -----
+ markAndTraceLiteral: literal in: cogMethod at: address
+ 	"Mark and trace a literal in a sqInt variable of cogMethod."
+ 	<var: #cogMethod type: #'CogMethod *'>
+ 	<var: #address type: #'sqInt *'>
+ 	| objOop |
+ 	(self couldBeObject: literal) ifFalse:
+ 		[^self].
+ 	self assert: (objectMemory addressCouldBeObj: literal).
+ 	(objectMemory isForwarded: literal) ifFalse:
+ 		[objectMemory markAndTrace: literal.
+ 		 ^self].
+ 	objOop := objectMemory followForwarded: literal.
+ 	address at: 0 put: objOop.
+ 	self markAndTraceUpdatedLiteral: objOop in: cogMethod!

Item was added:
+ ----- Method: CogObjectRepresentationForSpur>>markAndTraceLiteral:in:atpc: (in category 'garbage collection') -----
+ markAndTraceLiteral: literal in: cogMethodOrNil atpc: address
+ 	"Mark and trace a literal in a machine code instruction preceeding address in cogMethodOrNil.
+ 	 Answer if code was modified."
+ 	<var: #cogMethodOrNil type: #'CogMethod *'>
+ 	<var: #address type: #usqInt>
+ 	| objOop |
+ 	(self couldBeObject: literal) ifFalse:
+ 		[^false].
+ 	self assert: (objectMemory addressCouldBeObj: literal).
+ 	(objectMemory isForwarded: literal) ifFalse:
+ 		[objectMemory markAndTrace: literal.
+ 		 ^false].
+ 	objOop := objectMemory followForwarded: literal.
+ 	cogit backEnd storeLiteral: objOop beforeFollowingAddress: address.
+ 	self markAndTraceUpdatedLiteral: objOop in: cogMethodOrNil.
+ 	^true!

Item was added:
+ ----- Method: CogObjectRepresentationForSpur>>markAndTraceUpdatedLiteral:in: (in category 'garbage collection') -----
+ markAndTraceUpdatedLiteral: objOop in: cogMethodOrNil
+ 	"Common code to mark a literal in cogMethod and add
+ 	 the cogMethod to youngReferrers if the literal is young."
+ 	<var: #cogMethodOrNil type: #'CogMethod *'>
+ 	(objectMemory isNonImmediate: objOop) ifTrue:
+ 		[(cogMethodOrNil notNil
+ 		  and: [objectMemory isYoungObject: objOop]) ifTrue:
+ 			[methodZone ensureInYoungReferrers: cogMethodOrNil].
+ 		 objectMemory markAndTrace: objOop]!

Item was removed:
- ----- Method: CogObjectRepresentationForSqueakV3>>canLinkToYoungClasses (in category 'in-line cacheing') -----
- canLinkToYoungClasses
- 	<api>
- 	^methodZone roomOnYoungReferrersList!

Item was added:
+ ----- Method: CogObjectRepresentationForSqueakV3>>markAndTraceCacheTagLiteral:in:atpc: (in category 'garbage collection') -----
+ markAndTraceCacheTagLiteral: literal in: cogMethodOrNil atpc: address
+ 	"Mark and trace a literal in an inline cache preceeding address in cogMethodOrNil.
+ 	 Answer if code was modified."
+ 	<var: #cogMethodOrNil type: #'CogMethod *'>
+ 	<var: #address type: #usqInt>
+ 	<inline: true>
+ 	self markAndTraceLiteral: literal.
+ 	^false!

Item was added:
+ ----- Method: CogObjectRepresentationForSqueakV3>>markAndTraceLiteral:in:at: (in category 'garbage collection') -----
+ markAndTraceLiteral: literal in: cogMethod at: address
+ 	"Mark and trace a literal in a sqInt variable of cogMethod."
+ 	<var: #cogMethod type: #'CogMethod *'>
+ 	<var: #address type: #'sqInt *'>
+ 	<inline: true>
+ 	self markAndTraceLiteral: literal!

Item was added:
+ ----- Method: CogObjectRepresentationForSqueakV3>>markAndTraceLiteral:in:atpc: (in category 'garbage collection') -----
+ markAndTraceLiteral: literal in: cogMethodOrNil atpc: address
+ 	"Mark and trace a literal in a machine code instruction preceeding address in cogMethodOrNil.
+ 	 Answer if code was modified."
+ 	<var: #cogMethodOrNil type: #'CogMethod *'>
+ 	<var: #address type: #usqInt>
+ 	<inline: true>
+ 	self markAndTraceLiteral: literal.
+ 	^false!

Item was changed:
  ----- Method: CogVMSimulator>>shortPrint: (in category 'debug support') -----
  shortPrint: oop
  	| name classOop |
  	(objectMemory isImmediate: oop) ifTrue:
  		[(objectMemory isImmediateCharacter: oop) ifTrue:
  			[^(objectMemory characterValueOf: oop) < 256
  				ifTrue:
  					['=$' , (objectMemory characterValueOf: oop) printString , 
  					' (' , (String with: (Character value: (objectMemory characterValueOf: oop))) , ')']
  				ifFalse:
  					['=$' , (objectMemory characterValueOf: oop) printString, '(???)']].
  		(objectMemory isIntegerObject: oop) ifTrue:
  			[^ '=' , (objectMemory integerValueOf: oop) printString , 
  			' (' , (objectMemory integerValueOf: oop) hex , ')'].
  		^'= UNKNOWN IMMEDIATE', ' (' , (objectMemory integerValueOf: oop) hex , ')'].
  	(objectMemory addressCouldBeObj: oop) ifFalse:
  		[^(oop bitAnd: objectMemory allocationUnit - 1) ~= 0
  			ifTrue: [' is misaligned']
  			ifFalse: [self whereIs: oop]].
  	(objectMemory isFreeObject: oop) ifTrue:
  		[^' is a free chunk of size ', (objectMemory sizeOfFree: oop) printString].
  	(objectMemory isForwarded: oop) ifTrue:
  		[^' is a forwarded object to ', (objectMemory followForwarded: oop) hex,
  			' of slot size ', (objectMemory numSlotsOfAny: oop) printString].
  	classOop := objectMemory fetchClassOfNonImm: oop.
  	(objectMemory numSlotsOf: classOop) = metaclassNumSlots ifTrue:
  		[^'class ' , (self nameOfClass: oop)].
  	name := self nameOfClass: classOop.
  	name size = 0 ifTrue: [name := '??'].
  	name = 'String' ifTrue: [^ (self stringOf: oop) printString].
  	name = 'ByteString' ifTrue: [^ (self stringOf: oop) printString].
  	name = 'Symbol' ifTrue: [^ '#' , (self stringOf: oop)].
  	name = 'ByteSymbol' ifTrue: [^ '#' , (self stringOf: oop)].
  	name = 'Character' ifTrue: "SpurMemoryManager has immediate Characters; ObjectMemory does not"
  		[^ '=' , (Character value: (objectMemory integerValueOf: 
  				(objectMemory fetchPointer: 0 ofObject: oop))) printString].
  	name = 'UndefinedObject' ifTrue: [^ 'nil'].
  	name = 'False' ifTrue: [^ 'false'].
  	name = 'True' ifTrue: [^ 'true'].
  	name = 'Float' ifTrue: [^ '=' , (self dbgFloatValueOf: oop) printString].
+ 	"Try to spot association-like things; they're all subclasses of LookupKey"
+ 	((objectMemory isPointersNonImm: oop)
+ 	 and: [((objectMemory instanceSizeOf: classOop) between: ValueIndex + 1 and: ValueIndex + 2)
+ 	 and: [(objectMemory isBytes: (objectMemory fetchPointer: KeyIndex ofObject: oop))]]) ifTrue:
+ 		[| classLookupKey |
+ 		 classLookupKey := objectMemory fetchClassOfNonImm: (objectMemory splObj: SchedulerAssociation).
+ 		 [classLookupKey = objectMemory nilObject ifTrue:
+ 			[^(('AEIOU' includes: name first) ifTrue: ['an '] ifFalse: ['a ']), name].
+ 		  (objectMemory instanceSizeOf: classLookupKey) = (KeyIndex + 1)] whileFalse:
+ 			[classLookupKey := self superclassOf: classLookupKey].
+ 		 (self includesBehavior: classOop ThatOf: classLookupKey) ifTrue:
+ 			[^(('AEIOU' includes: name first) ifTrue: ['an '] ifFalse: ['a ']), name,
+ 				' ', (self shortPrint: (objectMemory fetchPointer: KeyIndex ofObject: oop)),
+ 				' -> ',
+ 				(objectMemory fetchPointer: ValueIndex ofObject: oop) hex8]].
- 	(#('Association' 'ReadOnlyVariableBinding' 'VariableBinding') includes: name) ifTrue:
- 		[^ '(' ,
- 		(self shortPrint: (self longAt: oop + BaseHeaderSize)) ,
- 		' -> ' ,
- 		(self longAt: oop + BaseHeaderSize + BytesPerWord) hex8 , ')'].
  	^(('AEIOU' includes: name first) ifTrue: ['an '] ifFalse: ['a ']), name!

Item was added:
+ ----- Method: Cogit>>addAllToYoungReferrers (in category 'jit - api') -----
+ addAllToYoungReferrers
+ 	<doNotGenerate>
+ 	methodZone addAllToYoungReferrers!

Item was removed:
- ----- Method: Cogit>>canLinkToYoungClasses (in category 'jit - api') -----
- canLinkToYoungClasses
- 	<doNotGenerate>
- 	^objectRepresentation canLinkToYoungClasses!

Item was changed:
  ----- Method: Cogit>>ceImplicitReceiverFor:receiver: (in category 'in-line cacheing') -----
  ceImplicitReceiverFor: selector receiver: receiver
  	"Cached implicit receiver implementation.  Caller looks like
  		mov selector, ClassReg
  				call ceImplicitReceiver
  				br continue
  		Lclass	.word
  		Lmixin:	.word
  		continue:
  	 The trampoline has already fetched the class and probed the cache and found
  	 that the cache missed.  Compute the implicit receiver for the receiver's class
  	 and reload the class tag.  If either the class tag or the mixin are young then the
  	 method needs to be added to the youngReferrers list to ensure correct GC."
  
  	<option: #SqueakV3ObjectMemory>
  	| rcvrClass retpc classpc mixinpc mixin cogMethod |
  	<var: #cogMethod type: #'CogMethod *'>
  	retpc := coInterpreter stackTop.
  	classpc := retpc + backEnd jumpShortByteSize.
  	mixinpc := retpc + backEnd jumpShortByteSize + BytesPerOop.
  	mixin := coInterpreter
  				implicitReceiverFor: receiver
  				mixin: coInterpreter mMethodClass
  				implementing: selector.
  	rcvrClass := objectMemory fetchClassOf: receiver.
  	cogMethod := coInterpreter mframeHomeMethodExport.
  	cogMethod cmRefersToYoung ifFalse:
  		[((objectRepresentation inlineCacheTagsMayBeObjects
  		   and: [objectMemory isYoung: rcvrClass])
  		  or: [mixin ~= receiver and: [objectMemory isYoung: mixin]]) ifTrue:
+ 			[methodZone ensureInYoungReferrers: cogMethod]].
- 			[methodZone roomOnYoungReferrersList ifFalse:
- 				[coInterpreter callForCogCompiledCodeCompaction.
- 				 ^mixin].
- 			 cogMethod cmRefersToYoung: true.
- 			 methodZone addToYoungReferrers: cogMethod]].
  	backEnd
  		unalignedLongAt: classpc
  			put: (objectRepresentation inlineCacheTagForClass: rcvrClass);
  		unalignedLongAt: mixinpc
  			put: (mixin = receiver ifTrue: [0] ifFalse: [mixin]).
  	^mixin!

Item was changed:
  ----- Method: Cogit>>ceImplicitReceiverFor:receiver:cache: (in category 'in-line cacheing') -----
  ceImplicitReceiverFor: selector receiver: receiver cache: cacheAddress
  	"Cached implicit receiver implementation.  Caller looks like
  				mov Lclass, Arg1Reg
  				mov selector, SendNumArgsReg
  				call ceImplicitReceiver
  	 and Lclass: .word; Lmixin: .word is somewhere on the heap.
  	 The trampoline has already fetched the class and probed the cache and found
  	 that the cache missed.  Compute the implicit receiver for the receiver's class
  	 and reload the class tag.  If either the class tag or the mixin are young then the
  	 method needs to be added to the youngReferrers list to ensure correct GC."
  
  	<option: #SpurMemoryManager>
  	<var: #cacheAddress type: #usqInt>
  	| rcvrClass mixin cogMethod |
  	<var: #cogMethod type: #'CogMethod *'>
  	mixin := coInterpreter
  				implicitReceiverFor: receiver
  				mixin: coInterpreter mMethodClass
  				implementing: selector.
  	rcvrClass := objectMemory fetchClassOf: receiver.
  	cogMethod := coInterpreter mframeHomeMethodExport.
  	cogMethod cmRefersToYoung ifFalse:
  		[((objectRepresentation inlineCacheTagsMayBeObjects
  		   and: [objectMemory isYoung: rcvrClass])
  		  or: [mixin ~= receiver and: [objectMemory isYoung: mixin]]) ifTrue:
+ 			[methodZone ensureInYoungReferrers: cogMethod]].
- 			[methodZone roomOnYoungReferrersList ifFalse:
- 				[coInterpreter callForCogCompiledCodeCompaction.
- 				 ^mixin].
- 			 cogMethod cmRefersToYoung: true.
- 			 methodZone addToYoungReferrers: cogMethod]].
  	backEnd
  		unalignedLongAt: cacheAddress
  			put: (objectRepresentation inlineCacheTagForClass: rcvrClass);
  		unalignedLongAt: cacheAddress + BytesPerOop
  			put: (mixin = receiver ifTrue: [0] ifFalse: [mixin]).
  	^mixin!

Item was changed:
  ----- Method: Cogit>>followForwardedLiteralsIn: (in category 'garbage collection') -----
  followForwardedLiteralsIn: cogMethod
  	<api>
  	<option: #SpurObjectMemory>
  	<var: #cogMethod type: #'CogMethod *'>
+ 	self assert: (objectMemory isForwarded: cogMethod methodObject) not.
- 	self assert: (objectMemory shouldRemapOop: cogMethod methodObject) not.
  	(objectMemory shouldRemapOop: cogMethod selector) ifTrue:
+ 		[cogMethod selector: (objectMemory remapObj: cogMethod selector).
+ 		 (objectMemory isYoung: cogMethod selector) ifTrue:
+ 			[methodZone ensureInYoungReferrers: cogMethod]].
- 		[cogMethod selector: (objectMemory remapObj: cogMethod selector)].
  	self mapFor: cogMethod
  		performUntil: #remapIfObjectRef:pc:hasYoung:
  		arg: 0!

Item was changed:
  ----- Method: Cogit>>followForwardedMethods (in category 'garbage collection') -----
  followForwardedMethods
  	<api>
  	<option: #SpurObjectMemory>
  	<var: #cogMethod type: #'CogMethod *'>
  	| cogMethod freedPIC |
  	<var: #cogMethod type: #'CogMethod *'>
  	freedPIC := false.
  	cogMethod := self cCoerceSimple: methodZoneBase to: #'CogMethod *'.
  	[cogMethod < methodZone limitZony] whileTrue:
  		[cogMethod cmType = CMMethod ifTrue:
  			[(objectMemory isForwarded: cogMethod methodObject) ifTrue:
  				[cogMethod methodObject: (objectMemory followForwarded: cogMethod methodObject).
+ 				 (objectMemory isYoungObject: cogMethod methodObject) ifTrue:
+ 					[methodZone ensureInYoungReferrers: cogMethod]]].
- 				 (cogMethod cmRefersToYoung not
- 				  and: [objectMemory isYoungObject: cogMethod methodObject]) ifTrue:
- 					[methodZone addToYoungReferrers: cogMethod]]].
  		 cogMethod cmType = CMClosedPIC ifTrue:
  			[(self followMethodReferencesInClosedPIC: cogMethod) ifTrue:
  				[freedPIC := true.
  				 methodZone freeMethod: cogMethod]].
  		 cogMethod := methodZone methodAfter: cogMethod].
  	freedPIC ifTrue:
  		[self unlinkSendsToFree.
  		 methodZone pruneYoungReferrers.
  		 processor flushICacheFrom: codeBase to: methodZone limitZony asInteger]!

Item was changed:
  ----- Method: Cogit>>linkSendAt:in:to:offset:receiver: (in category 'in-line cacheing') -----
  linkSendAt: callSiteReturnAddress in: sendingMethod to: targetMethod offset: theEntryOffset receiver: receiver
  	<api>
  	<var: #sendingMethod type: #'CogMethod *'>
  	<var: #targetMethod type: #'CogMethod *'>
  	| inlineCacheTag address extent |
  	self cppIf: NewspeakVM
  		ifTrue: [self assert: (theEntryOffset = cmEntryOffset
  							or: [theEntryOffset = cmNoCheckEntryOffset
  							or: [theEntryOffset = cmDynSuperEntryOffset]])]
  		ifFalse: [self assert: (theEntryOffset = cmEntryOffset
  							or: [theEntryOffset = cmNoCheckEntryOffset])].
  	self assert: (callSiteReturnAddress between: methodZoneBase and: methodZone freeStart).
  	inlineCacheTag := theEntryOffset = cmNoCheckEntryOffset
  						ifTrue: [targetMethod selector "i.e. no change"]
  						ifFalse: [objectRepresentation inlineCacheTagForInstance: receiver].
+ 	(objectRepresentation inlineCacheTagIsYoung: inlineCacheTag) ifTrue:
+ 		[methodZone ensureInYoungReferrers: sendingMethod].
- 	(sendingMethod cmRefersToYoung not
- 	 and: [(objectRepresentation inlineCacheTagIsYoung: inlineCacheTag)]) ifTrue:
- 		[self assert: (methodZone occurrencesInYoungReferrers: sendingMethod) = 0.
- 		 sendingMethod cmRefersToYoung: true.
- 		 methodZone addToYoungReferrers: sendingMethod].
  	address := targetMethod asInteger + theEntryOffset.
  	extent := backEnd
  				rewriteInlineCacheAt: callSiteReturnAddress
  				tag: inlineCacheTag
  				target: address.
  	processor
  		flushICacheFrom: callSiteReturnAddress - 1 - extent
  		to: callSiteReturnAddress - 1!

Item was changed:
  ----- Method: Cogit>>mapObjectReferencesInMachineCodeForBecome (in category 'garbage collection') -----
  mapObjectReferencesInMachineCodeForBecome
  	"Update all references to objects in machine code for a become.
  	 Unlike incrementalGC or fullGC a method that does not refer to young may
  	 refer to young as a result of the become operation.  Unlike incrementalGC
  	 or fullGC the reference from a Cog method to its methodObject *must not*
  	 change since the two are two halves of the same object."
  	| cogMethod hasYoungObj hasYoungObjPtr freedPIC |
  	<var: #cogMethod type: #'CogMethod *'>
  	hasYoungObj := false.
  	hasYoungObjPtr := (self addressOf: hasYoungObj put: [:val| hasYoungObj := val]) asInteger.
  	codeModified := freedPIC := false.
  	self mapObjectReferencesInGeneratedRuntime.
  	cogMethod := self cCoerceSimple: methodZoneBase to: #'CogMethod *'.
  	[cogMethod < methodZone limitZony] whileTrue:
  		[self assert: hasYoungObj not.
  		 cogMethod cmType ~= CMFree ifTrue:
  			[self assert: (self cogMethodDoesntLookKosher: cogMethod) = 0.
  			 cogMethod selector: (objectRepresentation remapOop: cogMethod selector).
  			 cogMethod cmType = CMClosedPIC
  				ifTrue:
  					[((objectMemory isYoung: cogMethod selector)
  					   or: [self mapObjectReferencesInClosedPIC: cogMethod]) ifTrue:
  						[freedPIC := true.
  						 methodZone freeMethod: cogMethod]]
  				ifFalse:
  					[(objectMemory isYoung: cogMethod selector) ifTrue:
  						[hasYoungObj := true].
  					 cogMethod cmType = CMMethod ifTrue:
  						[| remappedMethod |
  						 self assert: cogMethod objectHeader = objectMemory nullHeaderForMachineCodeMethod.
  						 remappedMethod := objectRepresentation remapOop: cogMethod methodObject.
  						 remappedMethod ~= cogMethod methodObject ifTrue:
  							[(coInterpreter methodHasCogMethod: remappedMethod) ifTrue:
  								[self error: 'attempt to become two cogged methods'].
  							 (objectMemory
  									withoutForwardingOn: cogMethod methodObject
  									and: remappedMethod
  									with: cogMethod cmUsesPenultimateLit
  									sendToCogit: #method:hasSameCodeAs:checkPenultimate:) ifFalse:
  								[self error: 'attempt to become cogged method into different method'].
  							 "For non-Newspeak there should ne a one-to-one mapping between bytecoded and
  							  cog methods.  For Newspeak not necessarily, but only for anonymous accessors."
  							 "Only reset the method object's header if it is referring to this CogMethod."
  							 (coInterpreter rawHeaderOf: cogMethod methodObject) = cogMethod asInteger
  								ifTrue:
  									[coInterpreter
  										rawHeaderOf: cogMethod methodObject
  										put: cogMethod methodHeader.
  									 cogMethod
  										methodHeader: (coInterpreter rawHeaderOf: remappedMethod);
  										methodObject: remappedMethod.
  									 coInterpreter
  										rawHeaderOf: remappedMethod
  										put: cogMethod asInteger]
  								ifFalse:
+ 									[self assert: (self noAssertMethodClassAssociationOf: cogMethod methodObject)
- 									[ self assert: (self noAssertMethodClassAssociationOf: cogMethod methodObject)
  													= objectMemory nilObject.
  									 cogMethod
  										methodHeader: (coInterpreter rawHeaderOf: remappedMethod);
  										methodObject: remappedMethod]].
  						 (objectMemory isYoung: cogMethod methodObject) ifTrue:
  							[hasYoungObj := true]].
  					 self mapFor: cogMethod
  						 performUntil: #remapIfObjectRef:pc:hasYoung:
  						 arg: hasYoungObjPtr.
  					 hasYoungObj
  						ifTrue:
+ 							[methodZone ensureInYoungReferrers: cogMethod.
- 							[cogMethod cmRefersToYoung ifFalse:
- 								[cogMethod cmRefersToYoung: true.
- 								 methodZone addToYoungReferrers: cogMethod].
  							hasYoungObj := false]
+ 						ifFalse:
+ 							[cogMethod cmRefersToYoung: false]]].
- 						ifFalse: [cogMethod cmRefersToYoung: false]]].
  		cogMethod := methodZone methodAfter: cogMethod].
  	methodZone pruneYoungReferrers.
  	freedPIC ifTrue:
  		[self unlinkSendsToFree.
  		 codeModified := true].
  	codeModified ifTrue: "After updating oops in inline caches we need to flush the icache."
  		[processor flushICacheFrom: codeBase to: methodZone limitZony asInteger]!

Item was changed:
  ----- Method: Cogit>>markAndTraceLiteralsIn: (in category 'garbage collection') -----
  markAndTraceLiteralsIn: cogMethod
  	<option: #SpurMemoryManager>
  	"Unlink sends that have unmarked classes in inline caches or freed/freeable targets.
  	 Nil-out inline caches linked to open PICs.
  	 Assert that any selectors are marked.  We can do this since
  	 this is only run on marked methods and thus any selectors they
  	 reference should already be marked."
  	<var: #cogMethod type: #'CogMethod *'>
  	<inline: true>
  	self assert: ((cogMethod cmType = CMMethod
  				 and: [objectMemory isMarked: cogMethod methodObject])
  				 or: [cogMethod cmType = CMOpenPIC
  				 and: [(objectMemory isImmediate: cogMethod selector)
  					or: [objectMemory isMarked: cogMethod selector]]]).
+ 	objectRepresentation
+ 		markAndTraceLiteral: cogMethod selector
+ 		in: cogMethod
+ 		at: (self addressOf: cogMethod selector put: [:val| cogMethod selector: val]).
- 	objectRepresentation markAndTraceLiteral: cogMethod selector.
  	self maybeMarkCountersIn: cogMethod.
  	self maybeMarkIRCsIn: cogMethod.
  	self mapFor: cogMethod
  		 performUntil: #markLiterals:pc:method:
  		 arg: cogMethod asInteger!

Item was changed:
  ----- Method: Cogit>>markAndTraceObjectReferencesInGeneratedRuntime (in category 'jit - api') -----
  markAndTraceObjectReferencesInGeneratedRuntime
  	"Mark and trace any object references in the generated run-time."
  	0 to: runtimeObjectRefIndex - 1 do:
  		[:i| | mcpc literal |
  		 mcpc := objectReferencesInRuntime at: i.
+ 		 literal := backEnd literalBeforeFollowingAddress: mcpc asUnsignedInteger.
+ 		 objectRepresentation
+ 			markAndTraceLiteral: literal
+ 			in: (self cCoerceSimple: nil to: #'CogMethod *')
+ 			atpc: mcpc asUnsignedInteger]!
- 		 literal := backEnd literalBeforeFollowingAddress: mcpc asInteger.
- 		 objectRepresentation markAndTraceLiteral: literal]!

Item was changed:
  ----- Method: Cogit>>markLiterals:pc:method: (in category 'garbage collection') -----
  markLiterals: annotation pc: mcpc method: cogMethod
  	"Mark and trace literals.
  	 Additionally in Newspeak, void push implicits that have unmarked classes."
  	<var: #mcpc type: #'char *'>
  	| literal |
  	annotation = IsObjectReference ifTrue:
+ 		[literal := backEnd literalBeforeFollowingAddress: mcpc asUnsignedInteger.
+ 		 (objectRepresentation
+ 				markAndTraceLiteral: literal
+ 				in: (self cCoerceSimple: cogMethod to: #'CogMethod *')
+ 				atpc: mcpc asUnsignedInteger) ifTrue:
+ 			[codeModified := true]].
- 		[literal := backEnd literalBeforeFollowingAddress: mcpc asInteger.
- 		 objectRepresentation markAndTraceLiteral: literal].
  	(self isSendAnnotation: annotation) ifTrue:
  		[self offsetCacheTagAndCouldBeObjectAt: mcpc annotation: annotation into:
  			[:entryPoint :cacheTag :tagCouldBeObj |
  			 tagCouldBeObj ifTrue:
+ 				[(objectRepresentation
+ 						markAndTraceCacheTagLiteral: cacheTag
+ 						in: (self cCoerceSimple: cogMethod to: #'CogMethod *')
+ 						atpc: mcpc asUnsignedInteger) ifTrue:
+ 					[codeModified := true]].  "cacheTag is selector"
- 				[objectRepresentation markAndTraceLiteral: cacheTag].  "cacheTag is selector"
  			  self cppIf: NewspeakVM ifTrue:
  				[entryPoint = ceImplicitReceiverTrampoline ifTrue:
  					[| cacheAddress class mixin |
  					 self assert: NumOopsPerIRC = 2.
  					 cacheAddress := self implicitReceiverCacheAddressAt: mcpc.
+ 					 (class := backEnd unalignedLongAt: cacheAddress) ~= 0
- 					 class := backEnd unalignedLongAt: cacheAddress.
- 					 class ~= 0
  						ifTrue:
  							[(objectRepresentation cacheTagIsMarked: class)
  								ifTrue:
  									[(mixin := backEnd unalignedLongAt: cacheAddress + BytesPerOop) ~= 0 ifTrue:
+ 										[objectRepresentation
+ 											markAndTraceLiteral: mixin
+ 											in: (self cCoerceSimple: cogMethod to: #'CogMethod *')
+ 											at: (self asAddress: cacheAddress + BytesPerOop
+ 													put: [:val| backEnd unalignedLongAt: cacheAddress + BytesPerOop put: val])]]
- 										[objectRepresentation markAndTraceLiteral: mixin]]
  								ifFalse:
  									[backEnd
  										unalignedLongAt: cacheAddress put: 0;
  										unalignedLongAt: cacheAddress + BytesPerOop put: 0.
  									 codeModified := true]]
  						ifFalse:
  							[self assert: (backEnd unalignedLongAt: cacheAddress + BytesPerOop) = 0]]]]].
  	^0 "keep scanning"!

Item was changed:
  ----- Method: Cogit>>markLiteralsAndUnlinkIfUnmarkedSend:pc:method: (in category 'garbage collection') -----
  markLiteralsAndUnlinkIfUnmarkedSend: annotation pc: mcpc method: cogMethod
  	"Mark and trace literals.  Unlink sends that have unmarked cache tags or targets."
  	<var: #mcpc type: #'char *'>
  	| literal |
  	annotation = IsObjectReference ifTrue:
+ 		[literal := backEnd literalBeforeFollowingAddress: mcpc asUnsignedInteger.
+ 		 (objectRepresentation
+ 				markAndTraceLiteral: literal
+ 				in: (self cCoerceSimple: cogMethod to: #'CogMethod *')
+ 				atpc: mcpc asUnsignedInteger) ifTrue:
+ 			[codeModified := true]].
- 		[literal := backEnd literalBeforeFollowingAddress: mcpc asInteger.
- 		 objectRepresentation markAndTraceLiteral: literal].
  	(self isSendAnnotation: annotation) ifTrue:
  		[self offsetCacheTagAndCouldBeObjectAt: mcpc annotation: annotation into:
  			[:entryPoint :cacheTag :tagCouldBeObj | | cacheTagMarked |
  			 cacheTagMarked := tagCouldBeObj and: [objectRepresentation cacheTagIsMarked: cacheTag].
  			 entryPoint > methodZoneBase
  				ifTrue: "It's a linked send."
  					[self targetMethodAndSendTableFor: entryPoint into:
  						[:targetMethod :sendTable| | unlinkedRoutine |
  						 (cacheTagMarked not
+ 						  or: [self markAndTraceOrFreeCogMethod: targetMethod
+ 								firstVisit: targetMethod asUnsignedInteger > mcpc asUnsignedInteger]) ifTrue:
- 						  or: [self markAndTraceOrFreeCogMethod: targetMethod firstVisit: targetMethod asUnsignedInteger > mcpc asUnsignedInteger]) ifTrue:
  							["Either the cacheTag is unmarked (e.g. new class) or the target
  							  has been freed (because it is unmarked), so unlink the send."
  							 unlinkedRoutine := sendTable at: (targetMethod cmNumArgs min: NumSendTrampolines - 1).
  							 backEnd
  								rewriteInlineCacheAt: mcpc asInteger
  								tag: targetMethod selector
  								target: unlinkedRoutine.
  							 codeModified := true.
+ 							 objectRepresentation
+ 								markAndTraceLiteral: targetMethod selector
+ 								in: targetMethod
+ 								at: (self addressOf: targetMethod selector put: [:val| targetMethod selector: val])]]]
+ 				ifFalse:  "cacheTag is selector"
+ 					[(objectRepresentation
+ 							markAndTraceCacheTagLiteral: cacheTag
+ 							in: cogMethod
+ 							atpc: mcpc asUnsignedInteger) ifTrue:
+ 						[codeModified := true].
- 							 objectRepresentation markAndTraceLiteral: targetMethod selector]]]
- 				ifFalse:
- 					[objectRepresentation markAndTraceLiteral: cacheTag.  "cacheTag is selector"
  					 self cppIf: NewspeakVM ifTrue:
  						[entryPoint = ceImplicitReceiverTrampoline ifTrue:
  							[| cacheAddress class mixin |
+ 							 (objectRepresentation
+ 									markAndTraceCacheTagLiteral: cacheTag
+ 									in: cogMethod
+ 									atpc: mcpc asUnsignedInteger) ifTrue:
+ 								[codeModified := true].  "cacheTag is selector"
- 							 objectRepresentation markAndTraceLiteral: cacheTag.  "cacheTag is selector"
  							 self assert: NumOopsPerIRC = 2.
  							 cacheAddress := self implicitReceiverCacheAddressAt: mcpc.
+ 							 (class := backEnd unalignedLongAt: cacheAddress) ~= 0
- 							 class := backEnd unalignedLongAt: cacheAddress.
- 							 class ~= 0
  								ifTrue:
  									[(objectRepresentation cacheTagIsMarked: class)
  										ifTrue:
  											[(mixin := backEnd unalignedLongAt: cacheAddress + BytesPerOop) ~= 0 ifTrue:
+ 												[objectRepresentation
+ 													markAndTraceLiteral: mixin
+ 													in: (self cCoerceSimple: cogMethod to: #'CogMethod *')
+ 													at: (self asAddress: cacheAddress + BytesPerOop
+ 															put: [:val| backEnd unalignedLongAt: cacheAddress + BytesPerOop put: val])]]
- 												[objectRepresentation markAndTraceLiteral: mixin]]
  										ifFalse:
  											[backEnd
  												unalignedLongAt: cacheAddress put: 0;
  												unalignedLongAt: cacheAddress + BytesPerOop put: 0.
  											 codeModified := true]]
  								ifFalse:
  									[self assert: (backEnd unalignedLongAt: cacheAddress + BytesPerOop) = 0]]]]]].
  	^0 "keep scanning"!

Item was changed:
  ----- Method: Cogit>>markLiteralsAndUnlinkUnmarkedSendsIn: (in category 'garbage collection') -----
  markLiteralsAndUnlinkUnmarkedSendsIn: cogMethod
  	"Unlink sends that have unmarked classes in inline caches or freed/freeable targets.
  	 Nil-out inline caches linked to open PICs.
  	 Assert that any selectors are marked.  We can do this since
  	 this is only run on marked methods and thus any selectors they
  	 reference should already be marked."
  	<var: #cogMethod type: #'CogMethod *'>
  	<inline: true>
  	self assert: cogMethod cmType = CMMethod.
  	self assert: (objectMemory isMarked: cogMethod methodObject).
+ 	objectRepresentation
+ 		markAndTraceLiteral: cogMethod selector
+ 		in: cogMethod
+ 		at: (self addressOf: cogMethod selector put: [:val| cogMethod selector: val]).
- 	objectRepresentation markAndTraceLiteral: cogMethod selector.
  	self maybeMarkCountersIn: cogMethod.
  	self maybeMarkIRCsIn: cogMethod.
  	self mapFor: cogMethod
  		 performUntil: #markLiteralsAndUnlinkIfUnmarkedSend:pc:method:
  		 arg: cogMethod asInteger!

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"
  	coInterpreter
  		compilationBreak: aSelectorOop
  		point: (objectMemory lengthOf: aSelectorOop).
  	self assert: cogMethod cmType = CMMethod.
  	cogMethod selector: aSelectorOop.
+ 	(objectMemory isYoung: aSelectorOop) ifTrue:
+ 		[methodZone ensureInYoungReferrers: cogMethod]!
- 	(cogMethod cmRefersToYoung not
- 	 and: [objectMemory isYoung: aSelectorOop]) ifTrue:
- 		[self assert: (methodZone occurrencesInYoungReferrers: cogMethod) = 0.
- 		 cogMethod cmRefersToYoung: true.
- 		 methodZone addToYoungReferrers: cogMethod]!

Item was changed:
  ----- Method: CurrentImageCoInterpreterFacade>>debugStackPointersFor: (in category 'accessing') -----
  debugStackPointersFor: anOop
  	^CArrayAccessor on:
+ 		((StackDepthFinder on: (objectMap keyAtValue: anOop))
+ 			encoderClass: (coInterpreter encoderClassForHeader: (objectMap keyAtValue: anOop) header);
+ 			stackPointers)!
- 		(StackDepthFinder on: (objectMap keyAtValue: anOop))
- 			stackPointers!

Item was added:
+ ----- Method: CurrentImageCoInterpreterFacade>>isArrayNonImm: (in category 'testing') -----
+ isArrayNonImm: anOop
+ 	^(self objectForOop: anOop) class instSpec = Array instSpec!

Item was added:
+ ----- Method: CurrentImageCoInterpreterFacadeForSqueakV3ObjectRepresentation>>numSlotsOf: (in category 'accessing') -----
+ numSlotsOf: objOop 
+ 	"Answer the number of slots in the given non-immediate object.
+ 	 Does not adjust the size of contexts by stackPointer."
+ 	| obj elementSize wordSize |
+ 	obj := self objectForOop: objOop.
+ 	self deny: ([obj class isImmediateClass]
+ 				on: MessageNotUnderstood
+ 				do: [:ex| obj class == SmallInteger]).
+ 	wordSize := Smalltalk wordSize.
+ 	elementSize := 
+ 		[obj class elementSize]
+ 			on: MessageNotUnderstood
+ 			do: [:ex| obj class isBytes ifTrue: [1] ifFalse: [wordSize]].
+ 	wordSize = 4 ifTrue:
+ 		[^elementSize caseOf: {
+ 			[1]	->	[obj basicSize + 3 // wordSize].
+ 			[2]	->	[obj basicSize * 2 + 3 // wordSize].
+ 			[4]	->	[obj basicSize + obj class instSize] }].
+ 	^elementSize caseOf: {
+ 		[1]	->	[obj basicSize + (wordSize - 1) // wordSize].
+ 		[2]	->	[obj basicSize * 2 + (wordSize - 1) // wordSize].
+ 		[4]	->	[obj basicSize * 2 + (wordSize - 1) // wordSize].
+ 		[8]	->	[obj basicSize + obj class instSize] }!

Item was changed:
  ----- Method: InterpreterPrimitives>>primitiveNewMethod (in category 'compiled methods') -----
  primitiveNewMethod
  	| header bytecodeCount class size theMethod literalCount |
  	header := self stackTop.
  	bytecodeCount := self stackIntegerValue: 1.
  	self success: (objectMemory isIntegerObject: header).
  	self successful ifFalse: [^nil].
  	class := self stackValue: 2.
+ 	literalCount := self literalCountOfHeader: header.
+ 	size := literalCount + 1 * BytesPerWord + bytecodeCount.
- 	size := (self literalCountOfHeader: header) + 1 * BytesPerWord + bytecodeCount.
  	theMethod := objectMemory instantiateClass: class indexableSize: size.
  	objectMemory storePointerUnchecked: HeaderIndex ofObject: theMethod withValue: header.
- 	literalCount := self literalCountOfHeader: header.
  	1 to: literalCount do:
  		[:i | objectMemory storePointer: i ofObject: theMethod withValue: objectMemory nilObject].
  	self pop: 3 thenPush: theMethod!

Item was changed:
  ----- Method: SpurMemoryManager class>>initializeSpurObjectRepresentationConstants (in category 'class initialization') -----
  initializeSpurObjectRepresentationConstants
  	"SpurMemoryManager initializeSpurObjectRepresentationConstants"
  	BecamePointerObjectFlag := 1.
  	BecameCompiledMethodFlag := 2.
+ 	OldBecameNewFlag := 4.
+ 	"BecameClassFlag := 8" "this turns out not to be actionable"
- 	"BecameClassFlag := 4" "this turns out not to be actionable"
  !

Item was changed:
  ----- Method: SpurMemoryManager>>addFreeSubTree: (in category 'free space') -----
  addFreeSubTree: freeTree
  	"Add a freeChunk sub tree back into the large free chunk tree.
  	 This is for allocateOldSpaceChunkOf[Exactly]Bytes:[suchThat:]."
  	| bytesInArg treeNode bytesInNode subNode |
  	"N.B. *can't* use numSlotsOfAny: because of rounding up of odd slots
  	 and/or step in size at 1032 bytes in 32-bits or 2048 bytes in 64-bits."
  	self assert: (self isFreeObject: freeTree).
  	bytesInArg := self bytesInObject: freeTree.
  	self assert: bytesInArg >= (self numFreeLists * self allocationUnit).
  	treeNode := freeLists at: 0.
  	self assert: treeNode ~= 0.
  	[bytesInNode := self bytesInObject: treeNode.
+ 	 self assert: ((self oop: freeTree + bytesInArg isLessThanOrEqualTo: treeNode)
- 	 self assert: ((self oop: freeTree + bytesInArg isLessThan: treeNode)
  					or: [self oop: freeTree isGreaterThanOrEqualTo: treeNode + bytesInNode]).
  	 self assert: bytesInNode >= (self numFreeLists * self allocationUnit).
  	 self assert: bytesInArg ~= bytesInNode.
  	 bytesInNode > bytesInArg
  		ifTrue:
  			[subNode := self fetchPointer: self freeChunkSmallerIndex ofFreeChunk: treeNode.
  			 subNode = 0 ifTrue:
  				[self storePointer: self freeChunkSmallerIndex ofFreeChunk: treeNode withValue: freeTree.
  				 self storePointer: self freeChunkParentIndex ofFreeChunk: freeTree withValue: treeNode.
  				 ^self]]
  		ifFalse:
  			[subNode := self fetchPointer: self freeChunkLargerIndex ofFreeChunk: treeNode.
  			 subNode = 0 ifTrue:
  				[self storePointer: self freeChunkLargerIndex ofFreeChunk: treeNode withValue: freeTree.
  				 self storePointer: self freeChunkParentIndex ofFreeChunk: freeTree withValue: treeNode.
  				 ^self]].
  	 treeNode := subNode] repeat!

Item was changed:
  ----- Method: SpurMemoryManager>>become:with:twoWay:copyHash: (in category 'become api') -----
  become: array1 with: array2 twoWay: twoWayFlag copyHash: copyHashFlag
  	"All references to each object in array1 are swapped with all references to the
  	 corresponding object in array2. That is, all pointers to one object are replaced
  	 with with pointers to the other. The arguments must be arrays of the same length. 
  	 Answers PrimNoErr if the primitive succeeds, otherwise a relevant error code."
  	"Implementation: Uses lazy forwarding to defer updating references until message send."
  	| ec |
  	self assert: becomeEffectsFlags = 0.
  	self leakCheckBecome ifTrue:
  		[self runLeakCheckerForFullGC: true].
  	(self isArray: array1) ifFalse:
  		[^PrimErrBadReceiver].
  	((self isArray: array2)
  	 and: [(self numSlotsOf: array1) = (self numSlotsOf: array2)]) ifFalse:
  		[^PrimErrBadArgument].
  	(twoWayFlag or: [copyHashFlag])
  		ifTrue:
  			[ec := self containsOnlyValidBecomeObjects: array1 and: array2]
  		ifFalse:
  			[self followForwardedObjectFields: array2 toDepth: 0.
  			ec := self containsOnlyValidBecomeObjects: array1].
  	ec ~= 0 ifTrue: [^ec].
  
  	coInterpreter preBecomeAction.
  	twoWayFlag
  		ifTrue:
  			[self innerBecomeObjectsIn: array1 and: array2 copyHash: copyHashFlag]
  		ifFalse:
  			[self innerBecomeObjectsIn: array1 to: array2 copyHash: copyHashFlag].
  	self followSpecialObjectsOop.
+ 	self postBecomeScanClassTable: becomeEffectsFlags.
  	coInterpreter postBecomeAction: becomeEffectsFlags.
  	becomeEffectsFlags := 0.
  
  	self assert: self validClassTableHashes.
  	self leakCheckBecome ifTrue:
  		[self runLeakCheckerForFullGC: true].
  
  	^PrimNoErr "success"!

Item was changed:
  ----- Method: SpurMemoryManager>>doBecome:to:copyHash: (in category 'become implementation') -----
  doBecome: obj1 to: obj2 copyHash: copyHashFlag
  	| o1HashBits o2HashBits |
  	o1HashBits := self rawHashBitsOf: obj1.
  	o2HashBits := self rawHashBitsOf: obj2.
  	self forward: obj1 to: obj2.
+ 	((self isOldObject: obj1)
+ 	 and: [self isYoungObject: obj2]) ifTrue:
+ 		[becomeEffectsFlags := becomeEffectsFlags bitOr: OldBecameNewFlag].
  	copyHashFlag ifTrue: [self setHashBitsOf: obj2 to: o1HashBits].
  	"obj1 is on its way out.  Remove it from the classTable"
  	(o1HashBits ~= 0 and: [(self classAtIndex: o1HashBits) = obj1])
  		ifTrue: [self expungeFromClassTable: obj1]
  		ifFalse: [o1HashBits := 0]. "= 0 implies was not in class table"
  	self deny: (self isForwarded: obj2).
  	"o1HashBits ~= 0 implies obj1 was in class table and hence may have had instances.
  	 Therefore o1HashBits needs to refer to obj2 (put obj2 in table at o1HashBits)."
  	o1HashBits ~= 0 ifTrue:
  		[o2HashBits = 0 ifTrue: "obj2 has no hash; we're free to assign one"
  			[self setHashBitsOf: obj2 to: o1HashBits].
  		 self classAtIndex: o1HashBits put: obj2]!

Item was changed:
  ----- Method: SpurMemoryManager>>outOfPlaceBecome:and:copyHashFlag: (in category 'become implementation') -----
  outOfPlaceBecome: obj1 and: obj2 copyHashFlag: copyHashFlag
  	"Allocate two new objects, n1 & n2.  Copy the contents appropriately. Convert
  	 obj1 and obj2 into forwarding objects pointing to n2 and n1 respectively"
  	| clone1 clone2 |
  	clone1 := (self isContextNonImm: obj1)
  				ifTrue: [coInterpreter cloneContext: obj1]
  				ifFalse: [self clone: obj1].
  	clone2 := (self isContextNonImm: obj2)
  				ifTrue: [coInterpreter cloneContext: obj2]
  				ifFalse: [self clone: obj2].
  	copyHashFlag
  		ifTrue:
  			[self setHashBitsOf: clone1 to: (self rawHashBitsOf: obj2).
  			 self setHashBitsOf: clone2 to: (self rawHashBitsOf: obj1)]
  		ifFalse:
  			[self setHashBitsOf: clone1 to: (self rawHashBitsOf: obj1).
  			 self setHashBitsOf: clone2 to: (self rawHashBitsOf: obj2)].
  	self
  		forward: obj1 to: clone2;
+ 		forward: obj2 to: clone1.
+ 	((self isYoungObject: obj1) ~= (self isYoungObject: clone2)
+ 	 or: [(self isYoungObject: obj2) ~= (self isYoungObject: clone1)]) ifTrue:
+ 		[becomeEffectsFlags := becomeEffectsFlags bitOr: OldBecameNewFlag]!
- 		forward: obj2 to: clone1!

Item was added:
+ ----- Method: SpurMemoryManager>>postBecomeScanClassTable: (in category 'become implementation') -----
+ postBecomeScanClassTable: effectsFlags
+ 	"Scan the class table post-become (iff a pointer object was becommed) to ensure no forwarding
+ 	 pointers exist in the class table.
+ 	 Note that one-way become can cause duplications in the class table.
+ 	 When can these be eliminated?  We use the classTableBitmap to mark classTable entries
+ 	 (not the classes themselves, since marking a class doesn't help in knowing if its index is used).
+ 	 On image load, and during incrememtal scan-mark and full GC, classIndices are marked.
+ 	 We can somehow avoid following classes from the classTable until after this mark phase."
+ 	self assert: self validClassTableRootPages.
+ 
+ 	(effectsFlags anyMask: BecamePointerObjectFlag) ifFalse: [^self].
+ 
+ 	0 to: numClassTablePages - 1 do:
+ 		[:i| | page |
+ 		page := self fetchPointer: i ofObject: hiddenRootsObj.
+ 		self assert: (self isForwarded: page) not.
+ 		0 to: (self numSlotsOf: page) - 1 do:
+ 			[:j| | classOrNil |
+ 			classOrNil := self fetchPointer: j ofObject: page.
+ 			(classOrNil ~= nilObj
+ 			 and: [self isForwarded: classOrNil]) ifTrue:
+ 				[classOrNil := self followForwarded: classOrNil.
+ 				 self storePointer: j ofObject: page withValue: classOrNil]]]!

Item was changed:
  InstructionStream subclass: #StackDepthFinder
+ 	instanceVariableNames: 'stackp joins encoderClass'
- 	instanceVariableNames: 'stackp joins'
  	classVariableNames: ''
  	poolDictionaries: ''
  	category: 'VMMaker-Support'!

Item was added:
+ ----- Method: StackDepthFinder>>blockReturnConstant: (in category 'instruction decoding') -----
+ blockReturnConstant: value
+ 	"Return Constant From Block bytecode."
+ 	self resetStackAfterBranchOrReturn!

Item was added:
+ ----- Method: StackDepthFinder>>encoderClass (in category 'accessing') -----
+ encoderClass
+ 
+ 	^encoderClass!

Item was added:
+ ----- Method: StackDepthFinder>>encoderClass: (in category 'accessing') -----
+ encoderClass: anObject
+ 
+ 	encoderClass := anObject!

Item was changed:
  ----- Method: StackDepthFinder>>interpretNextInstructionFor: (in category 'decoding') -----
  interpretNextInstructionFor: client
  	joins at: pc put: stackp.
+ 	^encoderClass
+ 		ifNil: [super interpretNextInstructionFor: client]
+ 		ifNotNil: [encoderClass interpretNextInstructionFor: client in: self]!
- 	^super interpretNextInstructionFor: client!

Item was changed:
  ----- Method: StackDepthFinder>>stackPointers (in category 'accessing') -----
  stackPointers
  	"Collect the stack depth for each bytecode in the method.
  	 For the convenience of clients, write the stack depth for extended bytecodes
  	 to the bytecode pc, as well as the bytecocdes' extensions' pcs."
+ 	| method stackPointers end |
- 	| method encoderClass stackPointers end |
  	stackPointers :=  Array new: (end := (method := self method) endPC).
+ 	encoderClass ifNil: [encoderClass := method encoderClass].
- 	encoderClass := method encoderClass.
  	[pc <= end] whileTrue:
  		[stackPointers at: pc put: stackp.
  		 encoderClass extensionsAt: pc in: method into:
  			[:extA :extB :delta|
  			delta > 0 ifTrue:
  				[stackPointers at: pc + delta put: stackp]].
  		 self interpretNextInstructionFor: self].
  	^stackPointers!

Item was added:
+ ----- Method: StackDepthFinder>>trapIfNotInstanceOf: (in category 'instruction decoding') -----
+ trapIfNotInstanceOf: behaviorOrArrayOfBehavior
+ 	"If the top of stack is not an instance of either the argument, or, if the argument is an Array,
+ 	  any of the elements of the argument, send the class trap message to the current context."
+ 	self drop!

Item was changed:
  ----- Method: StackInterpreter class>>initializeBytecodeTableForSistaV1 (in category 'initialization') -----
  initializeBytecodeTableForSistaV1
  	"See e.g. the cass comment for EncoderForSistaV1"
  	"StackInterpreter initializeBytecodeTableForSistaV1"
  	"Note: This table will be used to generate a C switch statement."
  
  	BytecodeTable := Array new: 256.
+ 	BytecodeEncoderClassName := #EncoderForSistaV1.
  	self table: BytecodeTable from:
  	#(	"1 byte bytecodes"
  		(   0  15 pushReceiverVariableBytecode)
  		( 16  31 pushLiteralVariable16CasesBytecode)
  		( 32  63 pushLiteralConstantBytecode)
  		( 64  75 pushTemporaryVariableBytecode)
  		( 76	 pushReceiverBytecode)
  		( 77	 pushConstantTrueBytecode)
  		( 78	 pushConstantFalseBytecode)
  		( 79	 pushConstantNilBytecode)
  		( 80	 pushConstantZeroBytecode)
  		( 81	 pushConstantOneBytecode)
  		( 82	 extPushPseudoVariable)
  		( 83	 duplicateTopBytecode)
  	
  		( 84 87	unknownBytecode)
  		( 88	returnReceiver)
  		( 89	returnTrue)
  		( 90	returnFalse)
  		( 91	returnNil)
  		( 92	returnTopFromMethod)
  		( 93	returnNilFromBlock)
  		( 94	returnTopFromBlock)
  		( 95	extNopBytecode)
  
  		( 96	 bytecodePrimAdd)
  		( 97	 bytecodePrimSubtract)
  		( 98	 bytecodePrimLessThanSistaV1) "for booleanCheatSistaV1:"
  		( 99	 bytecodePrimGreaterThanSistaV1) "for booleanCheatSistaV1:"
  		(100	 bytecodePrimLessOrEqualSistaV1) "for booleanCheatSistaV1:"
  		(101	 bytecodePrimGreaterOrEqualSistaV1) "for booleanCheatSistaV1:"
  		(102	 bytecodePrimEqualSistaV1) "for booleanCheatSistaV1:"
  		(103	 bytecodePrimNotEqualSistaV1) "for booleanCheatSistaV1:"
  		(104	 bytecodePrimMultiply)
  		(105	 bytecodePrimDivide)
  		(106	 bytecodePrimMod)
  		(107	 bytecodePrimMakePoint)
  		(108	 bytecodePrimBitShift)
  		(109	 bytecodePrimDiv)
  		(110	 bytecodePrimBitAnd)
  		(111	 bytecodePrimBitOr)
  
  		(112	 bytecodePrimAt)
  		(113	 bytecodePrimAtPut)
  		(114	 bytecodePrimSize)
  		(115	 bytecodePrimNext)		 "i.e. a 0 arg special selector"
  		(116	 bytecodePrimNextPut)		 "i.e. a 1 arg special selector"
  		(117	 bytecodePrimAtEnd)
  		(118	 bytecodePrimIdenticalSistaV1) "for booleanCheatSistaV1:"
  		(119	 bytecodePrimClass)
  		(120	 bytecodePrimSpecialSelector24) "was blockCopy:"
  		(121	 bytecodePrimValue)
  		(122	 bytecodePrimValueWithArg)
  		(123	 bytecodePrimDo)			"i.e. a 1 arg special selector"
  		(124	 bytecodePrimNew)			"i.e. a 0 arg special selector"
  		(125	 bytecodePrimNewWithArg)	"i.e. a 1 arg special selector"
  		(126	 bytecodePrimPointX)		"i.e. a 0 arg special selector"
  		(127	 bytecodePrimPointY)		"i.e. a 0 arg special selector"
  
  		(128 143	sendLiteralSelector0ArgsBytecode)
  		(144 159	sendLiteralSelector1ArgBytecode)
  		(160 175	sendLiteralSelector2ArgsBytecode)
  
  		(176 183	shortUnconditionalJump)
  		(184 191	shortConditionalJumpTrue)
  		(192 199	shortConditionalJumpFalse)
  	
  		(200 207	storeAndPopReceiverVariableBytecode)
  		(208 215	storeAndPopTemporaryVariableBytecode)
  		(216		popStackBytecode)
  
  		(217 223	unknownBytecode)
  
  		"2 byte bytecodes"
  		(224		extABytecode)
  		(225		extBBytecode)
  
  		(226		extPushReceiverVariableBytecode)
  		(227		extPushLiteralVariableBytecode)
  		(228		extPushLiteralBytecode)
  		(229		longPushTemporaryVariableBytecode)
  		(230		pushClosureTempsBytecode)
  		(231		pushNewArrayBytecode)
  		(232		extPushIntegerBytecode)
  		(233		extPushCharacterBytecode)
  
  		(234		extSendBytecode)
  		(235		extSendSuperBytecode)
  
  		(236		extTrapIfNotInstanceOfBehaviorsBytecode)
  
  		(237		extUnconditionalJump)
  		(238		extJumpIfTrue)
  		(239		extJumpIfFalse)
  
  		(240		extStoreAndPopReceiverVariableBytecode)
  		(241		extStoreAndPopLiteralVariableBytecode)
  		(242		longStoreAndPopTemporaryVariableBytecode)
  
  		(243		extStoreReceiverVariableBytecode)
  		(244		extStoreLiteralVariableBytecode)
  		(245		longStoreTemporaryVariableBytecode)
  
  		(246 247	unknownBytecode)
  
  		"3 byte bytecodes"
  		(248		callPrimitiveBytecode)
  		(249		unknownBytecode) "reserved for Push Float"
  
  		(250		extPushClosureBytecode)
  		(251		pushRemoteTempLongBytecode)
  		(252		storeRemoteTempLongBytecode)
  		(253		storeAndPopRemoteTempLongBytecode)
  
  		(254 255	unknownBytecode)
  	)!

Item was changed:
  ----- Method: StackInterpreter>>literalCountOfHeader: (in category 'compiled methods') -----
  literalCountOfHeader: headerPointer
  	<api>
+ 	"We support two method header formats, as selected by the sign flag.  Even if the VM only
+ 	 has one bytecode set, supporting teh two formats here allows for instantiating methods in
+ 	 the other format for testing, etc."
+ 	^(self headerIndicatesAlternateBytecodeSet: headerPointer)
+ 		ifTrue: [self literalCountOfAlternateHeader: headerPointer]
- 	^self cppIf: MULTIPLEBYTECODESETS
- 		ifTrue: [(self headerIndicatesAlternateBytecodeSet: headerPointer)
- 					ifTrue: [self literalCountOfAlternateHeader: headerPointer]
- 					ifFalse: [self literalCountOfOriginalHeader: headerPointer]]
  		ifFalse: [self literalCountOfOriginalHeader: headerPointer]!

Item was changed:
  ----- Method: StackInterpreter>>printOopShortInner: (in category 'debug printing') -----
  printOopShortInner: oop
  	| classOop name nameLen |
  	<var: #name type: #'char *'>
  	<inline: true>
  	(objectMemory isImmediate: oop) ifTrue:
  		[(objectMemory isImmediateCharacter: oop) ifTrue:
  			[^self
  				printChar: $$;
  				printChar: (objectMemory characterValueOf: oop);
  				printChar: $(;
  				printHex: (objectMemory integerValueOf: oop);
  				printChar: $)].
  		^self
  			printNum: (objectMemory integerValueOf: oop);
  			printChar: $(;
  			printHex: (objectMemory integerValueOf: oop);
  			printChar: $)].
  	(objectMemory addressCouldBeObj: oop) ifFalse:
  		[^self print: ((oop bitAnd: objectMemory allocationUnit - 1) ~= 0
  						ifTrue: [' is misaligned']
  						ifFalse: [self whereIs: oop])].
  	(objectMemory isFreeObject: oop) ifTrue:
  		[^self print: ' is a free chunk'].
  	(objectMemory isForwarded: oop) ifTrue:
  		[^self print: ' is a forwarder to '; printHex: (objectMemory followForwarded: oop)].
  	(self isFloatObject: oop) ifTrue:
  		[^self printFloat: (self dbgFloatValueOf: oop)].
  	classOop := objectMemory fetchClassOfNonImm: oop.
  	(objectMemory addressCouldBeObj: classOop) ifFalse:
  		[^self print: 'a ??'].
  	(objectMemory numSlotsOf: classOop) = metaclassNumSlots ifTrue:
  		[^self printNameOfClass: oop count: 5].
  	oop = objectMemory nilObject ifTrue: [^self print: 'nil'].
  	oop = objectMemory trueObject ifTrue: [^self print: 'true'].
  	oop = objectMemory falseObject ifTrue: [^self print: 'false'].
  	nameLen := self lengthOfNameOfClass: classOop.
  	nameLen = 0 ifTrue: [^self print: 'a ??'].
  	name := self nameOfClass: classOop.
  	nameLen = 10 ifTrue:
  		[(self str: name n: 'ByteString' cmp: 10) = 0 "strncmp is weird" ifTrue:
  			[^self printChar: $'; printStringOf: oop; printChar: $'].
  		 (self str: name n: 'ByteSymbol' cmp: 10) = 0 "strncmp is weird" ifTrue:
  			[self printChar: $#; printStringOf: oop. ^self]].
  	(nameLen = 9 and: [(self str: name n: 'Character' cmp: 9) = 0]) ifTrue:
  		[^self printChar: $$; printChar: (objectMemory integerValueOf: (objectMemory fetchPointer: 0 ofObject: oop))].
  	self print: 'a(n) '.
  	self
  		cCode: [0 to: nameLen - 1 do: [:i| self printChar: (name at: i)]]
  		inSmalltalk:
  			[name isString
  				ifTrue: [self print: name]
  				ifFalse: [0 to: nameLen - 1 do: [:i| self printChar: (name at: i)]]].
  	"Try to spot association-like things; they're all subclasses of LookupKey"
+ 	((objectMemory isPointersNonImm: oop)
+ 	 and: [(objectMemory instanceSizeOf: classOop) = (ValueIndex + 1)
+ 	 and: [(objectMemory isBytes: (objectMemory fetchPointer: KeyIndex ofObject: oop))]]) ifTrue:
+ 		[| classLookupKey |
+ 		 classLookupKey := objectMemory fetchClassOfNonImm: (objectMemory splObj: SchedulerAssociation).
+ 		 [classLookupKey = objectMemory nilObject ifTrue:
+ 			[^self].
+ 		  (objectMemory instanceSizeOf: classLookupKey) = (KeyIndex + 1)] whileFalse:
+ 			[classLookupKey := self superclassOf: classLookupKey].
+ 		 (self includesBehavior: classOop ThatOf: classLookupKey) ifTrue:
+ 			[self space;
+ 				printOopShort: (objectMemory fetchPointer: KeyIndex ofObject: oop);
+ 				print: ' -> ';
+ 				printHex: (objectMemory fetchPointer: ValueIndex ofObject: oop)]]!
- 	((objectMemory instanceSizeOf: classOop) = (ValueIndex + 1)
- 	 and: [(self superclassOf: classOop) = (self superclassOf: (objectMemory fetchClassOfNonImm: (objectMemory splObj: SchedulerAssociation)))
- 	 and: [objectMemory isBytes: (objectMemory fetchPointer: KeyIndex ofObject: oop)]]) ifTrue:
- 		[self space;
- 			printOopShort: (objectMemory fetchPointer: KeyIndex ofObject: oop);
- 			print: ' -> ';
- 			printHex: (objectMemory fetchPointer: ValueIndex ofObject: oop)]!

Item was added:
+ ----- Method: VMClass>>asAddress:put: (in category 'translation support') -----
+ asAddress: address put: aBlock
+ 	<doNotGenerate>
+ 	"Simulate a C pointer.  Translates into address in C. Provides something
+ 	 that evaluates aBlock with the new value in response to at:put:"
+ 	^CPluggableAccessor new
+ 		setObject: nil;
+ 		atBlock: [:obj :idx| self error: 'cannot dereference pseudo-pointers']
+ 		atPutBlock: [:obj :idx :val| aBlock value: val]!

Item was changed:
  VMBasicConstants subclass: #VMSpurObjectRepresentationConstants
  	instanceVariableNames: ''
+ 	classVariableNames: 'BecameCompiledMethodFlag BecamePointerObjectFlag OldBecameNewFlag'
- 	classVariableNames: 'BecameCompiledMethodFlag BecamePointerObjectFlag'
  	poolDictionaries: ''
  	category: 'VMMaker-Interpreter'!



More information about the Vm-dev mailing list