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

commits at source.squeak.org commits at source.squeak.org
Sat Jan 17 22:08:20 UTC 2015


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

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

Name: VMMaker.oscog-eem.1023
Author: eem
Time: 17 January 2015, 2:06:56.3 pm
UUID: 3b0b931e-e8b1-4155-ac38-8a078ddcec98
Ancestors: VMMaker.oscog-eem.1022

Spur:
Rename and correct ensureSemaphoreForwardedThroughContext:
to ensureSemaphoreUnforwardedThroughContext:, its intended
function.

Make shouldRemapObj: filter-out objects already in newSpace
since mapStackPages, va mapInterpreterOops, can visit objects
twice in a scavenge, GC, compact sequence.

General:
Speed up assert engines by using addressIsInPage: instead of
stackPageFor:.

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

Item was changed:
  ----- Method: CoInterpreter>>assertValidExecutionPointe:r:s:imbar:line: (in category 'debug support') -----
  assertValidExecutionPointe: lip r: lifp s: lisp imbar: inInterpreter line: ln
  	<var: #lip type: #usqInt>
  	<var: #lifp type: #'char *'>
  	<var: #lisp type: #'char *'>
  	| methodField cogMethod theIP  |
  	<var: #cogMethod type: #'CogMethod *'>
- 	self assert: stackPage = (stackPages stackPageFor: lifp) l: ln.
  	self assert: stackPage = stackPages mostRecentlyUsedPage l: ln.
