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

commits at source.squeak.org commits at source.squeak.org
Wed Jul 24 00:22:55 UTC 2013


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

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

Name: VMMaker.oscog-eem.308
Author: eem
Time: 23 July 2013, 5:20:45.148 pm
UUID: 66681ccb-5127-4525-a519-55ee71410844
Ancestors: VMMaker.oscog-eem.307

Add an assert that checks all the instructionPointers in all stack
pages.  Use the assert in code compaction.  (tracking down a rare
crash at Cadence).

Fix the assert in CogIA32Compiler>>relocateCallBeforeReturnPC:by:
that was being triggered by relocating calls to
ceSendFromInlineCacheMiss: in open PICs.
Do this by making simulated addresses +ve, i.e. putting them in the
top of the bottom half of the address space, not the top of the
address space, to clear their sign bits.

Beef up the assertValidExecutionPointe:r:s:imbar:line: assert for
interpreted frames (i.e. check savedIP if pc is ceRetrnToInterpreter)

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

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 savedIP  |
- 	| methodField cogMethod |
  	<var: #cogMethod type: #'CogMethod *'>
  	self assert: stackPage = (stackPages stackPageFor: lifp) l: ln.
  	self assert: stackPage = stackPages mostRecentlyUsedPage 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) < LargeContextSize 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: methodField asUnsignedInteger > objectMemory startOfMemory l: ln)
  			   and: [self asserta: methodField asUnsignedInteger < objectMemory freeStart l: ln]) ifTrue:
