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

commits at source.squeak.org commits at source.squeak.org
Thu Nov 17 19:47:11 UTC 2016


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

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

Name: VMMaker.oscog-eem.1993
Author: eem
Time: 17 November 2016, 11:46:08.385148 am
UUID: b98dd9d4-1e93-4aa8-bd46-5ac460a44262
Ancestors: VMMaker.oscog-eem.1992

Fix primitiveIntegerAt in Spur 64-bits by always using signed32BitIntegerFor: to obtain the result object.  Refactor signed32BitIntegerFor: into an inlineable part that cvhecks for isIntegerValue: and a non-inlined part (noInlineSigned32BitIntegerGutsFor:) that constructs a LargeInteger object.

Fix a simulation inlitialization slip.

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

Item was changed:
  ----- Method: InterpreterPrimitives>>primitiveIntegerAt (in category 'sound primitives') -----
  primitiveIntegerAt
  	"Return the 32bit signed integer contents of a words receiver"
  
+ 	| index rcvr sz addr intValue result |
+ 	<var: #intValue type: #int>
+ 	index := self stackValue: 0.
+ 	(objectMemory isIntegerObject: index) ifFalse:
- 	| index rcvr sz addr value intValue |
- 	<var: #intValue type: 'int'>
- 	index := self stackIntegerValue: 0.
- 	self successful ifFalse:
  		[^self primitiveFailFor: PrimErrBadArgument].
  	rcvr := self stackValue: 1.
  	(objectMemory isWords: rcvr) ifFalse:
  		[^self primitiveFailFor: PrimErrInappropriate].
+ 	index := objectMemory integerValueOf: index.
  	sz := objectMemory lengthOf: rcvr.  "number of fields"
+ 	(index >= 1 and: [index <= sz]) ifFalse:
- 	((index >= 1) and: [index <= sz]) ifFalse:
  		[^self primitiveFailFor: PrimErrBadIndex].
  	"4 = 32 bits / 8"
  	addr := rcvr + objectMemory baseHeaderSize + (index - 1 * 4). "for zero indexing"
+ 	intValue := objectMemory intAt: addr.
+ 	result := self signed32BitIntegerFor: intValue.
+ 	self pop: 2 thenPush: result!
- 	value := objectMemory intAt: addr.
- 	self pop: 2.  "pop rcvr, index"
- 	"push element value"
- 	(objectMemory isIntegerValue: value)
- 		ifTrue: [self pushInteger: value]
- 		ifFalse: [intValue := value. "32 bit int may have been stored in 32 or 64 bit sqInt"
- 				self push: (self signed32BitIntegerFor: intValue)] "intValue may be sign extended to 64 bit sqInt"!

Item was changed:
  ----- Method: SpurMemoryManager>>initialize (in category 'initialization') -----
  initialize
  	"We can put all initializations that set something to 0 or to false here.
  	 In C all global variables are initialized to 0, and 0 is false."
  	remapBuffer := Array new: RemapBufferSize.
  	remapBufferCount := extraRootCount := 0. "see below"
  	freeListsMask := totalFreeOldSpace := lowSpaceThreshold := 0.
  	checkForLeaks := 0.
  	needGCFlag := signalLowSpace := scavengeInProgress := marking := false.
  	becomeEffectsFlags := 0.
  	statScavenges := statIncrGCs := statFullGCs := 0.
  	statScavengeGCUsecs := statIncrGCUsecs := statFullGCUsecs := statGCEndUsecs := 0.
  	statSGCDeltaUsecs := statIGCDeltaUsecs := statFGCDeltaUsecs := 0.
  	statGrowMemory := statShrinkMemory := statRootTableCount := 0.
  	statRootTableOverflows := statMarkCount := statCompactPassCount := statCoalesces := 0.
  
  	"We can initialize things that are allocated but are lazily initialized."
  	unscannedEphemerons := SpurContiguousObjStack new.
  
  	"we can initialize things that are virtual in C."
  	scavenger := SpurGenerationScavengerSimulator new manager: self; yourself.
  	segmentManager := SpurSegmentManager new manager: self; yourself.
  
  	"We can also initialize here anything that is only for simulation."
  	heapMap := CogCheck32BitHeapMap new.
  
  	"N.B. We *don't* initialize extraRoots because we don't simulate it."
