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

commits at source.squeak.org commits at source.squeak.org
Fri Aug 1 08:47:42 UTC 2014


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

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

Name: VMMaker.oscog-eem.840
Author: eem
Time: 31 July 2014, 10:42:47.947 pm
UUID: 2e1a90f6-f8c0-40d1-9af5-28d14899bdf2
Ancestors: VMMaker.oscog-eem.839

SpurBootstrap:
Reduce use of bootstrap hack.
Move assertVEPAES test into assertValidExecutionPointers
to speed up singleStep simulation and hence the bootstrap.

Simulator:
Have VMCompiledMethodProxy>>encoderClass answer
those associated with the simulated image, not those
associated with the current system.
Don't print scavenge report if bootstrapping (again for speed).

Sista:
Implement part of the Squeak V3 class trap code.

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

Item was added:
+ ----- Method: CogObjectRepresentationForSqueakV3>>branchIfInstanceOfBehavior:branches: (in category 'sista support') -----
+ branchIfInstanceOfBehavior: classObj branches: branches
+ 	<var: #branches type: #'AbstractInstruction *'>
+ 	| jmpImmediate compactClassIndex |
+ 	<var: #jmpImmediate type: #'AbstractInstruction *'>
+ 	cogit MoveR: ReceiverResultReg R: TempReg.
+ 	jmpImmediate := self genJumpSmallIntegerInScratchReg: TempReg.
+ 	classObj = (objectMemory splObj: ClassSmallInteger) ifTrue:
+ 		[branches at: 0 put: jmpImmediate.
+ 		 ^0].
+ 	(compactClassIndex := objectMemory compactClassIndexOfClass: classObj) ~= 0
+ 		ifTrue:
+ 			[self genGetCompactClassIndexNonImmOf: ReceiverResultReg into: TempReg.
+ 			 cogit CmpCq: compactClassIndex R: TempReg]
+ 		ifFalse:
+ 			[self genGetClassObjectOfNonCompact: ReceiverResultReg into: TempReg.
+ 			 cogit
+ 				annotate: (cogit CmpCw: classObj R: TempReg)
+ 				objRef: classObj].
+ 	branches at: 0 put: (cogit JumpZero: 0).
+ 	^0!

Item was added:
+ ----- Method: CogObjectRepresentationForSqueakV3>>genGetClassObjectOfNonCompact:into: (in category 'compile abstract instructions') -----
+ genGetClassObjectOfNonCompact: instReg into: destReg
+ 	cogit
+ 		MoveMw: objectMemory classFieldOffset r: instReg R: destReg;
+ 		AndCq: AllButTypeMask signedIntFromLong R: destReg.
+ 	^0!

Item was added:
+ ----- Method: ObjectMemory>>compactClassIndexOfClass: (in category 'object format') -----
+ compactClassIndexOfClass: classObj
+ 	<api>
+ 	^self compactClassIndexOfHeader: (self formatOfClass: classObj)!

Item was changed:
  ----- Method: SpurGenerationScavengerSimulator>>scavenge: (in category 'scavenger') -----
  scavenge: tenuringCriterion
+ 	manager bootstrapping ifFalse:
+ 		[coInterpreter transcript nextPutAll: 'scavenging('; print: manager statScavenges; nextPutAll: ')...'; flush].
- 	coInterpreter transcript nextPutAll: 'scavenging('; print: manager statScavenges; nextPutAll: ')...'; flush.
  	^super scavenge: tenuringCriterion!

Item was changed:
  ----- Method: SpurMemoryManager>>allNewSpaceEntitiesDo: (in category 'object enumeration') -----
  allNewSpaceEntitiesDo: aBlock
  	"Enumerate all new space objects, including free objects."
  	<inline: true>
  	| prevObj prevPrevObj objOop limit |
  	prevPrevObj := prevObj := nil.
  	"After a scavenge eden is empty, futureSpace is empty, and all newSpace objects are
  	  in pastSpace.  Objects are allocated in eden.  So enumerate only pastSpace and eden."
