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

commits at source.squeak.org commits at source.squeak.org
Wed Oct 2 18:50:38 UTC 2013


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

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

Name: VMMaker.oscog-eem.424
Author: eem
Time: 2 October 2013, 11:47:58.444 am
UUID: 04c70bb8-9f13-4744-b63f-c48f34a1b961
Ancestors: VMMaker.oscog-eem.423

Fix adding entries to the method cache (hash needs to use classTag,
not classObj).

Make scavenging flush the atCache (plumbing for ObjectMemory is
through mapPointersInObjectsFrom:to:, so not obvous).

Add routines to print mehtodCache & atCache.

Cogt+Spur now halt long before 3+4 when trying to compile
primtiive size.

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

Item was changed:
  ----- Method: CoInterpreter>>internalFindNewMethod (in category 'message sending') -----
  internalFindNewMethod
  	"Find the compiled method to be run when the current messageSelector is
  	 sent to the given class, setting the values of newMethod and primitiveIndex."
  	| ok |
  	<inline: true>
  	ok := self lookupInMethodCacheSel: messageSelector classTag: lkupClassTag.
  	ok	ifTrue:
  			[self ifAppropriateCompileToNativeCode: newMethod selector: messageSelector]
  		ifFalse:
+ 			[self externalizeIPandSP.
+ 			 ((objectMemory isOopForwarded: messageSelector)
+ 			  or: [objectMemory isForwardedClassTag: lkupClassTag]) ifTrue:
+ 				[(objectMemory isOopForwarded: messageSelector) ifTrue:
+ 					[messageSelector := self handleForwardedSelectorFaultFor: messageSelector].
+ 				 (objectMemory isForwardedClassTag: lkupClassTag) ifTrue:
+ 					[lkupClassTag := self handleForwardedSendFaultFor: lkupClassTag].
+ 				ok := self lookupInMethodCacheSel: messageSelector classTag: lkupClassTag.
+ 				ok ifTrue:
+ 					[self ifAppropriateCompileToNativeCode: newMethod selector: messageSelector.
+ 					^nil]].
+ 			 lkupClass := objectMemory classForClassTag: lkupClassTag.
- 			["entry was not found in the cache; look it up the hard way"
- 			lkupClass := objectMemory classForClassTag: lkupClassTag.
- 			objectMemory hasSpurMemoryManagerAPI ifTrue:
- 				[| oop |
- 				 oop := self internalStackValue: argumentCount.
- 				 ((objectMemory isNonImmediate: oop)
- 				  and: [objectMemory isForwarded: oop]) ifTrue:
- 					[self internalStackValue: argumentCount put: (objectMemory followForwarded: oop)]].
- 			self externalizeIPandSP.
  			self lookupMethodInClass: lkupClass.
  			self internalizeIPandSP.
  			self addNewMethodToCache: lkupClass]!

Item was changed:
  ----- Method: Cogit>>blockAlignment (in category 'accessing') -----
  blockAlignment
+ 	"Block method headers must be aligned on the correct boundary, just like non-block method headers.
+ 	 This is because the CoInterpreter encodes flags in the least significant three bits of the method field."
  	<cmacro: '(self) 8'>
  	self assert: (methodZone roundUpLength: 1) = 8.
  	^8!

Item was changed:
  ----- Method: Cogit>>cog:selector: (in category 'jit - api') -----
  cog: aMethodObj selector: aSelectorOop
  	"Attempt to produce a machine code method for the bytecode method
  	 object aMethodObj.  N.B. If there is no code memory available do *NOT*
  	 attempt to reclaim the method zone.  Certain clients (e.g. ceSICMiss:)
  	 depend on the zone remaining constant across method generation."
  	<api>
  	<returnTypeC: #'CogMethod *'>
  	| cogMethod |
  	<var: #cogMethod type: #'CogMethod *'>
  	self assert: ((coInterpreter methodHasCogMethod: aMethodObj) not
  				or: [(self noAssertMethodClassAssociationOf: aMethodObj) = objectMemory nilObject]).
+ 	aSelectorOop = (coInterpreter specialSelector: 16) ifTrue: [self halt].
  	"coInterpreter stringOf: aSelectorOop"
  	coInterpreter
  		compilationBreak: aSelectorOop
  		point: (objectMemory lengthOf: aSelectorOop).
  	aMethodObj = breakMethod ifTrue: [self halt: 'Compilation of breakMethod'].
  	self cppIf: NewspeakVM
  		ifTrue: [cogMethod := methodZone findPreviouslyCompiledVersionOf: aMethodObj with: aSelectorOop.
  				cogMethod ifNotNil:
  					[(coInterpreter methodHasCogMethod: aMethodObj) not ifTrue:
  						[self assert: (coInterpreter rawHeaderOf: aMethodObj) = cogMethod methodHeader.
  						 cogMethod methodObject: aMethodObj.
  						 coInterpreter rawHeaderOf: aMethodObj put: cogMethod asInteger].
  					^cogMethod]].
  	"If the generators for the alternate bytecode set are missing then interpret."
  	(coInterpreter methodUsesAlternateBytecodeSet: aMethodObj)
  		ifTrue:
  			[(self numElementsIn: generatorTable) <= 256 ifTrue:
  				[^nil].
  			 bytecodeSetOffset := 256]
  		ifFalse:
  			[bytecodeSetOffset := 0].
  	extA := extB := 0.
  	methodObj := aMethodObj.
  	cogMethod := self compileCogMethod: aSelectorOop.
  	(cogMethod asInteger between: MaxNegativeErrorCode and: -1) ifTrue:
  		[cogMethod asInteger = InsufficientCodeSpace ifTrue:
  			[coInterpreter callForCogCompiledCodeCompaction].
  		"Right now no errors should be reported, so nothing more to do."
  		"self reportError: (self cCoerceSimple: cogMethod to: #sqInt)."
  		 ^nil].
  	"self cCode: ''
  		inSmalltalk:
  			[coInterpreter printCogMethod: cogMethod.
  			 ""coInterpreter symbolicMethod: aMethodObj.""
  			 self assertValidMethodMap: cogMethod."
  			 "self disassembleMethod: cogMethod."
  			 "printInstructions := clickConfirm := true""]."
  	^cogMethod!

Item was changed:
  ----- Method: SpurMemoryManager>>isIntegerObject: (in category 'object testing') -----
  isIntegerObject: oop
  	"This list records the valid senders of isIntegerObject: as we replace uses of
  	  isIntegerObject: by isImmediate: where appropriate."
  	| sel |
  	sel := thisContext sender method selector.
  	(#(	DoIt
  		DoItIn:
  		on:do: "from the debugger"
  		makeBaseFrameFor:
  		quickFetchInteger:ofObject:
  		frameOfMarriedContext:
  		objCouldBeClassObj:
  		isMarriedOrWidowedContext:
  		shortPrint:
  		bytecodePrimAt
  		bytecodePrimAtPut
  		commonAt:
  		commonAtPut:
  		loadFloatOrIntFrom:
  		positive32BitValueOf:
  		primitiveExternalCall
  		checkedIntegerValueOf:
  		bytecodePrimAtPut
  		commonAtPut:
  		primitiveVMParameter
  		checkIsStillMarriedContext:currentFP:
  		displayBitsOf:Left:Top:Right:Bottom:
  		fetchStackPointerOf:
  		primitiveContextAt
  		primitiveContextAtPut
  		subscript:with:storing:format:
  		printContext:
  		compare31or32Bits:equal:
  		signed64BitValueOf:
  		primDigitMultiply:negative:
  		digitLength:
  		isNegativeIntegerValueOf:
  		magnitude64BitValueOf:
  		primitiveMakePoint
  		primitiveAsCharacter
  		primitiveInputSemaphore
  		baseFrameReturn
  		primitiveExternalCall
  		primDigitCompare:
  		isLiveContext:
  		numPointerSlotsOf:
  		fileValueOf:
  		loadBitBltDestForm
  		fetchIntOrFloat:ofObject:ifNil:
  		fetchIntOrFloat:ofObject:
  		loadBitBltSourceForm
  		loadPoint:from:
  		primDigitAdd:
  		primDigitSubtract:
  		positive64BitValueOf:
  		digitBitLogic:with:opIndex:
  		signed32BitValueOf:
  		isNormalized:
  		primDigitDiv:negative:
  		bytesOrInt:growTo:
  		primitiveNewMethod
  		isCogMethodReference:
  		functionForPrimitiveExternalCall:
  		genSpecialSelectorArithmetic
  		genSpecialSelectorComparison
  		ensureContextHasBytecodePC:
  		instVar:ofContext:
  		ceBaseFrameReturn:
  		inlineCacheTagForInstance:
+ 		primitiveObjectAtPut
+ 		commonVariable:at:put:cacheIndex:) includes: sel) ifFalse:
- 		primitiveObjectAtPut) includes: sel) ifFalse:
  		[self halt].
  	^(oop bitAnd: 1) ~= 0!

