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

commits at source.squeak.org commits at source.squeak.org
Sat Aug 15 08:21:36 UTC 2015


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

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

Name: VMMaker.oscog-eem.1433
Author: eem
Time: 15 August 2015, 1:19:34.476 am
UUID: 9ad71bda-65b6-4a4b-a0a1-97c45ec115cd
Ancestors: VMMaker.oscog-eem.1432

Good to know the max number of live pages on map as well and this makeds for cleaner counting code.

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

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 *'>
+ 	| numLivePages |
+ 	numLivePages := 0.
- 	stackPages countStackPagesMap.
  	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).
+ 			 numLivePages := numLivePages + 1.
- 			 stackPages countLivePageWhenMapping.
  			 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]]].
+ 	stackPages recordLivePagesOnMapping: numLivePages!
- 				 theSP := theSP + objectMemory wordSize]]]!

Item was changed:
  CogClass subclass: #CogStackPages
+ 	instanceVariableNames: 'coInterpreter objectMemory pages mostRecentlyUsedPage overflowLimit bytesPerPage statNumMaps statPageCountWhenMappingSum statMaxPageCountWhenMapping'
- 	instanceVariableNames: 'coInterpreter objectMemory pages mostRecentlyUsedPage overflowLimit bytesPerPage statNumMaps statPageCountWhenMappingSum'
  	classVariableNames: ''
  	poolDictionaries: 'VMBasicConstants'
  	category: 'VMMaker-Interpreter'!
  
  !CogStackPages commentStamp: 'eem 8/14/2015 16:43' prior: 0!
  I am a class that helps organize the StackInterpreter's collection of stack pages.  I hold the set of stack pages represented by InterpreterStackPage instances/StackPage structs.  The pages are held in a doubly-linked list that notionally has two heads:
  
  mostRecentlyUsedPage-->used page<->used page<->used page<->used page<--leastRecentlyUsedPage
                                         ^                        <-next-prev->                         ^
                                          |                                                                       |
                                          v                        <-prev-next->                         v
                                          free page<->free page<->free page<->free page
  
  In fact we don't need the least-recently-used page, and so it is only present conceptually.  The point is that there is a possibly empty but contiguous sequence of free pages starting at mostRecentlyUsedPage nextPage.  New pages are allocated preferentially from the free page next to the MRUP.
  If there are no free pages then (effectively) the LRUP's frames are flushed to contexts and it is used instead.
  
  I have two concrete classes, one for the StackInterpreter and one for the CoInterpreter.
  
  Instance Variables
  	bytesPerPage:						<Integer>
  	coInterpreter:						<StackInterpreter>
  	mostRecentlyUsedPage:			<CogStackPage>
  	objectMemory:						<ObjectMemory|SpurMemoryManager>
  	overflowLimit:						<Integer>
  	pages:								<Array of: CogStackPage>
  	statNumMaps:						<Integer>
  	statPageCountWhenMappingSum:		<Integer>
  
  bytesPerPage
  	- the size of a page in bytes
  
  coInterpreter
  	- the interpreter the receiver is holding pages for
  
  mostRecentlyUsedPage
  	- the most recently used stack page
  
  objectMemory
  	- the objectMemory of the interpreter
  
  overflowLimit
  	- the length in bytes of the portion of teh stack that can be used for frames before the page is judged to have overflowed
  
  pages
  	- the collection of stack pages the receiver is managing
  
  statNumMaps
  	- the number of mapStackPages calls
  
  statPageCountWhenMappingSum:
  	- the sum of the number of in use pages at each mapStackPages, used to estimate the average number of in use pages at scavenge, which heavily influences scavenger performance
  !

Item was removed:
- ----- Method: CogStackPages>>countLivePageWhenMapping (in category 'accessing') -----
- countLivePageWhenMapping
- 	<inline: true>
- 	statPageCountWhenMappingSum := statPageCountWhenMappingSum + 1!

Item was removed:
- ----- Method: CogStackPages>>countStackPagesMap (in category 'accessing') -----
- countStackPagesMap
- 	<inline: true>
- 	statNumMaps := statNumMaps + 1!

Item was changed:
  ----- Method: CogStackPages>>initialize (in category 'initialization') -----
  initialize
  	"Here we can initialize the variables C initializes to zero.  #initialize methods do /not/ get translated."
+ 	statNumMaps := statPageCountWhenMappingSum := statMaxPageCountWhenMapping := 0!
- 	statNumMaps := statPageCountWhenMappingSum := 0!

Item was added:
+ ----- Method: CogStackPages>>recordLivePagesOnMapping: (in category 'statistics') -----
+ recordLivePagesOnMapping: numLivePages
+ 	<inline: true>
+ 	statNumMaps := statNumMaps + 1.
+ 	statPageCountWhenMappingSum := statPageCountWhenMappingSum + numLivePages.
+ 	statMaxPageCountWhenMapping := statMaxPageCountWhenMapping max: numLivePages!

Item was added:
+ ----- Method: CogStackPages>>statMaxPageCountWhenMapping (in category 'statistics') -----
+ statMaxPageCountWhenMapping
+ 	<cmacro: '() GIV(statMaxPageCountWhenMapping)'>
+ 	^statMaxPageCountWhenMapping!

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 *'>
+ 	| numLivePages |
+ 	numLivePages := 0.
- 	stackPages countStackPagesMap.
  	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).
+ 			 numLivePages := numLivePages + 1.
- 			 stackPages countLivePageWhenMapping.
  			 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]]].
+ 	stackPages recordLivePagesOnMapping: numLivePages!
- 				 theSP := theSP + objectMemory wordSize]]]!

Item was changed:
  ----- Method: StackInterpreterPrimitives>>primitiveVMParameter (in category 'system control primitives') -----
(excessive size, no diff calculated)



More information about the Vm-dev mailing list