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

commits at source.squeak.org commits at source.squeak.org
Fri Dec 6 21:34:05 UTC 2013


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

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

Name: VMMaker.oscog-eem.539
Author: eem
Time: 6 December 2013, 1:31:28.164 pm
UUID: b6a1dcf2-b6e4-4e22-9430-c660b115800b
Ancestors: VMMaker.oscog-eem.538

Slight streamlining in followForwardingPointersInStackZone:, plus
fixing followjng of frameMethodObject vs frameMethod in
machine-code frames.

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

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 we scan the receivers and
  	 methods 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: #thePage type: #'StackPage *'>
  	<var: #theSP type: #'char *'>
  	<var: #theFP type: #'char *'>
  	<var: #callerFP type: #'char *'>
  	<var: #theIPPtr type: #usqInt>
  
  	(theBecomeEffectsFlags anyMask: BecameCompiledMethodFlag) ifTrue:
  		[(objectMemory isForwarded: method) ifTrue:
  			[theIPPtr := instructionPointer - method.
  			 method := objectMemory followForwarded: method.
  			 instructionPointer := method + theIPPtr].
  		(objectMemory isForwarded: 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:
  			[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 asUnsignedInteger.
  					 theSP := theSP + BytesPerWord].
  			 [self assert: (thePage addressIsInPage: theFP).
  			  self assert: (theIPPtr = 0 or: [thePage addressIsInPage: theIPPtr asVoidPointer]).
  			  offset := self frameStackedReceiverOffset: theFP.
  			  oop := stackPages longAt: theFP + offset.
+ 			  (objectMemory isOopForwarded: oop) ifTrue:
- 			  ((objectMemory isNonImmediate: oop)
- 			   and: [(objectMemory isForwarded: oop)]) ifTrue:
  				[stackPages
  					longAt: theFP + offset
  					put: (objectMemory followForwarded: oop)].
  			  ((self frameHasContext: theFP)
  			   and: [(objectMemory isForwarded: (self frameContext: theFP))]) ifTrue:
  				[stackPages
  					longAt: theFP + FoxThisContext
  					put: (objectMemory followForwarded: (self frameContext: theFP))].
  			 (self isMachineCodeFrame: theFP)
  				ifTrue:
+ 					[oop := stackPages longAt: theFP + FoxMFReceiver.
+ 					 (objectMemory isOopForwarded: oop) ifTrue:
- 					[oop := stackPages longAt: theFP + FoxIFReceiver.
- 					 ((objectMemory isNonImmediate: oop)
- 					  and: [(objectMemory isForwarded: oop)]) ifTrue:
  						[stackPages
+ 							longAt: theFP + FoxMFReceiver
- 							longAt: theFP + FoxIFReceiver
  							put: (objectMemory followForwarded: oop)].
+ 					 oop := (self mframeHomeMethod: theFP) methodObject.
+ 					 self assert: (objectMemory isForwarded: oop) not]
- 					 self assert: (objectMemory isForwarded: (self frameMethodObject: theFP)) not]
  				ifFalse:
  					[oop := stackPages longAt: theFP + FoxIFReceiver.
+ 					 (objectMemory isOopForwarded: oop) ifTrue:
- 					 ((objectMemory isNonImmediate: oop)
- 					  and: [(objectMemory isForwarded: oop)]) ifTrue:
  						[stackPages
  							longAt: theFP + FoxIFReceiver
  							put: (objectMemory followForwarded: oop)].
+ 					 oop := self iframeMethod: theFP.
- 					 oop := self frameMethod: theFP.
  					 (objectMemory isForwarded: oop) ifTrue:
+ 						[| newOop delta |
+ 						 newOop := objectMemory followForwarded: oop.
+ 						 delta := newOop - oop.
- 						[| delta |
- 						 delta := (objectMemory followForwarded: oop) - oop.
  						 (theIPPtr ~= 0
+ 						  and: [(stackPages longAt: theIPPtr) > oop]) ifTrue:
- 						  and: [(stackPages longAt: theIPPtr) > (self frameMethod: theFP)]) ifTrue:
  							[stackPages
  								longAt: theIPPtr
  								put: (stackPages longAt: theIPPtr) + delta].
  						stackPages
  							longAt: theFP + FoxIFSavedIP
  							put: (stackPages longAt: theFP + FoxIFSavedIP) + delta.
  						stackPages
  							longAt: theFP + FoxMethod
+ 							put: (oop := newOop)]].
+ 			  self followNecessaryForwardingInMethod: oop.
- 							put: (objectMemory followForwarded: oop)]].
- 			  self followNecessaryForwardingInMethod: (self frameMethod: theFP).
  			  (callerFP := self frameCallerFP: theFP) ~= 0] whileTrue:
  				[theIPPtr := (theFP + FoxCallerSavedIP) asUnsignedInteger.
  				 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 we scan the receivers and
  	 methods 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: #thePage type: #'StackPage *'>
  	<var: #theSP type: #'char *'>
  	<var: #theFP type: #'char *'>
  	<var: #callerFP type: #'char *'>
  	<var: #theIPPtr type: #usqInt>
  
  	(theBecomeEffectsFlags anyMask: BecameCompiledMethodFlag) ifTrue:
  		[(objectMemory isForwarded: method) ifTrue:
  			[theIPPtr := instructionPointer - method.
  			 method := objectMemory followForwarded: method.
  			 instructionPointer := method + theIPPtr].
  		(objectMemory isForwarded: newMethod) ifTrue:
  			[newMethod := objectMemory followForwarded: newMethod]].
  
  	self assert: stackPage ~= 0.
  	0 to: numStackPages - 1 do:
  		[:i| | thePage theSP theFP callerFP theIP oop |
  		thePage := stackPages stackPageAt: i.
  		thePage isFree ifFalse:
  			[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 asUnsignedInteger.
  					 theSP := theSP + BytesPerWord].
  			 [self assert: (thePage addressIsInPage: theFP).
  			  self assert: (theIPPtr = 0 or: [thePage addressIsInPage: theIPPtr asVoidPointer]).
  			  oop := stackPages longAt: theFP + FoxReceiver.
+ 			  (objectMemory isOopForwarded: oop) ifTrue:
- 			  ((objectMemory isNonImmediate: oop)
- 			   and: [(objectMemory isForwarded: oop)]) ifTrue:
  				[stackPages
  					longAt: theFP + FoxReceiver
  					put: (objectMemory followForwarded: oop)].
  			  theIP := (theFP + (self frameStackedReceiverOffset: theFP)) asUnsignedInteger. "reuse theIP; its just an offset here"
  			  oop := stackPages longAt: theIP.
+ 			  (objectMemory isOopForwarded: oop) ifTrue:
- 			  ((objectMemory isNonImmediate: oop)
- 			   and: [(objectMemory isForwarded: oop)]) ifTrue:
  				[stackPages
  					longAt: theIP
  					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.
- 				[| delta |
  				 theIPPtr ~= 0 ifTrue:
  					[self assert: (stackPages longAt: theIPPtr) > (self frameMethod: theFP).
+ 					 delta := newOop - oop.
- 					 delta := (objectMemory followForwarded: oop) - oop.
  					 stackPages
  						longAt: theIPPtr
  						put: (stackPages longAt: theIPPtr) + delta].
  				stackPages
  					longAt: theFP + FoxMethod
+ 					put: (oop := newOop)].
+ 			  self followNecessaryForwardingInMethod: oop.
- 					put: (objectMemory followForwarded: oop)].
- 			  self followNecessaryForwardingInMethod: (self frameMethod: theFP).
  			  (callerFP := self frameCallerFP: theFP) ~= 0] whileTrue:
  				[theIPPtr := (theFP + FoxCallerSavedIP) asUnsignedInteger.
  				 theFP := callerFP]]]!



More information about the Vm-dev mailing list