Item was changed:
  ----- Method: SpurMemoryManager>>scavengingGC (in category 'generation scavenging') -----
  scavengingGC
  	"Run the scavenger."
  
  	self assert: remapBufferCount = 0.
  	self checkFreeSpace.
  	"coInterpreter printCallStackFP: coInterpreter framePointer"
  
  	self runLeakCheckerForFullGC: false.
+ 	coInterpreter
+ 		preGCAction: GCModeIncr;
+ 		"would prefer this to be in mapInterpreterOops, but
+ 		 compatibility with ObjectMemory dictates it goes here."
+ 		flushMethodCacheFrom: startOfMemory to: newSpaceLimit.
- 	coInterpreter preGCAction: GCModeIncr.
  	needGCFlag := false.
  
  	gcStartUsecs := coInterpreter ioUTCMicrosecondsNow.
  
  	scavengeInProgress := true.
  	pastSpaceStart := scavenger scavenge.
  	self assert: (self
  					oop: pastSpaceStart
  					isGreaterThanOrEqualTo: scavenger pastSpace start
  					andLessThanOrEqualTo: scavenger pastSpace limit).
  	freeStart := scavenger eden start.
  	self initSpaceForAllocationCheck: scavenger eden.
  	scavengeInProgress := false.
  
  	statScavenges := statScavenges + 1.
  	statGCEndUsecs := coInterpreter ioUTCMicrosecondsNow.
  	statSGCDeltaUsecs := statGCEndUsecs - gcStartUsecs.
  	statScavengeGCUsecs := statScavengeGCUsecs + statSGCDeltaUsecs.
  
  	coInterpreter postGCAction.
  	self runLeakCheckerForFullGC: false.
  
  	self checkFreeSpace!