+ 	self assert: (stackPage addressIsInPage: lifp) l: ln.
  	self assert: (self deferStackLimitSmashAround: #assertValidStackLimits: asSymbol with: ln).
- 	self assert: lifp < stackPage baseAddress l: ln.
  	self assert: lisp < lifp l: ln.
  	self assert: lifp > lisp l: ln.
  	self assert: lisp >= (stackPage realStackLimit - self stackLimitOffset) l: ln.
  	self assert: (lifp - lisp) / objectMemory bytesPerOop < LargeContextSlots l: ln.
  	methodField := self frameMethodField: lifp.
  	inInterpreter
  		ifTrue:
  			[self assert: (self isMachineCodeFrame: lifp) not l: ln.
  			 self assert: method = methodField l: ln.
  			 self cppIf: MULTIPLEBYTECODESETS
  				ifTrue: [self assert: (self methodUsesAlternateBytecodeSet: method) = (bytecodeSetSelector = 256) l: ln].
  			 (self asserta: (objectMemory cheapAddressCouldBeInHeap: methodField) l: ln) ifTrue:
  				[theIP := lip = cogit ceReturnToInterpreterPC
  							ifTrue: [self iframeSavedIP: lifp]
  							ifFalse: [lip].
  				 self assert: (theIP >= (methodField + (objectMemory lastPointerOf: methodField))
  							  and: [theIP < (methodField + (objectMemory numBytesOf: methodField) + objectMemory baseHeaderSize - 1)])
  					l: ln].
  			 self assert: ((self iframeIsBlockActivation: lifp)
  					or: [(self pushedReceiverOrClosureOfFrame: lifp) = (self iframeReceiver: lifp)])
  				l: ln]
  		ifFalse:
  			[self assert: (self isMachineCodeFrame: lifp) l: ln.
  			 ((self asserta: methodField asUnsignedInteger >= cogit minCogMethodAddress l: ln)
  			  and: [self asserta: methodField asUnsignedInteger < cogit maxCogMethodAddress l: ln]) ifTrue:
  				[cogMethod := self mframeHomeMethod: lifp.
  				 self assert: (lip > (methodField + ((self mframeIsBlockActivation: lifp)
  													ifTrue: [self sizeof: CogBlockMethod]
  													ifFalse: [self sizeof: CogMethod]))
  						and: [lip < (methodField + cogMethod blockSize)])
  					l: ln].
  			 self assert: ((self mframeIsBlockActivation: lifp)
  					or: [(self pushedReceiverOrClosureOfFrame: lifp) = (self mframeReceiver: lifp)])
  				l: ln].
  	(self isBaseFrame: lifp) ifTrue:
  		[self assert: (self frameHasContext: lifp) l: ln.
  		 self assert: (self frameContext: lifp) = (stackPages longAt: stackPage baseAddress - objectMemory wordSize) l: ln]!

Item was changed:
  ----- Method: CoInterpreter>>synchronousSignal: (in category 'process primitive support') -----
  synchronousSignal: aSemaphore 
  	"Signal the given semaphore from within the interpreter.
  	 Answer if the current process was preempted.
  	 Override to add tracing info."
  	| excessSignals |
  	<inline: false>
  	(self isEmptyList: aSemaphore) ifTrue:
  		["no process is waiting on this semaphore"
  		 excessSignals := self fetchInteger: ExcessSignalsIndex ofObject: aSemaphore.
  		 self storeInteger: ExcessSignalsIndex
  			ofObject: aSemaphore
  			withValue: excessSignals + 1.
  		 ^false].
  
+ 	objectMemory ensureSemaphoreUnforwardedThroughContext: aSemaphore.
- 	objectMemory ensureSemaphoreForwardedThroughContext: aSemaphore.
  
  	^self resume: (self removeFirstLinkOfList: aSemaphore)
  		preemptedYieldingIf: preemptionYields
  		from: CSSignal!

Item was changed:
  ----- Method: CoInterpreterStackPages>>pageListIsWellFormed (in category 'assertions') -----
  pageListIsWellFormed
  	"Answer if the stack page list is well-formed.
  	 MRUP-->used page<->used page<->used page<->used page<--LRUP
  	               ^                        <-next-prev->                         ^
  	                |                                                                       |
  	                v                        <-prev-next->                         v
  	                free page<->free page<->free page<->free page"
  	| ok page count limit |
  	<inline: false>
  	<var: #page type: #'StackPage *'>
  	ok := true.
  	page := mostRecentlyUsedPage nextPage.
  	count := 1.
  	limit := coInterpreter numStkPages * 2.
  	[page isFree
  	 and: [page ~= mostRecentlyUsedPage
  	 and: [count <= limit]]] whileTrue:
  		[(self asserta: page nextPage prevPage == page) ifFalse:
  			[ok := false].
  		 page := page nextPage.
  		 count := count + 1].
  	[page ~= mostRecentlyUsedPage
  	 and: [count <= limit]] whileTrue:
  		[(self asserta: page nextPage prevPage == page) ifFalse:
  			[ok := false].
  		 (self asserta: page isFree not)
  			ifTrue:
+ 				[(self asserta: ((page addressIsInPage: page baseFP)
+ 								and: [page addressIsInPage: page headSP])) ifFalse:
- 				[(self asserta: (self stackPageFor: page baseFP) == page) ifFalse:
- 					[ok := false].
- 				 (self asserta: (self stackPageFor: page headSP) == page) ifFalse:
  					[ok := false]]
  			ifFalse:
  				[ok := false].
  		 page := page nextPage.
  		 count := count + 1].
  	(self asserta: count = coInterpreter numStkPages) ifFalse:
  		[ok := false].
  	^ok!

Item was changed:
  ----- Method: InterpreterStackPages>>pageListIsWellFormed (in category 'assertions') -----
  pageListIsWellFormed
  	"Answer if the stack page list is well-formed.
  	 MRUP-->used page<->used page<->used page<->used page<--LRUP
  	               ^                        <-next-prev->                         ^
  	                |                                                                       |
  	                v                        <-prev-next->                         v
  	                free page<->free page<->free page<->free page"
  	| ok page count limit |
  	<inline: false>
  	<var: #page type: #'StackPage *'>
  	ok := true.
  	page := mostRecentlyUsedPage nextPage.
  	count := 1.
  	limit := numPages * 2.
  	[page isFree
  	 and: [page ~= mostRecentlyUsedPage
  	 and: [count <= limit]]] whileTrue:
  		[(self asserta: page nextPage prevPage == page) ifFalse:
  			[ok := false].
  		 page := page nextPage.
  		 count := count + 1].
  	[page ~= mostRecentlyUsedPage
  	 and: [count <= limit]] whileTrue:
  		[(self asserta: page nextPage prevPage == page) ifFalse:
  			[ok := false].
  		 (self asserta: page isFree not)
  			ifTrue:
+ 				[(self asserta: ((page addressIsInPage: page baseFP)
+ 								and: [page addressIsInPage: page headSP])) ifFalse:
- 				[(self asserta: (self stackPageFor: page baseFP) == page) ifFalse:
- 					[ok := false].
- 				 (self asserta: (self stackPageFor: page headSP) == page) ifFalse:
  					[ok := false]]
  			ifFalse:
  				[ok := false].
  		 page := page nextPage.
  		 count := count + 1].
  	(self asserta: count = numPages) ifFalse:
  		[ok := false].
  	^ok!

Item was removed:
- ----- Method: ObjectMemory>>ensureSemaphoreForwardedThroughContext: (in category 'forward compatibility') -----
- ensureSemaphoreForwardedThroughContext: aSemaphore
- 	"Compatibility with SpurMemoryManager"
- 	<inline: true>!

Item was added:
+ ----- Method: ObjectMemory>>ensureSemaphoreUnforwardedThroughContext: (in category 'forward compatibility') -----
+ ensureSemaphoreUnforwardedThroughContext: aSemaphore
+ 	"Compatibility with SpurMemoryManager"
+ 	<inline: true>!

Item was removed:
- ----- Method: SpurMemoryManager>>ensureSemaphoreForwardedThroughContext: (in category 'interpreter access') -----
- ensureSemaphoreForwardedThroughContext: aSemaphore
- 	"Make sure that the aSemaphore is forwarded through to the suspendedContext of the first link."
- 	<inline: true>
- 	(self isForwarded: (self fetchPointer: FirstLinkIndex ofObject: aSemaphore)) ifTrue:
- 		["0 = aSemaphore, 1 = aProcess. Hence references to suspendedContext will /not/ be forwarded."
- 		 self followForwardedObjectFields: aSemaphore toDepth: 1].
- 	self deny: (self isForwarded: (self
- 									fetchPointer: SuspendedContextIndex
- 									ofObject: (self fetchPointer: FirstLinkIndex ofObject: aSemaphore)))!

Item was added:
+ ----- Method: SpurMemoryManager>>ensureSemaphoreUnforwardedThroughContext: (in category 'interpreter access') -----
+ ensureSemaphoreUnforwardedThroughContext: aSemaphore
+ 	"Make sure that the aSemaphore is followed through to the suspendedContext of the first link."
+ 	<inline: true>
+ 	| proc ctxt |
+ 	proc := self fetchPointer: FirstLinkIndex ofObject: aSemaphore.
+ 	(self isForwarded: proc) ifTrue:
+ 		[self followForwardedObjectFields: aSemaphore toDepth: 1.
+ 		 proc := self fetchPointer: FirstLinkIndex ofObject: aSemaphore].
+ 	self deny: (self isForwarded: proc).
+ 	ctxt := self fetchPointer: SuspendedContextIndex ofObject: proc.
+ 	(self isForwarded: ctxt) ifTrue:
+ 		[ctxt := self followForwarded: ctxt.
+ 		 self storePointer: SuspendedContextIndex ofObject: proc withValue: ctxt]!

Item was added:
+ ----- Method: SpurMemoryManager>>isFreeOop: (in category 'object testing') -----
+ isFreeOop: oop
+ 	^(self isNonImmediate: oop) and: [self isFreeObject: oop]!

Item was changed:
  ----- Method: SpurMemoryManager>>isValidFreeObject: (in category 'free space') -----
  isValidFreeObject: objOop
  	| chunk |
  	^(self addressCouldBeOldObj: objOop)
  	  and: [(self isFreeObject: objOop)
  	  and: [(self oop: (self addressAfter: objOop) isLessThanOrEqualTo: endOfMemory)
  	  and: [((chunk := (self fetchPointer: self freeChunkNextIndex ofFreeChunk: objOop)) = 0
+ 		   or: [self isFreeOop: chunk])
+ 	  and: [(self isLargeFreeObject: objOop) not
- 		   or: [self isFreeObject: chunk])
- 	  and: [(self bytesInObject: objOop) < (self numFreeLists * self allocationUnit)
  		    or: [((chunk := (self fetchPointer: self freeChunkParentIndex ofFreeChunk: objOop)) = 0
+ 			   or: [(self isFreeOop: chunk) and: [self isLargeFreeObject: chunk]])
- 			   or: [self isFreeObject: chunk])
  			  and: [((chunk := (self fetchPointer: self freeChunkSmallerIndex ofFreeChunk: objOop)) = 0
+ 				    or: [(self isFreeOop: chunk) and: [self isLargeFreeObject: chunk]])
- 				    or: [self isFreeObject: chunk])
  			  and: [(chunk := (self fetchPointer: self freeChunkLargerIndex ofFreeChunk: objOop)) = 0
+ 				    or: [(self isFreeOop: chunk) and: [self isLargeFreeObject: chunk]]]]]]]]]!
- 				    or: [self isFreeObject: chunk]]]]]]]]!

