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

commits at source.squeak.org commits at source.squeak.org
Wed Feb 11 02:38:33 UTC 2015


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

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

Name: VMMaker.oscog-eem.1050
Author: eem
Time: 10 February 2015, 6:37:01.618 pm
UUID: ad3a825c-97ba-4d01-a0e7-637af8cbf52b
Ancestors: VMMaker.oscog-eem.1049

Clean up a few more flushAtCache duplicates

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

Item was changed:
  ----- Method: CogVMSimulator>>initialize (in category 'initialization') -----
  initialize
  	"Initialize the CogVMSimulator when running the interpreter inside Smalltalk.  The
  	 primary responsibility of this method is to allocate Smalltalk Arrays for variables
  	 that will be declared as statically-allocated global arrays in the translated code."
  	super initialize.
  
  	transcript := Transcript.
  
  	objectMemory ifNil:
  		[objectMemory := self class objectMemoryClass simulatorClass new].
  	cogit ifNil:
  		[cogit := self class cogitClass new setInterpreter: self].
  	objectMemory coInterpreter: self cogit: cogit.
  
  	cogit numRegArgs > 0 ifTrue:
  		[debugStackDepthDictionary := Dictionary new].
  
  	cogThreadManager ifNotNil:
  		[super initialize].
  
  	"Note: we must initialize ConstMinusOne & HasBeenReturnedFromMCPC differently
  	 for simulation, due to the fact that the simulator works only with +ve 32-bit values"
  	ConstMinusOne := objectMemory integerObjectOf: -1.
  	HasBeenReturnedFromMCPC := objectMemory integerObjectOf: -1.
  	cogMethodZone := cogit methodZone. "Because Slang can't remove intermediate implicit receivers (cogit methodZone foo doesn't reduce to foo())"
  	enableCog := true.
  
  	methodCache := Array new: MethodCacheSize.
  	atCache := Array new: AtCacheTotalSize.
  	self flushMethodCache.
- 	self flushAtCache.
  	cogCompiledCodeCompactionCalledFor := false.
  	gcSemaphoreIndex := 0.
  	externalSemaphoreSignalRequests := externalSemaphoreSignalResponses := #().
  	externalPrimitiveTable := CArrayAccessor on: (Array new: MaxExternalPrimitiveTableSize).
  	externalPrimitiveTableFirstFreeIndex := 0.
  	primitiveTable := self class primitiveTable copy.
  	mappedPluginEntries := OrderedCollection new.
  	objectMemory hasSpurMemoryManagerAPI
  		ifTrue:
  			[primitiveAccessorDepthTable := Array new: primitiveTable size.
  			 pluginList := {}.
  			 self loadNewPlugin: '']
  		ifFalse:
  			[pluginList := {'' -> self }].
  	desiredNumStackPages := desiredEdenBytes := desiredCogCodeSize := 0.
  	"This is initialized on loading the image, but convenient for testing stack page values..."
  	numStackPages := self defaultNumStackPages. 
  	startMicroseconds := Time totalSeconds * 1000000.
  	maxLiteralCountForCompile := MaxLiteralCountForCompile.
  	minBackwardJumpCountForCompile := MinBackwardJumpCountForCompile.
  	flagInterpretedMethods := false.
  
  	"initialize InterpreterSimulator variables used for debugging"
  	byteCount := lastPollCount := sendCount := lookupCount := 0.
  	quitBlock := [^ self].
  	traceOn := true.
  	printSends := printFrameAtEachStep := printBytecodeAtEachStep := false.
  	myBitBlt := BitBltSimulator new setInterpreter: self.
  	displayForm := 'Display has not yet been installed' asDisplayText form.
  	suppressHeartbeatFlag := deferSmash := deferredSmash := false.
  	systemAttributes := Dictionary new.
  	primTraceLog := CArrayAccessor on: (Array new: 256 withAll: 0).
  	primTraceLogIndex := 0.
  	traceLog := CArrayAccessor on: (Array new: TraceBufferSize withAll: 0).
  	traceLogIndex := 0.
  	traceSources := TraceSources.
  	statCodeCompactionCount := 0.
  	statCodeCompactionUsecs := 0.
  	extSemTabSize := 256!

Item was changed:
  ----- Method: InterpreterPrimitives>>primitiveFlushCache (in category 'system control primitives') -----
  primitiveFlushCache
  	"Clear the method lookup cache. This must be done after every programming change."
  
+ 	self flushMethodCache!
- 	self flushMethodCache.
- 	self flushAtCache!