+ 	self assert: (scavenger pastSpace start < scavenger eden start).
- 	self assert: (self bootstrapping or: [scavenger pastSpace start < scavenger eden start]).
  	objOop := self objectStartingAt: scavenger pastSpace start.
  	limit := pastSpaceStart.
  	[self oop: objOop isLessThan: limit] whileTrue:
  		[aBlock value: objOop.
  		 prevPrevObj := prevObj.
  		 prevObj := objOop.
  		 objOop := self objectAfter: objOop limit: limit].
  	objOop := self objectStartingAt: scavenger eden start.
  	[self oop: objOop isLessThan: freeStart] whileTrue:
  		[aBlock value: objOop.
  		 prevPrevObj := prevObj.
  		 prevObj := objOop.
  		 objOop := self objectAfter: objOop limit: freeStart].
  	self touch: prevPrevObj.
  	self touch: prevObj!

Item was changed:
  ----- Method: SpurMemoryManager>>initializeObjectMemory: (in category 'initialization') -----
  initializeObjectMemory: bytesToShift
  	"Initialize object memory variables at startup time. Assume endOfMemory at al are
  	 initialised by the image-reading code via setHeapBase:memoryLimit:endOfMemory:.
  	 endOfMemory is assumed to point to the end of the last object in the image.
  	 Assume: image reader also initializes the following variables:
  		specialObjectsOop
  		lastHash"
  	<inline: false>
  	| freeListObj |
  	"Catch mis-initializations leading to bad translations to C"
  	self assert: BaseHeaderSize = self baseHeaderSize.
  	self assert: (self maxSlotsForAlloc * BytesPerWord) asInteger > 0.
  	self bootstrapping ifFalse:
  		[self
  			initSegmentBridgeWithBytes: self bridgeSize
  			at: endOfMemory - self bridgeSize].
  	segmentManager adjustSegmentSwizzlesBy: bytesToShift.
  	"image may be at a different address; adjust oops for new location"
  	self adjustAllOopsBy: bytesToShift.
  	specialObjectsOop := segmentManager swizzleObj: specialObjectsOop.
  
  	"heavily used special objects"
  	nilObj		:= self splObj: NilObject.
  	falseObj	:= self splObj: FalseObject.
  	trueObj		:= self splObj: TrueObject.
  
  	"In Cog we insist that nil, true & false are next to each other (Cogit generates tighter
  	 conditional branch code as a result).  In addition, Spur places the free lists and
  	 class table root page immediately following them."
  	self assert: nilObj = oldSpaceStart.
  	self assert: falseObj = (self objectAfter: nilObj).
  	self assert: trueObj = (self objectAfter: falseObj).
  	freeListObj := self objectAfter: trueObj.
  	self reInitializeClassTablePostLoad: (self objectAfter: freeListObj).
  	markStack := self swizzleObjStackAt: MarkStackRootIndex.
  	weaklingStack := self swizzleObjStackAt: WeaklingStackRootIndex.
  	ephemeronQueue := self swizzleObjStackAt: EphemeronQueueRootIndex.
  	self assert: self validObjStacks.
  	self assert: (self isEmptyObjStack: markStack).
  	self assert: (self isEmptyObjStack: weaklingStack).
  
  	self initializeFreeSpacePostLoad: freeListObj.
  	segmentManager collapseSegmentsPostSwizzle.
  	self computeFreeSpacePostSwizzle.
  	self initializeOldSpaceFirstFree: freeOldSpaceStart. "initializes endOfMemory, freeStart, free space"