+ 	maxOldSpaceSize := self class initializationOptions
+ 							ifNotNil: [:initOpts| initOpts at: #maxOldSpaceSize ifAbsent: [0]]
+ 							ifNil: [0]!
- 
- 	maxOldSpaceSize := self class initializationOptions ifNotNil: [:initOpts| initOpts at: #maxOldSpaceSize ifAbsent: [0]]!

Item was removed:
- ----- Method: StackInterpreter>>noInlineSigned32BitIntegerFor: (in category 'primitive support') -----
- noInlineSigned32BitIntegerFor: integerValue
- 	"Answer a full 32 bit integer object for the given integer value."
- 	<notOption: #Spur64BitMemoryManager>
- 	| newLargeInteger magnitude largeClass |
- 	<inline: false>
- 	<var: 'magnitude' type: 'unsigned int'>
- 	(objectMemory isIntegerValue: integerValue) ifTrue:
- 		[^objectMemory integerObjectOf: integerValue].
- 	self deny: objectMemory hasSixtyFourBitImmediates.
- 	 integerValue < 0
- 		ifTrue: [largeClass := ClassLargeNegativeIntegerCompactIndex.
- 				magnitude := 0 asUnsignedInteger - integerValue]
- 		ifFalse: [largeClass := ClassLargePositiveIntegerCompactIndex.
- 				magnitude := integerValue].
- 	newLargeInteger := objectMemory
- 							eeInstantiateSmallClassIndex: largeClass
- 							format: (objectMemory byteFormatForNumBytes: 4)
- 							numSlots: 1.
- 	SPURVM
- 		ifTrue:
- 			["Memory is 8 byte aligned in Spur, make sure that oversized bytes are set to zero" "eem 4/28/2016 questionable; they should never be read"
- 			objectMemory storeLong32: 0 ofObject: newLargeInteger withValue: (objectMemory byteSwapped32IfBigEndian: magnitude).
- 			objectMemory storeLong32: 1 ofObject: newLargeInteger withValue: 0]
- 		ifFalse: 
- 			[objectMemory storeLong32: 0 ofObject: newLargeInteger withValue: (objectMemory byteSwapped32IfBigEndian: magnitude)].
- 	^newLargeInteger!

Item was added:
+ ----- Method: StackInterpreter>>noInlineSigned32BitIntegerGutsFor: (in category 'primitive support') -----
+ noInlineSigned32BitIntegerGutsFor: integerValue
+ 	"Answer a full 32 bit integer object for the given integer value which
+ 	 is known not to be a SmallInteger value.  This serves to share the
+ 	 code for creating a four byte LargeInteger in one place."
+ 	<notOption: #Spur64BitMemoryManager>
+ 	| newLargeInteger magnitude largeClass |
+ 	<inline: #never>
+ 	<var: #magnitude type: #'unsigned int'>
+ 	self deny: objectMemory hasSixtyFourBitImmediates.
+ 	self deny: (objectMemory isIntegerValue: integerValue).
+ 	 integerValue < 0
+ 		ifTrue: [largeClass := ClassLargeNegativeIntegerCompactIndex.
+ 				magnitude := 0 asUnsignedInteger - integerValue]
+ 		ifFalse: [largeClass := ClassLargePositiveIntegerCompactIndex.
+ 				magnitude := integerValue].
+ 	newLargeInteger := objectMemory
+ 							eeInstantiateSmallClassIndex: largeClass
+ 							format: (objectMemory byteFormatForNumBytes: 4)
+ 							numSlots: 1.
+ 	objectMemory storeLong32: 0 ofObject: newLargeInteger withValue: (objectMemory byteSwapped32IfBigEndian: magnitude).
+ 	SPURVM ifTrue: "Memory is 8 byte aligned in Spur, make sure that oversized bytes are set to zero" "eem 4/28/2016 questionable; they should never be read"
+ 		[objectMemory storeLong32: 1 ofObject: newLargeInteger withValue: 0].
+ 	^newLargeInteger!

Item was changed:
  ----- Method: StackInterpreter>>signed32BitIntegerFor: (in category 'primitive support') -----
  signed32BitIntegerFor: integerValue
  	"Answer a full 32 bit integer object for the given integer value.
  	 N.B.  Returning in each arm separately enables Slang inlining.
  	 /Don't/ return the ifTrue:ifFalse: unless Slang inlining of conditionals is fixed."
  	<inline: true>
  	objectMemory hasSixtyFourBitImmediates
  		ifTrue:
  			[^objectMemory integerObjectOf: 
  				(self cCode: [self cCoerceSimple: integerValue to: #int]
  					inSmalltalk: [(integerValue bitAnd: 16r7FFFFFFF)
  								- ((integerValue >> 31 anyMask: 1)
  									ifTrue: [-16r100000000]
  									ifFalse: [0])])]
  		ifFalse:
+ 			[(objectMemory isIntegerValue: integerValue) ifTrue:
+ 				[^objectMemory integerObjectOf: integerValue].
+ 			 ^self noInlineSigned32BitIntegerGutsFor: integerValue]!
- 			[^self noInlineSigned32BitIntegerFor: integerValue]!



More information about the Vm-dev mailing list