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

commits at source.squeak.org commits at source.squeak.org
Thu Sep 19 21:41:55 UTC 2013


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

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

Name: VMMaker.oscog-eem.393
Author: eem
Time: 19 September 2013, 2:39:25.571 pm
UUID: 89054bad-ac17-46e1-916f-9728d3774f3e
Ancestors: VMMaker.oscog-eem.392

Replace eeInstantiateSmallClass:sizeInBytes: with
eeInstantiateSmallClass:numSlots: and implement in SpurMemMgr.

Implement SpurMemMgr>>isClassOfNonImm:equalTo:.

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

Item was added:
+ ----- Method: NewObjectMemory>>eeInstantiateSmallClass:numSlots: (in category 'interpreter access') -----
+ eeInstantiateSmallClass: classPointer numSlots: numSlots
+ 	"This version of instantiateClass assumes that the total object
+ 	 size is under 256 bytes, the limit for objects with only one or
+ 	 two header words. 
+ 	 NOTE this code will only work for sizes that are an integral number of words
+ 		(like not a 32-bit LargeInteger in a 64-bit system).
+ 	 Will *not* cause a GC.
+ 	 Note that the created small object IS NOT FILLED and must be completed before returning it to Squeak.
+ 	 Since this call is used in routines that do just that we are safe. Break this rule and die."
+ 
+ 	| sizeInBytes hash header1 header2 hdrSize |
+ 	sizeInBytes := numSlots << ShiftForWord + BaseHeaderSize.
+ 	self assert: sizeInBytes <= 252.
+ 	hash := self newObjectHash.
+ 	header1 := (hash bitAnd: HashMaskUnshifted) << HashBitsOffset bitOr: (self formatOfClass: classPointer).
+ 	header2 := classPointer.
+ 	hdrSize := (header1 bitAnd: CompactClassMask) > 0 "is this a compact class"
+ 				ifTrue: [1]
+ 				ifFalse: [2].
+ 	header1 := header1 + (sizeInBytes - (header1 bitAnd: SizeMask+Size4Bit)).
+ 	^self eeAllocate: sizeInBytes headerSize: hdrSize h1: header1 h2: header2 h3: 0!

Item was removed:
- ----- Method: NewObjectMemory>>eeInstantiateSmallClass:sizeInBytes: (in category 'interpreter access') -----
- eeInstantiateSmallClass: classPointer sizeInBytes: sizeInBytes
- 	"This version of instantiateClass assumes that the total object
- 	 size is under 256 bytes, the limit for objects with only one or
- 	 two header words. Note that the size is specified in bytes
- 	 and should include 4 or 8 bytes for the base header word.
- 	 NOTE this code will only work for sizes that are an integral number of words
- 		(like not a 32-bit LargeInteger in a 64-bit system).
- 	 Will *not* cause a GC.
- 	 Note that the created small object IS NOT FILLED and must be completed before returning it to Squeak.
- 	 Since this call is used in routines that do just that we are safe. Break this rule and die."
- 
- 	| hash header1 header2 hdrSize |
- 	"size must be integral number of words"
- 	self assert: (sizeInBytes bitAnd: (BytesPerWord-1)) = 0.
- 	hash := self newObjectHash.
- 	header1 := (hash bitAnd: HashMaskUnshifted) << HashBitsOffset bitOr: (self formatOfClass: classPointer).
- 	header2 := classPointer.
- 	hdrSize := (header1 bitAnd: CompactClassMask) > 0 "is this a compact class"
- 				ifTrue: [1]
- 				ifFalse: [2].
- 	header1 := header1 + (sizeInBytes - (header1 bitAnd: SizeMask+Size4Bit)).
- 	^self eeAllocate: sizeInBytes headerSize: hdrSize h1: header1 h2: header2 h3: 0!

Item was added:
+ ----- Method: SpurMemoryManager>>eeInstantiateSmallClass:numSlots: (in category 'allocation') -----
+ eeInstantiateSmallClass: classObj numSlots: numSlots
+ 	| classIndex |
+ 	<inline: true>
+ 	classIndex := self ensureBehaviorHash: classObj.
+ 	^self
+ 		eeInstantiateClassIndex: classIndex
+ 		format: (self instSpecOfClass: classObj)
+ 		numSlots: numSlots!

Item was changed:
  ----- Method: SpurMemoryManager>>isClassOfNonImm:equalTo: (in category 'object testing') -----
  isClassOfNonImm: objOop equalTo: classOop
+ 	^(self classIndexOf: objOop) = (self rawHashBitsOf: classOop)!
- 	self shouldBeImplemented!

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."
  	(#(	DoIt
  		DoItIn:
  		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) includes: thisContext sender method selector) ifFalse:
- 		magnitude64BitValueOf:) includes: thisContext sender method selector) ifFalse:
  		[self halt].
  	^(oop bitAnd: 1) ~= 0!