+ 	"self bootstrapping ifFalse:
+ 		["self initializeNewSpaceVariables.
+ 		 scavenger initializeRememberedSet"]".
- 	self bootstrapping ifFalse:
- 		[self initializeNewSpaceVariables.
- 		 scavenger initializeRememberedSet].
  	segmentManager checkSegments.
  
  	numCompactionPasses := CompactionPassesForGC.
  
  	"These defaults should depend on machine size; e.g. too small on a powerful laptop, too big on a Pi."
  	growHeadroom := 16*1024*1024.		"headroom when growing"
  	shrinkThreshold := 32*1024*1024.		"free space before shrinking"
  	self setHeapSizeAtPreviousGC.
  	heapGrowthToSizeGCRatio := 0.333333. "By default GC after scavenge if heap has grown by a third since the last GC"!

Item was added:
+ ----- Method: StackInterpreter>>encoderClassForHeader: (in category 'simulation') -----
+ encoderClassForHeader: headerInteger
+ 	^Smalltalk classNamed: ((self headerIndicatesAlternateBytecodeSet: headerInteger)
+ 								ifTrue: [AltBytecodeEncoderClassName]
+ 								ifFalse: [BytecodeEncoderClassName])!

Item was added:
+ ----- Method: StackInterpreterSimulator>>assertValidExecutionPointers (in category 'debug support') -----
+ assertValidExecutionPointers
+ 	assertVEPAES ifTrue:
+ 		[super assertValidExecutionPointers]!

Item was changed:
  ----- Method: StackInterpreterSimulator>>initialize (in category 'initialization') -----
  initialize
  	"Initialize the StackInterpreterSimulator 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.
  
  	bootstrapping := false.
  	transcript := Transcript.
  
  	objectMemory ifNil:
  		[objectMemory := self class objectMemoryClass simulatorClass new].
  	objectMemory coInterpreter: self.
  
  	"Note: we must initialize ConstMinusOne differently for simulation,
  		due to the fact that the simulator works only with +ve 32-bit values"
  	ConstMinusOne := objectMemory integerObjectOf: -1.
  
  	methodCache := Array new: MethodCacheSize.
  	atCache := Array new: AtCacheTotalSize.
  	self flushMethodCache.
  	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 := 0.
  	"This is initialized on loading the image, but convenient for testing stack page values..."
  	numStackPages := self defaultNumStackPages. 
  	startMicroseconds := Time totalSeconds * 1000000.
  
  	"initialize InterpreterSimulator variables used for debugging"
  	byteCount := 0.
  	sendCount := 0.
  	quitBlock := [^self].
  	traceOn := true.
  	printSends := printReturns := printFrameAtEachStep := printBytecodeAtEachStep := false.
  	myBitBlt := BitBltSimulator new setInterpreter: self.
  	displayForm := 'Display has not yet been installed' asDisplayText form.
  	eventQueue := SharedQueue new.
  	suppressHeartbeatFlag := false.
  	systemAttributes := Dictionary new.
  	extSemTabSize := 256.
  	disableBooleanCheat := false.
+ 	assertVEPAES := true. "a flag so the assertValidExecutionPointers can be disabled for simulation speed"!
- 	assertVEPAES := true. "a flag so the assertValidExecutionPointers in run can be turned off for simulation speed"!

Item was changed:
  ----- Method: StackInterpreterSimulator>>run (in category 'testing') -----
  run
  	"Just run"
  	quitBlock := [displayView ifNotNil:
  				   [displayView containingWindow ifNotNil:
  					[:topWindow|
  					((World submorphs includes: topWindow)
  					 and: [UIManager default confirm: 'close?']) ifTrue:
  						[topWindow delete]]].
  				  ^self].
  	self initStackPages.
  	self loadInitialContext.
  	self internalizeIPandSP.
  	self fetchNextBytecode.
  	[true] whileTrue:
+ 		[self assertValidExecutionPointers.
- 		[assertVEPAES ifTrue: [self assertValidExecutionPointers].
  		 atEachStepBlock value. "N.B. may be nil"
  		 self dispatchOn: currentBytecode in: BytecodeTable.
  		 self incrementByteCount].
  	localIP := localIP - 1.
  	"undo the pre-increment of IP before returning"
  	self externalizeIPandSP!

Item was changed:
  ----- Method: VMCompiledMethodProxy>>encoderClass (in category 'accessing') -----
  encoderClass
  
+ 	^coInterpreter encoderClassForHeader: self header!
- 	^(coInterpreter headerIndicatesAlternateBytecodeSet: self header)
- 		ifTrue: [EncoderForNewsqueakV4]
- 		ifFalse: [EncoderForV3PlusClosures]!



More information about the Vm-dev mailing list