Item was changed:
  ----- Method: NewspeakInterpreter>>flushExternalPrimitives (in category 'plugin primitive support') -----
  flushExternalPrimitives
  	"Flush the references to external functions from plugin 
  	primitives. This will force a reload of those primitives when 
  	accessed next. 
  	Note: We must flush the method cache here so that any 
  	failed primitives are looked up again."
  	| oop primIdx |
  	oop := self firstObject.
  	[oop < endOfMemory]
  		whileTrue: [(self isFreeObject: oop)
  				ifFalse: [(self isCompiledMethod: oop)
  						ifTrue: ["This is a compiled method"
  							primIdx := self primitiveIndexOf: oop.
  							primIdx = PrimitiveExternalCallIndex
  								ifTrue: ["It's primitiveExternalCall"
  									self flushExternalPrimitiveOf: oop]]].
  			oop := self objectAfter: oop].
  	self flushMethodCache.
- 	self flushAtCache.
  	self flushExternalPrimitiveTable!

Item was changed:
  ----- Method: NewspeakInterpreter>>flushMethodCache (in category 'method lookup cache') -----
  flushMethodCache
  	"Flush the method cache. The method cache is flushed on every programming change and garbage collect."
  
+ 	1 to: MethodCacheSize do: [ :i | methodCache at: i put: 0 ].
+ 	1 to: AtCacheTotalSize do: [ :i | atCache at: i put: 0 ]!
- 	1 to: MethodCacheSize do: [ :i | methodCache at: i put: 0 ]!

Item was changed:
  ----- Method: NewspeakInterpreter>>initializeInterpreter: (in category 'initialization') -----
  initializeInterpreter: bytesToShift 
  	"Initialize NewspeakInterpreter state before starting execution of a new image."
  	interpreterProxy := self sqGetInterpreterProxy.
  	self dummyReferToProxy.
  	self initializeObjectMemory: bytesToShift.
  	self checkAssumedCompactClasses.
  	primFailCode := 0.
  	self initializeExtraClassInstVarIndices.
  	activeContext := nilObj.
  	theHomeContext := nilObj.
  	method := nilObj.
  	receiver := nilObj.
  	messageSelector := nilObj.
  	newMethod := nilObj.
  	lkupClass := nilObj.
  	self flushMethodCache.
- 	self flushAtCache.
  	self loadInitialContext.
  	self initialCleanup.
  	interruptCheckCounter := 0.
  	interruptCheckCounterFeedBackReset := 1000.
  	interruptChecksEveryNms := 1.
  	nextPollTick := 0.
  	nextWakeupTick := 0.
  	lastTick := 0.
  	interruptKeycode := 2094. "cmd-. as used for Mac but no other OS"
  	interruptPending := false.
  	deferDisplayUpdates := false.
  	pendingFinalizationSignals := 0.
  	globalSessionID := 0.
  	[globalSessionID = 0]
  		whileTrue: [globalSessionID := self
  						cCode: 'time(NULL) + ioMSecs()'
  						inSmalltalk: [(Random new next * SmallInteger maxVal) asInteger]]!

Item was changed:
  ----- Method: NewspeakInterpreter>>primitiveFlushCache (in category 'system control primitives') -----
  primitiveFlushCache
  	"Clear the method lookup cache. This must be done after every programming change."
  
+ 	self flushMethodCache!
- 	self flushMethodCache.
- 	self flushAtCache!

Item was changed:
  ----- Method: StackInterpreter>>initialCleanup (in category 'initialization') -----
  initialCleanup
  	"This used to cope with issues with images written by VMs earlier than 3.6/3.7.
  	 Since we won't be loading such images (being a closure only VM) we only have to
  	 deal with external primitives.  Since references to external plugins in methods are
  	 cleaned up in snapshotCleanUp only initialize the tables, not visit each method."
  	self flushMethodCache.
- 	self flushAtCache.
  	self flushExternalPrimitiveTable!

Item was changed:
  ----- Method: StackInterpreter>>initializeInterpreter: (in category 'initialization') -----
  initializeInterpreter: bytesToShift
  	"Initialize Interpreter state before starting execution of a new image."
  	interpreterProxy := self sqGetInterpreterProxy.
  	self dummyReferToProxy.
  	objectMemory initializeObjectMemory: bytesToShift.
  	self checkAssumedCompactClasses.
  	self initializeExtraClassInstVarIndices.
  	method := newMethod := objectMemory nilObject.
  	self cCode: '' inSmalltalk:
  		[breakSelectorLength ifNil:
  			[breakSelectorLength := objectMemory minSmallInteger]].
  	methodDictLinearSearchLimit := 8.
  	self flushMethodCache.
- 	self flushAtCache.
  	self initialCleanup.
  	profileSemaphore := profileProcess := profileMethod := objectMemory nilObject.
  	interruptKeycode := 2094. "cmd-. as used for Mac but no other OS"
  	[globalSessionID = 0] whileTrue:
  		[globalSessionID := self
  								cCode: [(self time: #NULL) + self ioMSecs]
  								inSmalltalk: [(Random new next * SmallInteger maxVal) asInteger]]!



More information about the Vm-dev mailing list