Item was changed:
  ----- Method: SpurMemoryManager>>shouldRemapObj: (in category 'gc - scavenging') -----
  shouldRemapObj: objOop
  	<api>
  	"Answer if the obj should be scavenged (or simply followed). The method is called
+ 	 shouldRemapObj: for compatibility with ObjectMemory.  We test for being already
+ 	 scavenged because mapStackPages via mapInterpeeterOops may be applied twice
+ 	 in the context of a global GC where a scavenge, followed by a scan-mark-free, and
+ 	 final compaction passes may result in scvenged fields being visited twice."
- 	 shouldRemapObj: for compatibility with ObjectMemory."
  	^(self isForwarded: objOop)
+ 	  or: [(self isReallyYoungObject: objOop)
+ 		 and: [(self isInFutureSpace: objOop) not]]!
- 	  or: [self deny: (self isInFutureSpace: objOop).
- 		  self isReallyYoungObject: objOop]!

Item was changed:
  ----- Method: StackInterpreter>>assertValidExecutionPointe:r:s:imbar:line: (in category 'debug support') -----
  assertValidExecutionPointe: lip r: lfp s: lsp imbar: inInterpreter line: ln
  	<var: #lip type: #usqInt>
  	<var: #lfp type: #'char *'>
  	<var: #lsp type: #'char *'>
  	self assert: inInterpreter l: ln.
