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

commits at source.squeak.org commits at source.squeak.org
Thu Feb 21 17:43:03 UTC 2019


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

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

Name: VMMaker.oscog-eem.2521
Author: eem
Time: 21 February 2019, 9:42:49.533302 am
UUID: 4f1618e4-2a0c-4ba8-be03-b8670286ba00
Ancestors: VMMaker.oscog-eem.2520

Spur:
Fix segment loading so that an imported class (in outPointers) that has yet to be instantiated does not abort the load.  This should fix Terf room entry.

Simulator:
Correctly simulate primitiveUnloadModule

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

Item was changed:
  ----- Method: CogObjectRepresentation>>genPrimitiveIntegerAtPut (in category 'primitive generators') -----
  genPrimitiveIntegerAtPut
  	"subclasses override if they can"
- 	self break.
  	^UnimplementedPrimitive!

Item was changed:
  ----- Method: CogVMSimulator>>flushExternalPrimitives (in category 'plugin support') -----
  flushExternalPrimitives
+ 	self initializePluginEntries.
+ 	super flushExternalPrimitives!
- 	mappedPluginEntries := OrderedCollection new.
- 	super flushExternalPrimitives.!

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
  	 and: [VMClass initializationOptions at: #CheckStackDepth ifAbsent: [true]]) ifTrue:
  		[debugStackDepthDictionary := Dictionary new].
  
  	cogThreadManager ifNotNil:
  		[super initialize].
  
  	self assert: ConstMinusOne = (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.
  	nsMethodCache := Array new: NSMethodCacheSize.
  	atCache := nil.
  	self flushMethodCache.
  	cogCompiledCodeCompactionCalledFor := false.
  	gcSemaphoreIndex := 0.
  	externalSemaphoreSignalRequests := externalSemaphoreSignalResponses := #().
  	externalPrimitiveTable := CArrayAccessor on: (Array new: MaxExternalPrimitiveTableSize).
  	externalPrimitiveTableFirstFreeIndex := 0.
  	primitiveTable := self class primitiveTable copy.
+ 	self initializePluginEntries.
- 	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 := lastYieldMicroseconds := self ioUTCStartMicroseconds.
  	maxLiteralCountForCompile := MaxLiteralCountForCompile.
  	minBackwardJumpCountForCompile := MinBackwardJumpCountForCompile.
  	flagInterpretedMethods := false.
  
  	"initialize InterpreterSimulator variables used for debugging"
  	byteCount := lastPollCount := sendCount := lookupCount := 0.
  	quitBlock := [^self close].
  	traceOn := true.
  	printSends := printFrameAtEachStep := printBytecodeAtEachStep := false.
  	myBitBlt := BitBltSimulator new setInterpreter: self.
  	displayForm := fakeForm := 'Display has not yet been installed' asDisplayText form.
  	eventQueue := SharedQueue new.
  	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 added:
+ ----- Method: CogVMSimulator>>initializePluginEntries (in category 'plugin support') -----
+ initializePluginEntries.
+ 	mappedPluginEntries := OrderedCollection new.
+ 	objectMemory hasSpurMemoryManagerAPI
+ 		ifTrue:
+ 			[primitiveAccessorDepthTable := Array new: primitiveTable size.
+ 			 pluginList := {}.
+ 			 self loadNewPlugin: '']
+ 		ifFalse:
+ 			[pluginList := {'' -> self }]!

Item was changed:
  ----- Method: InterpreterPrimitives>>primitiveUnloadModule (in category 'plugin primitives') -----
  primitiveUnloadModule
  	"Primitive. Unload the module with the given name."
  	"Reloading of the module will happen *later* automatically, when a 
+ 	 function from it is called. This is ensured by invalidating current sessionID."
- 	function from it is called. This is ensured by invalidating current sessionID."
  	| moduleName |
  	self methodArgumentCount = 1 ifFalse:[^self primitiveFail].
  	moduleName := self stackTop.
- 	(objectMemory isIntegerObject: moduleName) ifTrue:[^self primitiveFail].
  	(objectMemory isBytes: moduleName) ifFalse:[^self primitiveFail].
  	(self ioUnloadModule: (self oopForPointer: (objectMemory firstIndexableField: moduleName))
  		OfLength: (objectMemory byteSizeOf: moduleName)) ifFalse:[^self primitiveFail].
  	self flushExternalPrimitives.
  	self forceInterruptCheck.
  	self pop: 1 "pop moduleName; return receiver"!

Item was changed:
  ----- Method: SpurMemoryManager>>assignClassIndicesAndPinFrom:to:outPointers:filling: (in category 'image segment in/out') -----
  assignClassIndicesAndPinFrom: segmentStart to: segmentLimit outPointers: outPointerArray filling: loadedObjectsArray
  	"This is part of loadImageSegmentFrom:outPointers:.
  	 Make a final pass, assigning the real class indices and/or pinning pinned objects."
  	| fillIdx objOop |
  	objOop := self objectStartingAt: segmentStart.
  	fillIdx := 0.
  	[self oop: objOop isLessThan: segmentLimit] whileTrue:
  		[| classRef classOop classIndex |
  		 self storePointerUnchecked: fillIdx ofObject: loadedObjectsArray withValue: objOop.
  		 fillIdx := fillIdx + 1.
  		 "In the segment, class indices are offset indexes into the segment data,
  		  or into outPointers.  See mapOopsFrom:to:outPointers:outHashes: and
  		  newOutPointer:at:in:hashes:."
  		 classRef := self classIndexOf: objOop.
  		 classOop := (classRef anyMask: TopHashBit)
  						ifTrue: [self fetchPointer: classRef - TopHashBit ofObject: outPointerArray]
  						ifFalse: [classRef - self firstClassIndexPun * self allocationUnit + segmentStart].
  		 classIndex := self rawHashBitsOf: classOop.
+ 		 classIndex = 0 ifTrue:
+ 			[classIndex := self ensureBehaviorHash: classOop.
+ 			 classIndex < 0 ifTrue: "Error code e.g. - PrimErrNoMemory"
+ 				[^classIndex negated halt]].
  		 self assert: (classIndex > self lastClassIndexPun
  					  and: [(self classOrNilAtIndex: classIndex) = classOop]).
  		 self setClassIndexOf: objOop to: classIndex.
  		 ((self isInNewSpace: objOop)
  		  and: [self isPinned: objOop]) ifTrue:
  			[| oldClone |
  			 oldClone := self cloneInOldSpace: objOop forPinning: true.
  			 oldClone ~= 0 ifTrue:
  				[self setIsPinnedOf: oldClone to: true.
  				 self forward: objOop to: oldClone]].
  		 objOop := self objectAfter: objOop limit: segmentLimit]!

Item was changed:
  ----- Method: SpurMemoryManager>>mapOopsAndValidateClassRefsFrom:to:outPointers: (in category 'image segment in/out') -----
  mapOopsAndValidateClassRefsFrom: segmentStart to: segmentLimit outPointers: outPointerArray
  	"This is part of loadImageSegmentFrom:outPointers:.
  	 Scan through mapping oops and validating class references.  Defer
  	 entering any class objects into the class table and/or pinning objects
  	 until the second pass in assignClassIndicesAndPinFrom:to:outPointers:."
  	<var: 'segmentLimit' type: #usqInt>
  	| numOutPointers numSegObjs objOop |
  	<var: #oop type: #usqInt>
  	numOutPointers := self numSlotsOf: outPointerArray.
  	numSegObjs := 0.
  	objOop := self objectStartingAt: segmentStart.
  	[self oop: objOop isLessThan: segmentLimit] whileTrue:
  		[| classIndex hash oop mappedOop |
  		 numSegObjs := numSegObjs + 1.
  		 "No object in the segment should be marked.  If is is something is wrong."
  		 (self isMarked: objOop) ifTrue:
+ 			[^PrimErrInappropriate halt].
- 			[^PrimErrInappropriate].
  		 classIndex := self classIndexOf: objOop.
  		 "validate the class ref, but don't update it until any internal classes have been added to the class table."
  		 (classIndex anyMask: TopHashBit)
  			ifTrue:
  				[classIndex := classIndex - TopHashBit.
  				 classIndex >= numOutPointers ifTrue:
  					[^PrimErrBadIndex halt].
  				 mappedOop := self fetchPointer: classIndex ofObject: outPointerArray.
  				 hash := self rawHashBitsOf: mappedOop.
+ 				 (hash = 0 "class has yet to be instantiated"
+ 				  or: [hash > self lastClassIndexPun and: [(self classOrNilAtIndex: hash) = mappedOop]]) ifFalse:
- 				 (hash > self lastClassIndexPun and: [(self classOrNilAtIndex: hash) = mappedOop]) ifFalse:
  					[^PrimErrInappropriate halt]]
  			ifFalse: "The class is contained within the segment."
  				[(oop := classIndex - self firstClassIndexPun * self allocationUnit + segmentStart) >= segmentLimit ifTrue:
  					[^PrimErrBadIndex halt].
  				 (self rawHashBitsOf: oop) ~= 0 ifTrue:
  					[^PrimErrInappropriate halt]].
  		 0 to: (self numPointerSlotsOf: objOop) - 1 do:
  			[:i|
  			 oop := self fetchPointer: i ofObject: objOop.
  			 (self isNonImmediate: oop) ifTrue:
  				[(oop anyMask: TopOopBit)
  					ifTrue:
  						[(oop := oop - TopOopBit / self bytesPerOop) >= numOutPointers ifTrue:
  							[^PrimErrBadIndex halt].
  						 mappedOop := self fetchPointer: oop ofObject: outPointerArray]
  					ifFalse:
  						[(oop bitAnd: self allocationUnit - 1) ~= 0 ifTrue:
  							[^PrimErrInappropriate halt].
  						 (mappedOop := oop + segmentStart) >= segmentLimit ifTrue:
  							[^PrimErrBadIndex halt]].
  				 self storePointerUnchecked: i ofObject: objOop withValue: mappedOop]].
  		 objOop := self objectAfter: objOop limit: segmentLimit].
  	^numSegObjs negated!

Item was added:
+ ----- Method: StackInterpreter>>ioUnloadModule:OfLength: (in category 'debug support') -----
+ ioUnloadModule: moduleName OfLength: moduleNameLength
+ 	"Fake forgiving stub.  The actual code is in platforms/Cross/vm/sqNamedPrims.c"
+ 	<doNotGenerate>
+ 	^true!

Item was changed:
  ----- Method: StackInterpreterSimulator>>flushExternalPrimitives (in category 'plugin support') -----
  flushExternalPrimitives
+ 	self initializePluginEntries.
- 	mappedPluginEntries := OrderedCollection new.
  	super flushExternalPrimitives!

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.
  
  	self assert: ConstMinusOne = (objectMemory integerObjectOf: -1).
  
  	methodCache := Array new: MethodCacheSize.
  	nsMethodCache := Array new: NSMethodCacheSize.
  	atCache := Array new: AtCacheTotalSize.
  	self flushMethodCache.
  	gcSemaphoreIndex := 0.
  	externalSemaphoreSignalRequests := externalSemaphoreSignalResponses := #().
  	externalPrimitiveTable := CArrayAccessor on: (Array new: MaxExternalPrimitiveTableSize).
  	externalPrimitiveTableFirstFreeIndex := 0.
  	primitiveTable := self class primitiveTable copy.
+ 	self initializePluginEntries.
- 	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 := lastYieldMicroseconds := self ioUTCStartMicroseconds.
  
  	"initialize InterpreterSimulator variables used for debugging"
  	byteCount := sendCount := lookupCount := 0.
  	quitBlock := [^self close].
  	traceOn := true.
  	printSends := printReturns := printFrameAtEachStep := printBytecodeAtEachStep := false.
  	myBitBlt := BitBltSimulator new setInterpreter: self.
  	displayForm := fakeForm := 'Display has not yet been installed' asDisplayText form.
  	eventQueue := SharedQueue new.
  	suppressHeartbeatFlag := false.
  	systemAttributes := Dictionary new.
  	extSemTabSize := 256.
  	disableBooleanCheat := false.
+ 	assertVEPAES := false. "a flag so the assertValidExecutionPointers can be disabled for simulation speed and enabled when necessary."!
- 	assertVEPAES := true. "a flag so the assertValidExecutionPointers can be disabled for simulation speed"!

Item was added:
+ ----- Method: StackInterpreterSimulator>>initializePluginEntries (in category 'plugin support') -----
+ initializePluginEntries.
+ 	mappedPluginEntries := OrderedCollection new.
+ 	objectMemory hasSpurMemoryManagerAPI
+ 		ifTrue:
+ 			[primitiveAccessorDepthTable := Array new: primitiveTable size.
+ 			 pluginList := {}.
+ 			 self loadNewPlugin: '']
+ 		ifFalse:
+ 			[pluginList := {'' -> self }]!



More information about the Vm-dev mailing list