+ 				[lip = cogit ceReturnToInterpreterPC
+ 					ifTrue:
+ 						[savedIP := self iframeSavedIP: lifp.
+ 						 self assert: (savedIP >= (methodField + (objectMemory lastPointerOf: methodField) + BaseHeaderSize - 1)
+ 								  and: [savedIP < (methodField + (objectMemory byteLengthOf: methodField) + BaseHeaderSize)])
+ 							l: ln]
+ 					ifFalse:
+ 						[self assert: (lip >= (methodField + (objectMemory lastPointerOf: methodField) + BaseHeaderSize - 1)
- 				[lip ~= cogit ceReturnToInterpreterPC ifTrue:
- 					[self assert: (lip >= (methodField + (objectMemory lastPointerOf: methodField) + BaseHeaderSize - 1)
  								  and: [lip < (methodField + (objectMemory byteLengthOf: methodField) + BaseHeaderSize)])
+ 							l: ln]].
- 						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 - BytesPerWord) l: ln]!

Item was added:
+ ----- Method: CoInterpreter>>assertValidStackedInstructionPointers: (in category 'debug support') -----
+ assertValidStackedInstructionPointers: ln
+ 	"Check that the stacked instruction pointers in all pages are correct.
+ 	 Checks the interpreter sender/machine code callee contract.
+ 	 Written so it will be optimized away if not in an assert VM."
+ 	| thePage |
+ 	<inline: false>
+ 	<var: #thePage type: #'StackPage *'>
+ 	0 to: numStackPages - 1 do:
+ 		[:i|
+ 		thePage := stackPages stackPageAt: i.
+ 		(stackPages isFree: thePage) ifFalse:
+ 			[self assert: (self assertValidStackedInstructionPointersIn: thePage line: ln) l: ln]]!

Item was added:
+ ----- Method: CoInterpreter>>assertValidStackedInstructionPointersIn:line: (in category 'debug support') -----
+ assertValidStackedInstructionPointersIn: aStackPage line: ln
+ 	"Check that the stacked instruction pointers in the given page are correct.
+ 	 Checks the interpreter sender/machine code callee contract."
+ 	<var: #aStackPage type: #'StackPage *'>
+ 	<var: #theFP type: #'char *'>
+ 	<var: #callerFP type: #'char *'>
+ 	<var: #theIPPtr type: #'char *'>
+ 	<var: #theIP type: #usqInt>
+ 	<var: #theMethod type: #'CogMethod *'>
+ 	<inline: false>
+ 	| prevFrameWasCogged theFP callerFP theMethod theIP theIPPtr methodObj |
+ 	(self asserta: (stackPages isFree: aStackPage) not l: ln) ifFalse:
+ 		[^false].
+ 	prevFrameWasCogged := false.
+ 	theIPPtr := aStackPage headSP.
+ 	theFP := aStackPage headFP.
+ 	[(self isMachineCodeFrame: theFP)
+ 		ifTrue:
+ 			[theMethod := self mframeHomeMethod: theFP.
+ 			 theIP := (stackPages longAt: theIPPtr) asUnsignedInteger.
+ 			 self assert: (theIP = cogit ceCannotResumePC
+ 						  or: [self asserta: (theIP >= theMethod asUnsignedInteger
+ 							   and: [theIP < (theMethod asUnsignedInteger + theMethod blockSize)])])
+ 				l: ln.
+ 			prevFrameWasCogged := true]
+ 		ifFalse: "assert-check the interpreter frame."
+ 			[theIP := (stackPages longAt: theIPPtr) asUnsignedInteger.
+ 			 methodObj := self iframeMethod: theFP.
+ 			 prevFrameWasCogged ifTrue:
+ 				[self assert: theIP = cogit ceReturnToInterpreterPC l: ln].
+ 			 theIP = cogit ceReturnToInterpreterPC ifTrue:
+ 				[theIP := self iframeSavedIP: theFP].
+ 			 self assert: (theIP >= (methodObj + (objectMemory lastPointerOf: methodObj) + BaseHeaderSize - 1)
+ 						  and: [theIP < (methodObj + (objectMemory byteLengthOf: methodObj) + BaseHeaderSize)])
+ 				l: ln.
+ 			 prevFrameWasCogged := false].
+ 	(callerFP := self frameCallerFP: theFP) ~= 0] whileTrue:
+ 		[theIPPtr := theFP + FoxCallerSavedIP.
+ 		 theFP := callerFP].
+ 	^true!

Item was changed:
  ----- Method: CoInterpreter>>commenceCogCompiledCodeCompaction (in category 'process primitive support') -----
  commenceCogCompiledCodeCompaction
  	| startTime |
  	<var: #startTime type: #usqLong>
  	cogCompiledCodeCompactionCalledFor := false.
  	cogit recordEventTrace ifTrue:
  		[self recordTrace: TraceCodeCompaction thing: TraceCodeCompaction source: 0].
  	startTime := self ioUTCMicrosecondsNow.
  
  	"This can be called in a number of circumstances.  The instructionPointer
  	 may contain a native pc that must be relocated.  There may already be a
  	 pushed instructionPointer on stack.  Clients ensure that instructionPointer
  	 is 0 if it should not be pushed and/or relocated.  Pushing twice is a mistake
  	 because only the top one will be relocated."
  	instructionPointer ~= 0 ifTrue:
  		[self push: instructionPointer.
  		 self externalWriteBackHeadStackPointer].
+ 	self assertValidStackedInstructionPointers: #'__LINE__'.
  	cogit compactCogCompiledCode.
+ 	self assertValidStackedInstructionPointers: #'__LINE__'.
  	instructionPointer ~= 0 ifTrue:
  		[instructionPointer := self popStack.
  		 self externalWriteBackHeadStackPointer].
  
  	statCodeCompactionCount := statCodeCompactionCount + 1.
  	statCodeCompactionUsecs := statCodeCompactionUsecs + (self ioUTCMicrosecondsNow - startTime).
  
  	objectMemory checkForLeaks ~= 0 ifTrue:
  		[objectMemory clearLeakMapAndMapAccessibleObjects.
  		 self assert: (self checkCodeIntegrity: false)]!

Item was changed:
  ----- Method: Cogit>>addressSpaceMask (in category 'accessing') -----
  addressSpaceMask
  	<doNotGenerate>
+ 	"Quad-byte-align, because the ARM requires 4-byte aligned jump & call targets."
+ 	^((1 << (8 * BytesPerWord)) - 1) bitAnd: -4!
- 	"The first parenthesis generates a word of ones, -3 removes the two lowest bits because of ARM's requirement to have 4-aligned jumping addresses"
- 	^((1 << (8 * BytesPerWord)) - 1) - 3!

Item was added:
+ ----- Method: Cogit>>allButTopBitOfAddressSpaceMask (in category 'accessing') -----
+ allButTopBitOfAddressSpaceMask
+ 	<doNotGenerate>
+ 	"Quad-byte-align, because the ARM requires 4-byte aligned jump & call targets."
+ 	^((1 << (8 * BytesPerWord - 1)) - 1) bitAnd: -4!

Item was changed:
  ----- Method: Cogit>>mapPrimitive:withIndexToUniqueAddress: (in category 'simulation only') -----
  mapPrimitive: primitiveRoutine "<Symbol>" withIndexToUniqueAddress: primitiveIndex "<SmallInteger>"
  	| uniqueAddress |
  	<doNotGenerate>
  	self assert: (primitiveRoutine isSymbol or: [primitiveRoutine isBlock]).
+ 	uniqueAddress := -1 - methodZoneBase - (primitiveIndex * 4) - 16r1000 bitAnd: self allButTopBitOfAddressSpaceMask.
- 	uniqueAddress := -1 - methodZoneBase - (primitiveIndex * 4) - 16r1000 bitAnd: self addressSpaceMask.
  	simulatedTrampolines
  		at: uniqueAddress
  		ifAbsentPut:
  			[primitiveRoutine isSymbol
  				ifTrue: [MessageSend receiver: coInterpreter selector: primitiveRoutine]
  				ifFalse: [primitiveRoutine]].
  	^uniqueAddress!

Item was changed:
  ----- Method: Cogit>>printMethodHeader:on: (in category 'disassembly') -----
  printMethodHeader: cogMethod on: aStream
  	<doNotGenerate>
  	self cCode: ''
  		inSmalltalk:
  			[cogMethod isInteger ifTrue:
  				[^self printMethodHeader: (self cogMethodOrBlockSurrogateAt: cogMethod) on: aStream]].
  	aStream ensureCr.
  	cogMethod asInteger printOn: aStream base: 16.
  	aStream crtab.
+ 	cogMethod cmType = CMMethod ifTrue:
+ 		[aStream nextPutAll: 'objhdr: '.
+ 		cogMethod objectHeader printOn: aStream base: 16].
+ 	cogMethod cmType = CMBlock ifTrue:
+ 		[aStream nextPutAll: 'homemth: '.
+ 		cogMethod cmHomeMethod asUnsignedInteger printOn: aStream base: 16.
+ 		aStream crtab; nextPutAll: 'startpc: '; print: cogMethod startpc].
- 	cogMethod cmType = CMMethod
- 		ifTrue:
- 			[aStream nextPutAll: 'objhdr: '.
- 			cogMethod objectHeader printOn: aStream base: 16]
- 		ifFalse:
- 			[aStream nextPutAll: 'homemth: '.
- 			cogMethod cmHomeMethod asUnsignedInteger printOn: aStream base: 16.
- 			aStream crtab; nextPutAll: 'startpc: '; print: cogMethod startpc].
  	aStream
  		crtab; nextPutAll: 'nArgs: ';	print: cogMethod cmNumArgs;
  		tab;    nextPutAll: 'type: ';	print: cogMethod cmType.
  	(cogMethod cmType ~= 0 and: [cogMethod cmType ~= CMBlock]) ifTrue:
  		[aStream crtab; nextPutAll: 'blksiz: '.
  		cogMethod blockSize printOn: aStream base: 16.
  		aStream crtab; nextPutAll: 'method: '.
  		cogMethod methodObject printOn: aStream base: 16.
  		aStream crtab; nextPutAll: 'mthhdr: '.
  		cogMethod methodHeader printOn: aStream base: 16.
  		aStream crtab; nextPutAll: 'selctr: '.
  		cogMethod selector printOn: aStream base: 16.
  		(coInterpreter lookupAddress: cogMethod selector) ifNotNil:
  			[:string| aStream nextPut: $=; nextPutAll: string].
  		aStream crtab; nextPutAll: 'blkentry: '.
  		cogMethod blockEntryOffset printOn: aStream base: 16.
  		cogMethod blockEntryOffset ~= 0 ifTrue:
  			[aStream nextPutAll: ' => '.
  			 cogMethod asInteger + cogMethod blockEntryOffset printOn: aStream base: 16]].
  	cogMethod cmType = CMClosedPIC
  		ifTrue:
  			[aStream crtab; nextPutAll: 'cPICNumCases: '.
  			 cogMethod cPICNumCases printOn: aStream base: 16.]
  		ifFalse:
  			[aStream crtab; nextPutAll: 'stackCheckOffset: '.
  			 cogMethod stackCheckOffset printOn: aStream base: 16.
  			 cogMethod stackCheckOffset > 0 ifTrue:
  				[aStream nextPut: $/.
  				 cogMethod asInteger + cogMethod stackCheckOffset printOn: aStream base: 16].
  			cogMethod cmType ~= CMBlock ifTrue:
  				[aStream
  					crtab;
  					nextPutAll: 'cmRefersToYoung: ';
  					nextPutAll: (cogMethod cmRefersToYoung ifTrue: ['yes'] ifFalse: ['no'])].
  			cogMethod cmType = CMMethod ifTrue:
  				[([cogMethod numCounters] on: MessageNotUnderstood do: [:ex| nil]) ifNotNil:
  					[:nc| aStream crtab; nextPutAll: 'numCounters: '; print: nc]]].
  	aStream cr; flush!

Item was changed:
  ----- Method: Cogit>>simulatedAddressFor: (in category 'initialization') -----
  simulatedAddressFor: anObject
  	"Answer a simulated address for a block or a symbol.  This is an address that
  	 can be called, read or written by generated machine code, and will be mapped
+ 	 into a Smalltalk message send or block evaluation.
+ 
+ 	 N.B. These addresses are at the top end of the bottom half of the address space
+ 	 so that they don't have the sign bit set and so will not look like negative numbers."
- 	 into a Smalltalk message send or block evaluation."
  	<doNotGenerate>
  	^simulatedAddresses
  		at: anObject
+ 		ifAbsentPut: [(simulatedAddresses size + 101 * BytesPerWord) negated bitAnd: self allButTopBitOfAddressSpaceMask]!
- 		ifAbsentPut: [(simulatedAddresses size + 101 * BytesPerWord) negated bitAnd: self addressSpaceMask]!



More information about the Vm-dev mailing list