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

commits at source.squeak.org commits at source.squeak.org
Thu May 7 01:04:00 UTC 2015


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

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

Name: VMMaker.oscog-eem.1292
Author: eem
Time: 6 May 2015, 6:01:52.857 pm
UUID: 0cde527f-cdb5-4345-adad-7dd496ef023e
Ancestors: VMMaker.oscog-eem.1291

Fix a regression in externalInstVar:ofContext:.  The
head frame pointers must be written back if we're
going to map a machince code pc to a bytecode pc
in case of code reclamation.

Add asserts to the stack page enumerators to check
that the head frame pointers have been written back.

Use macros for the oop comparisons, avoiding
cCoerce:, to get faster simulation and avoid the
inliner not inlining in conditionals.

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

Item was changed:
  ----- Method: CoInterpreter>>externalInstVar:ofContext: (in category 'frame access') -----
  externalInstVar: offset ofContext: aContext
  	"Fetch an instance variable from a maybe married context.
  	 If the context is still married compute the value of the
  	 relevant inst var from the spouse frame's state.
  
  	 If the context is single but has a negative instruction pointer
  	 recognise that the instruction pointer is actually into machine
  	 code and convert it to the corresponding bytecode pc."
  	<inline: false>
  	| value |
  
  	self assert: (objectMemory isContext: aContext).
  	"method, closureOrNil & receiver need no special handling; only
  	 sender, pc & stackp have to be computed for married contexts."
  	((self isReadMediatedContextInstVarIndex: offset)
  	 and: [self isMarriedOrWidowedContext: aContext]) ifFalse:
  		[value := objectMemory fetchPointer: offset ofObject: aContext.
  		 ^(offset = InstructionPointerIndex
  		    and: [(objectMemory isIntegerObject: value)
  		    and: [value signedIntFromLong < 0]])
+ 			ifTrue: [self externalWriteBackHeadFramePointers.
+ 					self mustMapMachineCodePC: (objectMemory integerValueOf: value)
- 			ifTrue: [self mustMapMachineCodePC: (objectMemory integerValueOf: value)
  						context: aContext]
  			ifFalse: [value]].
  
  	self externalWriteBackHeadFramePointers.
  	^(self isStillMarriedContext: aContext)
  		ifTrue: [self fetchPointer: offset ofMarriedContext: aContext]
  		ifFalse: [objectMemory fetchPointer: offset ofObject: aContext]!

Item was changed:
  ----- Method: CoInterpreter>>followForwardingPointersInStackZone: (in category 'object memory support') -----
  followForwardingPointersInStackZone: theBecomeEffectsFlags
  	"Spur's become: is lazy, turning the becommed object into a forwarding object to the other.
  	 The read-barrier is minimised by arranging that forwarding pointers will fail a method cache
  	 probe, since notionally objects' internals are accessed only via sending messages to them,
  	 the exception is primitives that access the internals of the non-receiver argument(s).
  
  	 To avoid a read barrier on bytecode, literal and inst var fetch and non-local return, we scan
  	 the receivers (including the stacked receiver for non-local return) and method references
  	 in the stack zone and follow any forwarded ones.  This is of course way cheaper than
  	 scanning all of memory as in the old become.
  
  	 Override to handle machine code frames"
  	| theIPPtr |
  	<inline: false>
  	<var: #theSP type: #'char *'>
  	<var: #theFP type: #'char *'>
  	<var: #theIPPtr type: #usqInt>
  	<var: #callerFP type: #'char *'>
  	<var: #thePage type: #'StackPage *'>
  
  	self externalWriteBackHeadFramePointers.
  
  	(theBecomeEffectsFlags anyMask: BecameCompiledMethodFlag) ifTrue:
  		[(objectMemory isForwarded: method) ifTrue:
  			[theIPPtr := instructionPointer - method.
  			 method := objectMemory followForwarded: method.
  			 instructionPointer := method + theIPPtr].
  		(objectMemory isOopForwarded: newMethod) ifTrue:
  			[newMethod := objectMemory followForwarded: newMethod]].
  
  	self assert: stackPage ~= 0.
  	0 to: numStackPages - 1 do:
  		[:i| | thePage theSP theFP callerFP oop offset |
  		thePage := stackPages stackPageAt: i.
  		thePage isFree ifFalse:
+ 			[self assert: (self ifCurrentStackPageHasValidHeadPointers: thePage).
+ 			 theFP := thePage headFP.
- 			[theFP := thePage  headFP.
  			 theIPPtr := thePage = stackPage ifTrue: [0] ifFalse: [thePage headSP asUnsignedInteger].
  			 [self assert: (thePage addressIsInPage: theFP).
  			  self assert: (theIPPtr = 0 or: [thePage addressIsInPage: theIPPtr asVoidPointer]).
+ 			  (self isMachineCodeFrame: theFP)
- 			 (self isMachineCodeFrame: theFP)
  				ifTrue:
  					[oop := stackPages longAt: theFP + FoxMFReceiver.
  					 (objectMemory isOopForwarded: oop) ifTrue:
  						[stackPages
  							longAt: theFP + FoxMFReceiver
  							put: (objectMemory followForwarded: oop)].
  					 self assert: (objectMemory isForwarded: (self mframeHomeMethod: theFP) methodObject) not]
  				ifFalse:
  					[oop := stackPages longAt: theFP + FoxIFReceiver.
  					 (objectMemory isOopForwarded: oop) ifTrue:
  						[stackPages
  							longAt: theFP + FoxIFReceiver
  							put: (objectMemory followForwarded: oop)].
  					 oop := self iframeMethod: theFP.
  					 (objectMemory isForwarded: oop) ifTrue:
  						[| newOop |
  						 newOop := objectMemory followForwarded: oop.
  						 offset := newOop - oop.
  						 (theIPPtr ~= 0
  						  and: [(stackPages longAt: theIPPtr) > oop]) ifTrue:
  							[stackPages
  								longAt: theIPPtr
  								put: (stackPages longAt: theIPPtr) + offset].
  						stackPages
  							longAt: theFP + FoxIFSavedIP
  							put: (stackPages longAt: theFP + FoxIFSavedIP) + offset.
  						stackPages
  							longAt: theFP + FoxMethod
  							put: (oop := newOop)]].
  			  ((self frameHasContext: theFP)
  			   and: [(objectMemory isForwarded: (self frameContext: theFP))]) ifTrue:
  				[stackPages
  					longAt: theFP + FoxThisContext
  					put: (objectMemory followForwarded: (self frameContext: theFP))].
  			  offset := self frameStackedReceiverOffset: theFP.
  			  oop := stackPages longAt: theFP + offset.
  			  (objectMemory isOopForwarded: oop) ifTrue:
  				[stackPages
  					longAt: theFP + offset
  					put: (objectMemory followForwarded: oop)].
  			  (callerFP := self frameCallerFP: theFP) ~= 0] whileTrue:
  				[theIPPtr := (theFP + FoxCallerSavedIP) asUnsignedInteger.
  				 theFP := callerFP].
  			 "And finally follow the saved context and the caller context."
  			 theSP := thePage baseAddress - objectMemory wordSize.
  			 [theSP <= thePage baseAddress] whileTrue:
  				[oop := stackPages longAt: theSP.
  				 (objectMemory isForwarded: oop) ifTrue:
  					[stackPages longAt: theSP put: (objectMemory followForwarded: oop)].
  				 theSP := theSP + objectMemory wordSize]]]!

Item was changed:
  ----- Method: CoInterpreter>>mapStackPages (in category 'object memory support') -----
  mapStackPages
  	<inline: #never>
  	<var: #thePage type: #'StackPage *'>
  	<var: #theSP type: #'char *'>
  	<var: #theFP type: #'char *'>
  	<var: #frameRcvrOffset type: #'char *'>
  	<var: #callerFP type: #'char *'>
  	<var: #theIPPtr type: #'char *'>
  	0 to: numStackPages - 1 do:
  		[:i| | thePage theSP theFP frameRcvrOffset callerFP theIPPtr theIP oop |
  		thePage := stackPages stackPageAt: i.
  		thePage isFree ifFalse:
+ 			[self assert: (self ifCurrentStackPageHasValidHeadPointers: thePage).
+ 			 theSP := thePage headSP.
- 			[theSP := thePage headSP.
  			 theFP := thePage  headFP.
  			 "Skip the instruction pointer on top of stack of inactive pages."
  			 thePage = stackPage
  				ifTrue: [theIPPtr := ((self isMachineCodeFrame: theFP)
  									or: [(self iframeSavedIP: theFP) = 0])
  										ifTrue: [0]
  										ifFalse: [theFP + FoxIFSavedIP]]
  				ifFalse:
  					[theIPPtr := theSP.
  					 theSP := theSP + objectMemory wordSize].
  			[self assert: (thePage addressIsInPage: theFP).
  			 self assert: (thePage addressIsInPage: theSP).
  			 self assert: (theIPPtr = 0 or: [thePage addressIsInPage: theIPPtr]).
  			 frameRcvrOffset := self frameReceiverLocation: theFP.
  	 		  [theSP <= frameRcvrOffset] whileTrue:
  				[oop := stackPages longAt: theSP.
  				 (objectMemory shouldRemapOop: oop) ifTrue:
  					[stackPages longAt: theSP put: (objectMemory remapObj: oop)].
  				 theSP := theSP + objectMemory wordSize].
  			 (self frameHasContext: theFP) ifTrue:
  				[(objectMemory shouldRemapObj: (self frameContext: theFP)) ifTrue:
  					[stackPages
  						longAt: theFP + FoxThisContext
  						put: (objectMemory remapObj: (self frameContext: theFP))].
  				 "forwarding scheme in SqueakV3 obj rep makes this hard to check."
  				 objectMemory hasSpurMemoryManagerAPI ifTrue:
  					[self assert: ((self isMarriedOrWidowedContext: (self frameContext: theFP))
  								and: [(self frameOfMarriedContext: (self frameContext: theFP)) = theFP])]].
  			(self isMachineCodeFrame: theFP) ifFalse:
  				[(objectMemory shouldRemapObj: (self iframeMethod: theFP)) ifTrue:
  					[theIPPtr ~= 0 ifTrue:
  						[theIP := stackPages longAt: theIPPtr.
  						 theIP = cogit ceReturnToInterpreterPC
  							ifTrue:
  								[self assert: (self iframeSavedIP: theFP) > (self iframeMethod: theFP).
  								 theIPPtr := theFP + FoxIFSavedIP.
  								 theIP := stackPages longAt: theIPPtr]
  							ifFalse:
  								[self assert: theIP > (self iframeMethod: theFP)].
  						 theIP := theIP - (self iframeMethod: theFP)].
  					 stackPages
  						longAt: theFP + FoxMethod
  						put: (objectMemory remapObj: (self iframeMethod: theFP)).
  					 theIPPtr ~= 0 ifTrue:
  						[stackPages longAt: theIPPtr put: theIP + (self iframeMethod: theFP)]]].
  			 (callerFP := self frameCallerFP: theFP) ~= 0] whileTrue:
  				[theSP := (theIPPtr := theFP + FoxCallerSavedIP) + objectMemory wordSize.
  				 theFP := callerFP].
  			 theSP := theFP + FoxCallerSavedIP + objectMemory wordSize.
  			 [theSP <= thePage baseAddress] whileTrue:
  				[oop := stackPages longAt: theSP.
  				 (objectMemory shouldRemapOop: oop) ifTrue:
  					[stackPages longAt: theSP put: (objectMemory remapObj: oop)].
  				 theSP := theSP + objectMemory wordSize]]]!

Item was changed:
  ----- Method: CoInterpreter>>markAndTraceStackPage: (in category 'object memory support') -----
  markAndTraceStackPage: thePage
  	| theSP theFP frameRcvrOffset callerFP oop |
  	<var: #thePage type: #'StackPage *'>
  	<var: #theSP type: #'char *'>
  	<var: #theFP type: #'char *'>
  	<var: #frameRcvrOffset type: #'char *'>
  	<var: #callerFP type: #'char *'>
  	<inline: false>
  
  	self assert: (stackPages isFree: thePage) not.
+ 	self assert: (self ifCurrentStackPageHasValidHeadPointers: thePage).
  	self assert: thePage trace ~= StackPageTraced.
  	thePage trace: StackPageTraced.
  
  	theSP := thePage headSP.
  	theFP := thePage  headFP.
  	"Skip the instruction pointer on top of stack of inactive pages."
  	thePage = stackPage ifFalse:
  		[theSP := theSP + objectMemory wordSize].
  	[frameRcvrOffset := self frameReceiverLocation: theFP.
  	 [theSP <= frameRcvrOffset] whileTrue:
  		[oop := stackPages longAt: theSP.
  		 (objectMemory isOopForwarded: oop) ifTrue:
  			[oop := objectMemory followForwarded: oop.
  			 stackPages longAt: theSP put: oop].
  		 (objectMemory isImmediate: oop) ifFalse:
  			[objectMemory markAndTrace: oop].
  		 theSP := theSP + objectMemory wordSize].
  	(self frameHasContext: theFP) ifTrue:
  		[self assert: (objectMemory isContext: (self frameContext: theFP)).
  		 objectMemory markAndTrace: (self frameContext: theFP)].
  	(self isMachineCodeFrame: theFP)
  		ifTrue: [self markAndTraceMachineCodeMethod: (self mframeCogMethod: theFP)]
  		ifFalse: [objectMemory markAndTrace: (self iframeMethod: theFP)].
  	(callerFP := self frameCallerFP: theFP) ~= 0] whileTrue:
  		[theSP := theFP + FoxCallerSavedIP + objectMemory wordSize.
  		 theFP := callerFP].
  	theSP := theFP + FoxCallerSavedIP + objectMemory wordSize. "caller ip is ceBaseReturnPC"
  	[theSP <= thePage baseAddress] whileTrue:
  		[oop := stackPages longAt: theSP.
  		 (objectMemory isOopForwarded: oop) ifTrue:
  			[oop := objectMemory followForwarded: oop.
  			 stackPages longAt: theSP put: oop].
  		 (objectMemory isImmediate: oop) ifFalse:
  			[objectMemory markAndTrace: oop].
  		 theSP := theSP + objectMemory wordSize]!

Item was changed:
  ----- Method: CoInterpreter>>markCogMethodsAndReferentsOnPage: (in category 'frame access') -----
  markCogMethodsAndReferentsOnPage: thePage
  	<var: #thePage type: #'StackPage *'>
  	| theFP callerFP |
  	<var: #theFP type: #'char *'>
  	<var: #callerFP type: #'char *'>
  	<inline: false>
  	self assert: (stackPages isFree: thePage) not.
+ 	self assert: (self ifCurrentStackPageHasValidHeadPointers: thePage).
  	theFP := thePage headFP.
  	"Skip the instruction pointer on top of stack of inactive pages."
  	[(self isMachineCodeFrame: theFP) ifTrue:
  		[cogit markMethodAndReferents: (self mframeCogMethod: theFP)].
  	(callerFP := self frameCallerFP: theFP) ~= 0] whileTrue:
  		[theFP := callerFP]!

Item was changed:
  ----- Method: StackInterpreter>>followForwardingPointersInStackZone: (in category 'object memory support') -----
  followForwardingPointersInStackZone: theBecomeEffectsFlags
  	"Spur's become: is lazy, turning the becommed object into a forwarding object to the other.
  	 The read-barrier is minimised by arranging that forwarding pointers will fail a method cache
  	 probe, since notionally objects' internals are accessed only via sending messages to them,
  	 the exception is primitives that access the internals of the non-receiver argument(s).
  
  	 To avoid a read barrier on bytecode, literal and inst var fetch and non-local return, we scan
  	 the receivers (including the stacked receiver for non-local return) and method references
  	 in the stack zone and follow any forwarded ones.  This is of course way cheaper than
  	 scanning all of memory as in the old become."
  	| theIPPtr |
  	<inline: false>
  	<var: #theFP type: #'char *'>
  	<var: #theIPPtr type: #usqInt>
  	<var: #callerFP type: #'char *'>
  	<var: #thePage type: #'StackPage *'>
  
  	self externalWriteBackHeadFramePointers.
  
  	(theBecomeEffectsFlags anyMask: BecameCompiledMethodFlag) ifTrue:
  		[(objectMemory isForwarded: method) ifTrue:
  			[theIPPtr := instructionPointer - method.
  			 method := objectMemory followForwarded: method.
  			 instructionPointer := method + theIPPtr].
  		(objectMemory isOopForwarded: newMethod) ifTrue:
  			[newMethod := objectMemory followForwarded: newMethod]].
  
  	self assert: stackPage ~= 0.
  	0 to: numStackPages - 1 do:
  		[:i| | thePage theFP callerFP ptr oop |
  		thePage := stackPages stackPageAt: i.
  		thePage isFree ifFalse:
+ 			[self assert: (self ifCurrentStackPageHasValidHeadPointers: thePage).
+ 			 theFP := thePage  headFP.
- 			[theFP := thePage  headFP.
  			 "Skip the instruction pointer on top of stack of inactive pages."
  			 theIPPtr := thePage = stackPage ifTrue: [0] ifFalse: [thePage headSP asUnsignedInteger].
  			 [self assert: (thePage addressIsInPage: theFP).
  			  self assert: (theIPPtr = 0 or: [thePage addressIsInPage: theIPPtr asVoidPointer]).
  			  oop := stackPages longAt: theFP + FoxReceiver.
  			  (objectMemory isOopForwarded: oop) ifTrue:
  				[stackPages
  					longAt: theFP + FoxReceiver
  					put: (objectMemory followForwarded: oop)].
  			  ((self frameHasContext: theFP)
  			   and: [(objectMemory isForwarded: (self frameContext: theFP))]) ifTrue:
  				[stackPages
  					longAt: theFP + FoxThisContext
  					put: (objectMemory followForwarded: (self frameContext: theFP))].
  			  oop := self frameMethod: theFP.
  			  (objectMemory isForwarded: oop) ifTrue:
  				[| newOop delta |
  				 newOop := objectMemory followForwarded: oop.
  				 theIPPtr ~= 0 ifTrue:
  					[self assert: (stackPages longAt: theIPPtr) > (self frameMethod: theFP).
  					 delta := newOop - oop.
  					 stackPages
  						longAt: theIPPtr
  						put: (stackPages longAt: theIPPtr) + delta].
  				stackPages
  					longAt: theFP + FoxMethod
  					put: (oop := newOop)].
  			  ptr := (theFP + (self frameStackedReceiverOffset: theFP)) asInteger.
  			  oop := stackPages longAt: ptr.
  			  (objectMemory isOopForwarded: oop) ifTrue:
  				[stackPages
  					longAt: ptr
  					put: (objectMemory followForwarded: oop)].
  			  (callerFP := self frameCallerFP: theFP) ~= 0] whileTrue:
  				[theIPPtr := (theFP + FoxCallerSavedIP) asInteger.
  				 theFP := callerFP].
  			 "And finally follow the caller context."
  			 self assert: theFP = thePage baseFP.
  			 oop := self frameCallerContext: theFP.
  			 (objectMemory isForwarded: oop) ifTrue:
  				[self frameCallerContext: theFP put: (objectMemory followForwarded: oop)]]]!

Item was added:
+ ----- Method: StackInterpreter>>ifCurrentStackPageHasValidHeadPointers: (in category 'stack pages') -----
+ ifCurrentStackPageHasValidHeadPointers: thePage
+ 	"If thePage is the stackPage and the stackPointer and/or the framePointer are pointing within it,
+ 	 answer if thePage's heapSP and headFP are equal to the stackPointer and framePointer respectively."
+ 	<var: #thePage type: #'StackPage *'>
+ 	thePage = stackPage ifTrue:
+ 		[(thePage addressIsInPage: framePointer) ifTrue:
+ 			[thePage headFP ~= framePointer ifTrue:
+ 				[^false]].
+ 		(thePage addressIsInPage: stackPointer) ifTrue:
+ 			[thePage headSP ~= stackPointer ifTrue:
+ 				[^false]]].
+ 	^true!

Item was changed:
  ----- Method: StackInterpreter>>mapStackPages (in category 'object memory support') -----
  mapStackPages
  	<inline: #never>
  	<var: #thePage type: #'StackPage *'>
  	<var: #theSP type: #'char *'>
  	<var: #theFP type: #'char *'>
  	<var: #callerFP type: #'char *'>
  	<var: #theIPPtr type: #'char *'>
  	0 to: numStackPages - 1 do:
  		[:i| | thePage theSP theFP callerFP theIPPtr theIP oop |
  		thePage := stackPages stackPageAt: i.
  		thePage isFree ifFalse:
+ 			[self assert: (self ifCurrentStackPageHasValidHeadPointers: thePage).
+ 			 theSP := thePage headSP.
- 			[theSP := thePage headSP.
  			 theFP := thePage  headFP.
  			 "Skip the instruction pointer on top of stack of inactive pages."
  			 thePage = stackPage
  				ifTrue: [theIPPtr := 0]
  				ifFalse:
  					[theIPPtr := theSP.
  					 theSP := theSP + objectMemory wordSize].
  			[self assert: (thePage addressIsInPage: theFP).
  			 self assert: (thePage addressIsInPage: theSP).
  			 self assert: (theIPPtr = 0 or: [thePage addressIsInPage: theIPPtr]).
  			 [theSP <= (theFP + FoxReceiver)] whileTrue:
  				[oop := stackPages longAt: theSP.
  				 (objectMemory shouldRemapOop: oop) ifTrue:
  					[stackPages longAt: theSP put: (objectMemory remapObj: oop)].
  				 theSP := theSP + objectMemory wordSize].
  			 (self frameHasContext: theFP) ifTrue:
  				[(objectMemory shouldRemapObj: (self frameContext: theFP)) ifTrue:
  					[stackPages
  						longAt: theFP + FoxThisContext
  						put: (objectMemory remapObj: (self frameContext: theFP))].
  				 "With SqueakV3 objectMemory can't assert since object body is yet to move."
  				 objectMemory hasSpurMemoryManagerAPI ifTrue:
  					[self assert: ((self isMarriedOrWidowedContext: (self frameContext: theFP))
  								  and: [(self frameOfMarriedContext: (self frameContext: theFP)) = theFP])]].
  			 (objectMemory shouldRemapObj: (self frameMethod: theFP)) ifTrue:
  				[theIPPtr ~= 0 ifTrue:
  					[self assert: (stackPages longAt: theIPPtr) > (self frameMethod: theFP).
  					 theIP := (stackPages longAt: theIPPtr) - (self frameMethod: theFP)].
  				 stackPages
  					longAt: theFP + FoxMethod
  					put: (objectMemory remapObj: (self frameMethod: theFP)).
  				 theIPPtr ~= 0 ifTrue:
  					[stackPages longAt: theIPPtr put: theIP + (self frameMethod: theFP)]].
  			 (callerFP := self frameCallerFP: theFP) ~= 0] whileTrue:
  				[theSP := (theIPPtr := theFP + FoxCallerSavedIP) + objectMemory wordSize.
  				 theFP := callerFP].
  			 theSP := theFP + FoxCallerContext. "a.k.a. FoxCallerSavedIP"
  			 [theSP <= thePage baseAddress] whileTrue:
  				[oop := stackPages longAt: theSP.
  				 (objectMemory shouldRemapOop: oop) ifTrue:
  					[stackPages longAt: theSP put: (objectMemory remapObj: oop)].
  				 theSP := theSP + objectMemory wordSize]]]!

Item was changed:
  ----- Method: StackInterpreter>>markAndTraceStackPage: (in category 'object memory support') -----
  markAndTraceStackPage: thePage
  	| theSP theFP frameRcvrOffset callerFP oop |
  	<var: #thePage type: #'StackPage *'>
  	<var: #theSP type: #'char *'>
  	<var: #theFP type: #'char *'>
  	<var: #frameRcvrOffset type: #'char *'>
  	<var: #callerFP type: #'char *'>
  	<inline: false>
  
  	self assert: (stackPages isFree: thePage) not.
+ 	self assert: (self ifCurrentStackPageHasValidHeadPointers: thePage).
  	self assert: thePage trace ~= StackPageTraced.
  	thePage trace: StackPageTraced.
  
  	theSP := thePage headSP.
  	theFP := thePage  headFP.
  	"Skip the instruction pointer on top of stack of inactive pages."
  	thePage = stackPage ifFalse:
  		[theSP := theSP + objectMemory wordSize].
  	[frameRcvrOffset := self frameReceiverLocation: theFP.
  	 [theSP <= frameRcvrOffset] whileTrue:
  		[oop := stackPages longAt: theSP.
  		 (objectMemory isOopForwarded: oop) ifTrue:
  			[oop := objectMemory followForwarded: oop.
  			 stackPages longAt: theSP put: oop].
  		 (objectMemory isImmediate: oop) ifFalse:
  			[objectMemory markAndTrace: oop].
  		 theSP := theSP + objectMemory wordSize].
  	(self frameHasContext: theFP) ifTrue:
  		[self assert: (objectMemory isContext: (self frameContext: theFP)).
  		 objectMemory markAndTrace: (self frameContext: theFP)].
  	objectMemory markAndTrace: (self iframeMethod: theFP).
  	(callerFP := self frameCallerFP: theFP) ~= 0] whileTrue:
  		[theSP := theFP + FoxCallerSavedIP + objectMemory wordSize.
  		 theFP := callerFP].
  	theSP := theFP + FoxCallerSavedIP. "caller ip is frameCallerContext in a base frame"
  	[theSP <= thePage baseAddress] whileTrue:
  		[oop := stackPages longAt: theSP.
  		 (objectMemory isOopForwarded: oop) ifTrue:
  			[oop := objectMemory followForwarded: oop.
  			 stackPages longAt: theSP put: oop].
  		 (objectMemory isImmediate: oop) ifFalse:
  			[objectMemory markAndTrace: oop].
  		 theSP := theSP + objectMemory wordSize]!

Item was changed:
  ----- Method: VMClass>>oop:isGreaterThan: (in category 'oop comparison') -----
  oop: anOop isGreaterThan: otherOop
+ 	"Compare two oop values, treating them as object memory locations; i.e. use unsigned comparisons.
+ 	 Use a macro, instead of #cCoerce:to: to provide fast simulation and inline code in conditionals,
+ 	 since the inliner doesn't inline in condtionals."
+ 	<cmacro: '(anOop,otherOop) ((usqInt)(anOop) > (usqInt)(otherOop))'>
+ 	^anOop > otherOop!
- 	"Compare two oop values, treating them as object memory locations.
- 	Use #cCoerce:to: to ensure comparison of unsigned magnitudes. This
- 	method will be inlined during C translation."
- 	<inline: true>
- 	^(self cCoerce: anOop to: #usqInt)
- 		> (self cCoerce: otherOop to: #usqInt)!

Item was changed:
  ----- Method: VMClass>>oop:isGreaterThan:andLessThan: (in category 'oop comparison') -----
  oop: anOop isGreaterThan: baseOop andLessThan: limitOop
+ 	"Compare two oop values, treating them as object memory locations; i.e. use unsigned comparisons.
+ 	 Use a macro, instead of #cCoerce:to: to provide fast simulation and inline code in conditionals,
+ 	 since the inliner doesn't inline in condtionals."
+ 	<cmacro: '(anOop,baseOop,limitOop) ((usqInt)(anOop) > (usqInt)(baseOop) && (usqInt)(anOop) < (usqInt)(limitOop))'>
+ 	^anOop > baseOop and: [anOop < limitOop]!
- 	"Compare two oop values, treating them as object memory locations.
- 	Use #cCoerce:to: to ensure comparison of unsigned magnitudes. This
- 	method will be inlined during C translation."
- 	<inline: true>
- 	^(self cCoerce: anOop to: #usqInt) > (self cCoerce: baseOop to: #usqInt)
- 	  and: [(self cCoerce: anOop to: #usqInt) < (self cCoerce: limitOop to: #usqInt)]!

Item was changed:
  ----- Method: VMClass>>oop:isGreaterThanOrEqualTo: (in category 'oop comparison') -----
  oop: anOop isGreaterThanOrEqualTo: otherOop
+ 	"Compare two oop values, treating them as object memory locations; i.e. use unsigned comparisons.
+ 	 Use a macro, instead of #cCoerce:to: to provide fast simulation and inline code in conditionals,
+ 	 since the inliner doesn't inline in condtionals."
+ 	<cmacro: '(anOop,otherOop) ((usqInt)(anOop) >= (usqInt)(otherOop))'>
+ 	^anOop >= otherOop!
- 	"Compare two oop values, treating them as object memory locations.
- 	Use #cCoerce:to: to ensure comparison of unsigned magnitudes. This
- 	method will be inlined during C translation."
- 	<inline: true>
- 	^(self cCoerce: anOop to: #usqInt)
- 		>= (self cCoerce: otherOop to: #usqInt)!

Item was changed:
  ----- Method: VMClass>>oop:isGreaterThanOrEqualTo:andLessThan: (in category 'oop comparison') -----
  oop: anOop isGreaterThanOrEqualTo: baseOop andLessThan: limitOop
+ 	"Compare two oop values, treating them as object memory locations; i.e. use unsigned comparisons.
+ 	 Use a macro, instead of #cCoerce:to: to provide fast simulation and inline code in conditionals,
+ 	 since the inliner doesn't inline in condtionals."
+ 	<cmacro: '(anOop,baseOop,limitOop) ((usqInt)(anOop) >= (usqInt)(baseOop) && (usqInt)(anOop) < (usqInt)(limitOop))'>
+ 	^anOop >= baseOop and: [anOop < limitOop]!
- 	"Compare two oop values, treating them as object memory locations.
- 	Use #cCoerce:to: to ensure comparison of unsigned magnitudes. This
- 	method will be inlined during C translation."
- 	<inline: true>
- 	^(self cCoerce: anOop to: #usqInt) >= (self cCoerce: baseOop to: #usqInt)
- 	  and: [(self cCoerce: anOop to: #usqInt) < (self cCoerce: limitOop to: #usqInt)]!

Item was changed:
  ----- Method: VMClass>>oop:isGreaterThanOrEqualTo:andLessThanOrEqualTo: (in category 'oop comparison') -----
  oop: anOop isGreaterThanOrEqualTo: baseOop andLessThanOrEqualTo: limitOop
+ 	"Compare two oop values, treating them as object memory locations; i.e. use unsigned comparisons.
+ 	 Use a macro, instead of #cCoerce:to: to provide fast simulation and inline code in conditionals,
+ 	 since the inliner doesn't inline in condtionals."
+ 	<cmacro: '(anOop,baseOop,limitOop) ((usqInt)(anOop) >= (usqInt)(baseOop) && (usqInt)(anOop) <= (usqInt)(limitOop))'>
+ 	^anOop >= baseOop and: [anOop <= limitOop]!
- 	"Compare two oop values, treating them as object memory locations.
- 	Use #cCoerce:to: to ensure comparison of unsigned magnitudes. This
- 	method will be inlined during C translation."
- 	<inline: true>
- 	^(self cCoerce: anOop to: #usqInt) >= (self cCoerce: baseOop to: #usqInt)
- 	  and: [(self cCoerce: anOop to: #usqInt) <= (self cCoerce: limitOop to: #usqInt)]!

Item was changed:
  ----- Method: VMClass>>oop:isLessThan: (in category 'oop comparison') -----
  oop: anOop isLessThan: otherOop
+ 	"Compare two oop values, treating them as object memory locations; i.e. use unsigned comparisons.
+ 	 Use a macro, instead of #cCoerce:to: to provide fast simulation and inline code in conditionals,
+ 	 since the inliner doesn't inline in condtionals."
+ 	<cmacro: '(anOop,otherOop) ((usqInt)(anOop) < (usqInt)(otherOop))'>
+ 	^anOop < otherOop!
- 	"Compare two oop values, treating them as object memory locations.
- 	Use #cCoerce:to: to ensure comparison of unsigned magnitudes. This
- 	method will be inlined during C translation."
- 	<inline: true>
- 	^(self cCoerce: anOop to: #usqInt) < (self cCoerce: otherOop to: #usqInt)!

Item was changed:
  ----- Method: VMClass>>oop:isLessThanOrEqualTo: (in category 'oop comparison') -----
  oop: anOop isLessThanOrEqualTo: otherOop
+ 	"Compare two oop values, treating them as object memory locations; i.e. use unsigned comparisons.
+ 	 Use a macro, instead of #cCoerce:to: to provide fast simulation and inline code in conditionals,
+ 	 since the inliner doesn't inline in condtionals."
+ 	<cmacro: '(anOop,otherOop) ((usqInt)(anOop) <= (usqInt)(otherOop))'>
+ 	^anOop <= otherOop!
- 	"Compare two oop values, treating them as object memory locations.
- 	Use #cCoerce:to: to ensure comparison of unsigned magnitudes. This
- 	method will be inlined during C translation."
- 	<inline: true>
- 	^(self cCoerce: anOop to: #usqInt)
- 		<= (self cCoerce: otherOop to: #usqInt)!



More information about the Vm-dev mailing list