Item was added:
+ ----- Method: SpurMemoryManager>>splObj:put: (in category 'interpreter access') -----
+ splObj: index put: anObject
+ 	"Set one of the objects in the SpecialObjectsArray"
+ 	self storePointer: index ofObject: specialObjectsOop withValue: anObject!

Item was changed:
  ----- Method: StackInterpreter>>closureIn:numArgs:instructionPointer:copiedValues: (in category 'control primitives') -----
  closureIn: context numArgs: numArgs instructionPointer: initialIP copiedValues: copiedValues
  	| newClosure numCopied |
  	<inline: true>
  	"numCopied should be zero for nil"
  	numCopied := objectMemory fetchWordLengthOf: copiedValues.
  	ClassBlockClosureCompactIndex ~= 0
  		ifTrue:
  			[newClosure := objectMemory
  								eeInstantiateClassIndex: ClassBlockClosureCompactIndex
  								format: objectMemory indexablePointersFormat
  								numSlots: ClosureFirstCopiedValueIndex + numCopied]
  		ifFalse:
  			[newClosure := objectMemory
  								eeInstantiateSmallClass: (objectMemory splObj: ClassBlockClosure)
+ 								numSlots: ClosureFirstCopiedValueIndex + numCopied].
- 								sizeInBytes: (BytesPerWord * (ClosureFirstCopiedValueIndex + numCopied)) + BaseHeaderSize].
  	"Assume: have just allocated a new closure; it must be young. Thus, can use unchecked stores."
  	objectMemory
  		storePointerUnchecked: ClosureOuterContextIndex ofObject: newClosure withValue: context;
  		storePointerUnchecked: ClosureStartPCIndex ofObject: newClosure withValue: (objectMemory integerObjectOf: initialIP);
  		storePointerUnchecked: ClosureNumArgsIndex ofObject: newClosure withValue: (objectMemory integerObjectOf: numArgs).
  	0 to: numCopied - 1 do:
  		[:i|
  		objectMemory storePointerUnchecked: i + ClosureFirstCopiedValueIndex
  			ofObject: newClosure
  			withValue: (objectMemory fetchPointer: i ofObject: copiedValues)].
  	^newClosure!

Item was changed:
  ----- Method: StackInterpreter>>closureIn:numArgs:instructionPointer:numCopiedValues: (in category 'control primitives') -----
  closureIn: context numArgs: numArgs instructionPointer: initialIP numCopiedValues: numCopied
  	| newClosure |
  	<inline: true>
  	ClassBlockClosureCompactIndex ~= 0
  		ifTrue:
  			[newClosure := objectMemory
  								eeInstantiateClassIndex: ClassBlockClosureCompactIndex
  								format: objectMemory indexablePointersFormat
  								numSlots: ClosureFirstCopiedValueIndex + numCopied]
  		ifFalse:
+ 			[newClosure := objectMemory
- 			[self assert: (BytesPerWord * (ClosureFirstCopiedValueIndex + numCopied)) + BaseHeaderSize <= 252.
- 			 newClosure := objectMemory
  								eeInstantiateSmallClass: (objectMemory splObj: ClassBlockClosure)
+ 								numSlots: ClosureFirstCopiedValueIndex + numCopied].
- 								sizeInBytes: (BytesPerWord * (ClosureFirstCopiedValueIndex + numCopied)) + BaseHeaderSize].
  	"Assume: have just allocated a new closure; it must be young. Thus, can use unchecked stores."
  	objectMemory storePointerUnchecked: ClosureOuterContextIndex ofObject: newClosure withValue: context.
  	objectMemory storePointerUnchecked: ClosureStartPCIndex ofObject: newClosure withValue: (objectMemory integerObjectOf: initialIP).
  	objectMemory storePointerUnchecked: ClosureNumArgsIndex ofObject: newClosure withValue: (objectMemory integerObjectOf: numArgs).
  	^newClosure!

Item was changed:
  ----- Method: StackInterpreter>>makePointwithxValue:yValue: (in category 'utilities') -----
  makePointwithxValue: xValue yValue: yValue
+ 	"make a Point xValue at yValue.
+ 	 We know both will be integers so no value nor root checking is needed"
- "make a Point xValue at yValue.
- We know both will be integers so no value nor root checking is needed"
  	| pointResult |
+ 	pointResult := objectMemory eeInstantiateSmallClass: (objectMemory splObj: ClassPoint) numSlots: YIndex + 1.
- 	pointResult := objectMemory eeInstantiateSmallClass: (objectMemory splObj: ClassPoint) sizeInBytes: 3*BytesPerWord.
  	objectMemory storePointerUnchecked: XIndex ofObject: pointResult withValue: (objectMemory integerObjectOf: xValue).
  	objectMemory storePointerUnchecked: YIndex ofObject: pointResult withValue: (objectMemory integerObjectOf: yValue).
+ 	^pointResult!
- 	^ pointResult!



More information about the Vm-dev mailing list