- 	self assert: stackPage = (stackPages stackPageFor: lfp) l: ln.
  	self assert: stackPage = stackPages mostRecentlyUsedPage l: ln.
  	self assertValidStackLimits: ln.
+ 	self assert: (stackPage addressIsInPage: lfp) l: ln.
- 	self assert: lfp < stackPage baseAddress l: ln.
  	self assert: lsp < lfp l: ln.
  	self assert: lfp > lsp l: ln.
  	self assert: lsp >= (stackPage realStackLimit - self stackLimitOffset) l: ln.
  	self assert: (lfp - lsp) / objectMemory bytesPerOop < LargeContextSlots l: ln.
  	self assert: (self validInstructionPointer: lip inFrame: lfp) l: ln.
  	self assert: ((self frameIsBlockActivation: lfp)
  				or: [(self pushedReceiverOrClosureOfFrame: lfp) = (self frameReceiver: lfp)])
  		l: ln.
  	self assert: method = (self frameMethod: lfp) l: ln.
  	self cppIf: MULTIPLEBYTECODESETS
  		ifTrue: [self assert: (self methodUsesAlternateBytecodeSet: method) = (bytecodeSetSelector = 256)  l: ln].!

Item was changed:
  ----- Method: StackInterpreter>>synchronousSignal: (in category 'process primitive support') -----
  synchronousSignal: aSemaphore 
  	"Signal the given semaphore from within the interpreter.
  	 Answer if the current process was preempted."
  	| excessSignals |
  	<inline: false>
  	(self isEmptyList: aSemaphore) ifTrue:
  		["no process is waiting on this semaphore"
  		 excessSignals := self fetchInteger: ExcessSignalsIndex ofObject: aSemaphore.
  		 self storeInteger: ExcessSignalsIndex
  			ofObject: aSemaphore
  			withValue: excessSignals + 1.
  		 ^false].
  
+ 	objectMemory ensureSemaphoreUnforwardedThroughContext: aSemaphore.
- 	objectMemory ensureSemaphoreForwardedThroughContext: aSemaphore.
  
  	^self resume: (self removeFirstLinkOfList: aSemaphore)
  		preemptedYieldingIf: preemptionYields!



More information about the Vm-dev mailing list