Item was changed:
  ----- Method: StackInterpreter>>addNewMethodToCache: (in category 'method lookup cache') -----
+ addNewMethodToCache: classObj
- addNewMethodToCache: class
  	"Add the given entry to the method cache.
  	The policy is as follows:
  		Look for an empty entry anywhere in the reprobe chain.
  		If found, install the new entry there.
  		If not found, then install the new entry at the first probe position
  			and delete the entries in the rest of the reprobe chain.
  		This has two useful purposes:
  			If there is active contention over the first slot, the second
  				or third will likely be free for reentry after ejection.
  			Also, flushing is good when reprobe chains are getting full."
  	| probe hash primitiveIndex |
  	<inline: false>
+ 	hash := messageSelector bitXor: (objectMemory classTagForClass: classObj).  "drop low-order zeros from addresses (if classObj not classTag)"
- 	hash := messageSelector bitXor: class.  "drop low-order zeros from addresses"
  	(objectMemory isOopCompiledMethod: newMethod)
  		ifTrue:
  			[primitiveIndex := self primitiveIndexOf: newMethod.
+ 			 primitiveFunctionPointer := self functionPointerFor: primitiveIndex inClass: classObj]
- 			 primitiveFunctionPointer := self functionPointerFor: primitiveIndex inClass: class]
  		ifFalse:
  			[primitiveFunctionPointer := #primitiveInvokeObjectAsMethod].
  
  	0 to: CacheProbeMax-1 do:
  		[:p | probe := (hash >> p) bitAnd: MethodCacheMask.
  		(methodCache at: probe + MethodCacheSelector) = 0 ifTrue:
  			["Found an empty entry -- use it"
  			methodCache at: probe + MethodCacheSelector put: messageSelector.
+ 			methodCache at: probe + MethodCacheClass put: (objectMemory classTagForClass: classObj).
- 			methodCache at: probe + MethodCacheClass put: (objectMemory classTagForClass: class).
  			methodCache at: probe + MethodCacheMethod put: newMethod.
  			methodCache at: probe + MethodCachePrimFunction put: (self cCoerce: primitiveFunctionPointer to: #long).
  			lastMethodCacheProbeWrite := probe. "this for primitiveExternalMethod"
  			^ nil]].
  
  	"OK, we failed to find an entry -- install at the first slot..."
  	probe := hash bitAnd: MethodCacheMask.  "first probe"
  	methodCache at: probe + MethodCacheSelector put: messageSelector.
+ 	methodCache at: probe + MethodCacheClass put: (objectMemory classTagForClass: classObj).
- 	methodCache at: probe + MethodCacheClass put: (objectMemory classTagForClass: class).
  	methodCache at: probe + MethodCacheMethod put: newMethod.
  	methodCache at: probe + MethodCachePrimFunction put: (self cCoerce: primitiveFunctionPointer to: #long).
  	lastMethodCacheProbeWrite := probe. "this for primitiveExternalMethod"
  
  	"...and zap the following entries"
  	1 to: CacheProbeMax-1 do:
  		[:p | probe := (hash >> p) bitAnd: MethodCacheMask.
  		methodCache at: probe + MethodCacheSelector put: 0]!

Item was changed:
  ----- Method: StackInterpreter>>commonVariable:at:put:cacheIndex: (in category 'indexing primitive support') -----
  commonVariable: rcvr at: index put: value cacheIndex: atIx
  	"This code assumes the receiver has been identified at location atIx in the atCache."
  	| stSize fmt fixedFields valToPut isCharacter |
  	<inline: true>
  	stSize := atCache at: atIx+AtCacheSize.
  	((self oop: index isGreaterThanOrEqualTo: 1)
  	  and: [self oop: index isLessThanOrEqualTo: stSize]) ifTrue:
  		[fmt := atCache at: atIx+AtCacheFmt.
  		fmt <= objectMemory weakArrayFormat ifTrue:
  			[self assert: (objectMemory isContextNonImm: rcvr) not.
  			 fixedFields := atCache at: atIx+AtCacheFixedFields.
  			 ^objectMemory storePointer: index + fixedFields - 1 ofObject: rcvr withValue: value].
  		fmt < objectMemory firstByteFormat ifTrue:  "Bitmap"
  			[valToPut := self positive32BitValueOf: value.
  			 self successful ifTrue:
  				[objectMemory storeLong32: index - 1 ofObject: rcvr withValue: valToPut.
  				^nil].
  			 ^self primitiveFailFor: PrimErrBadArgument].
  		fmt >= objectMemory firstStringyFakeFormat  "Note fmt >= firstStringyFormat is an artificial flag for strings"
+ 			ifTrue:
+ 				[isCharacter := objectMemory isCharacterObject: value.
+ 				 isCharacter ifFalse:
+ 					[^self primitiveFailFor: PrimErrBadArgument].
+ 				 objectMemory hasSpurMemoryManagerAPI
+ 					ifTrue: [valToPut := objectMemory characterValueOf: value]
+ 					ifFalse:
+ 						[valToPut := objectMemory fetchPointer: CharacterValueIndex ofObject: value.
+ 						 valToPut := (objectMemory isIntegerObject: valToPut)
+ 										ifTrue: [objectMemory integerValueOf: valToPut]
+ 										ifFalse: [-1]]]
- 			ifTrue: [isCharacter := objectMemory isCharacterObject: value.
- 					isCharacter ifFalse:
- 						[^self primitiveFailFor: PrimErrBadArgument].
- 					objectMemory hasSpurMemoryManagerAPI
- 						ifTrue: [valToPut := objectMemory characterValueOf: value]
- 						ifFalse:
- 							[valToPut := objectMemory fetchPointer: CharacterValueIndex ofObject: value.
- 							 valToPut := (objectMemory isIntegerObject: valToPut)
- 											ifTrue: [objectMemory integerValueOf: valToPut]
- 											ifFalse: [-1]]]
  			ifFalse:
  				[(fmt >= objectMemory firstCompiledMethodFormat
  				  and: [index < (self firstByteIndexOfMethod: rcvr)]) ifTrue:
  					[^self primitiveFailFor: PrimErrBadIndex].
  				valToPut := (objectMemory isIntegerObject: value)
  								ifTrue: [objectMemory integerValueOf: value]
  								ifFalse: [-1]].
  		((valToPut >= 0) and: [valToPut <= 255]) ifFalse: [^self primitiveFailFor: PrimErrBadArgument].
  		^objectMemory storeByte: index - 1 ofObject: rcvr withValue: valToPut].
  
  	^self primitiveFailFor: ((objectMemory isIndexable: rcvr)
  								ifFalse: [PrimErrBadReceiver]
  								ifTrue: [PrimErrBadIndex])!

Item was changed:
  ----- Method: StackInterpreter>>flushMethodCacheFrom:to: (in category 'method lookup cache') -----
  flushMethodCacheFrom: memStart to: memEnd 
  	"Flush entries in the method cache only if the oop address is within the given memory range. 
  	This reduces overagressive cache clearing. Note the AtCache is fully flushed, 70% of the time 
  	cache entries live in newspace, new objects die young"
  	| probe |
  	probe := 0.
  	1 to: MethodCacheEntries do: [:i | 
  			(methodCache at: probe + MethodCacheSelector) = 0
  				ifFalse: [((((self oop: (methodCache at: probe + MethodCacheSelector) isGreaterThanOrEqualTo: memStart)
  										and: [self oop: (methodCache at: probe + MethodCacheSelector) isLessThan: memEnd])
  									or: [(self oop: (methodCache at: probe + MethodCacheClass) isGreaterThanOrEqualTo: memStart)
  											and: [self oop: (methodCache at: probe + MethodCacheClass) isLessThan: memEnd]])
  								or: [(self oop: (methodCache at: probe + MethodCacheMethod) isGreaterThanOrEqualTo: memStart)
  										and: [self oop: (methodCache at: probe + MethodCacheMethod) isLessThan: memEnd]])
  						ifTrue: [methodCache at: probe + MethodCacheSelector put: 0]].
  			probe := probe + MethodCacheEntrySize].
+ 	self flushAtCache!
- 	1 to: AtCacheTotalSize do: [:i | atCache at: i put: 0]!

Item was changed:
  ----- Method: StackInterpreter>>install:inAtCache:at:string: (in category 'indexing primitive support') -----
  install: rcvr inAtCache: cache at: atIx string: stringy
  	"Attempt to install the oop of this object in the given cache (at or atPut),
  	 along with its size, format and fixedSize. Answer if this was successful."
  	| hdr fmt totalLength fixedFields |
  	<inline: true>
  	<var: #cache type: 'sqInt *'>
+ 	self assert: (objectMemory isContext: rcvr) not.
- 
  	hdr := objectMemory baseHeader: rcvr.
  	fmt := objectMemory formatOfHeader: hdr.
  	stringy
  		ifTrue:
  			[totalLength := objectMemory lengthOf: rcvr baseHeader: hdr format: fmt.
  			 fixedFields := 0.
  			 fmt := fmt + objectMemory firstStringyFakeFormat]  "special flag for strings"
  		ifFalse:
  			[(fmt = objectMemory indexablePointersFormat and: [objectMemory isContextHeader: hdr]) ifTrue:
  				["Contexts must not be put in the atCache, since their size is not constant"
  				self primitiveFailFor: PrimErrBadReceiver.
  				^false].
  			 totalLength := objectMemory lengthOf: rcvr baseHeader: hdr format: fmt.
  			 fixedFields := objectMemory fixedFieldsOf: rcvr format: fmt length: totalLength].
  
  	cache at: atIx+AtCacheOop put: rcvr.
  	cache at: atIx+AtCacheFmt put: fmt.
  	cache at: atIx+AtCacheFixedFields put: fixedFields.
  	cache at: atIx+AtCacheSize put: totalLength - fixedFields.
  	^true!

Item was added:
+ ----- Method: StackInterpreter>>printAtCache (in category 'debug printing') -----
+ printAtCache
+ 	0 to: AtCacheTotalSize - 1 by: 4 do:
+ 		[:i | | obj sz fmt fixed |
+ 		obj := atCache at: i + AtCacheOop.
+ 		sz := atCache at: i + AtCacheSize.
+ 		fmt := atCache at: i + AtCacheFmt.
+ 		fixed := atCache at: i + AtCacheFixedFields.
+ 		(objectMemory addressCouldBeObj: obj) ifTrue:
+ 			[self transcript ensureCr.
+ 			 self print: i; tab; print: (i < AtPutBase ifTrue: ['at   '] ifFalse: ['put ']);
+ 				tab; printNum: sz; tab; printNum: fmt; tab; printNum: fixed; tab;
+ 				shortPrintOop: obj]]!

Item was added:
+ ----- Method: StackInterpreter>>printMethodCache (in category 'debug printing') -----
+ printMethodCache
+ 	0 to: MethodCacheSize - 1 by: MethodCacheEntrySize do:
+ 		[:i | | s c m p |
+ 		s := methodCache at: i + MethodCacheSelector.
+ 		c := methodCache at: i + MethodCacheClass.
+ 		m := methodCache at: i + MethodCacheMethod.
+ 		p := methodCache at: i + MethodCachePrimFunction.
+ 		((objectMemory addressCouldBeOop: s)
+ 		 and: [c ~= 0
+ 		 and: [(self addressCouldBeClassObj: c)
+ 			or: [self addressCouldBeClassObj: (objectMemory classForClassTag: c)]]]) ifTrue:
+ 			[self transcript ensureCr.
+ 			 self print: i; cr; tab.
+ 			 (objectMemory isBytesNonImm: s)
+ 				ifTrue: [self printHex: s; space; print: (self stringOf: s); cr]
+ 				ifFalse: [self shortPrintOop: s].
+ 			 self tab.
+ 			 (self addressCouldBeClassObj: c)
+ 				ifTrue: [self shortPrintOop: c]
+ 				ifFalse: [self printNum: c; space; shortPrintOop: (objectMemory classForClassTag: c)].
+ 			self tab; shortPrintOop: m; tab.
+ 			p isSymbol
+ 				ifTrue: [self print: p]
+ 				ifFalse: [self printNum: p].
+ 			self cr]]!



More information about the Vm-dev mailing list