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

commits at source.squeak.org commits at source.squeak.org
Wed Sep 11 01:20:32 UTC 2013


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

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

Name: VMMaker.oscog-eem.367
Author: eem
Time: 10 September 2013, 6:17:29.89 pm
UUID: 09afa7c7-ad24-4cc7-bb80-7104da4b97c6
Ancestors: VMMaker.oscog-eem.366

Implement pushNewArrayBytecode in terms of new instantiation
api.  Hence fix > 0 assert in eeInstantiateClassIndex:format:numSlots:.
Add pastSpaceBytes and simplify accordingly.
Bootstrap executes 2113 bytecodes, but appears to fail an Array basicNew:.

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

Item was changed:
  ----- Method: NewObjectMemory>>eeInstantiateClassIndex:format:numSlots: (in category 'interpreter access') -----
  eeInstantiateClassIndex: compactClassIndex format: objFormat numSlots: numSlots
  	"Instantiate an instance of a compact class.  ee stands for execution engine and
  	 implies that this allocation will *NOT* cause a GC.  N.B. the instantiated object
  	 IS NOT FILLED and must be completed before returning it to Smalltalk. Since this
  	 call is used in routines that do just that we are safe.  Break this rule and die in GC."
  	<api>
  	| hash header1 header2 byteSize header3 hdrSize |
  	<inline: false>
  	"cannot have a negative indexable field count"
+ 	self assert: (numSlots >= 0 and: [compactClassIndex ~= 0]).
- 	self assert: (numSlots > 0 and: [compactClassIndex ~= 0]).
  	self assert: (objFormat < self firstByteFormat
  					ifTrue: [objFormat]
  					ifFalse: [objFormat bitAnd: self byteFormatMask])
  				= (self instSpecOfClass: (self compactClassAt: compactClassIndex)).
  	hash := self newObjectHash.
  	"Low 2 bits are 0"
  	header1 := (objFormat << self instFormatFieldLSB
  					bitOr: compactClassIndex << 12)
  					bitOr: (hash bitAnd: HashMaskUnshifted) << HashBitsOffset.
  	self assert: "sizeHiBits" ((self formatOfClass: (self compactClassAt: compactClassIndex)) bitAnd: 16r60000) >> 9 = 0.
  	self flag: #sizeLowBits.
  	"size in bytes -- low 2 bits are 0; may need another shift if 64-bits.
  	 strangely, size includes size of header, but only of single header.
  	 why include header size at all?  gives us an extra word."
  	byteSize := numSlots << (ShiftForWord + (ShiftForWord-2)) + BaseHeaderSize.
  	(BytesPerWord = 8 "David, please check this!!!!"
  	 and: [objFormat >= self firstLongFormat "32-bit longs and byte objects"
  	 and: [(numSlots bitAnd: 1) ~= 0]]) ifTrue:
  		["extra low bit (4) for 64-bit VM goes in 4-bit (betw hdr bits and sizeBits)"
  		 header1 := header1 bitOr: 4].
  	byteSize > 255 "requires size header word/full header"
  		ifTrue: [header3 := byteSize. hdrSize := 3. header2 := self compactClassAt: compactClassIndex]
  		ifFalse: [header1 := header1 bitOr: byteSize. hdrSize := 1].
  	^self eeAllocate: byteSize headerSize: hdrSize h1: header1 h2: header2 h3: header3!

Item was added:
+ ----- Method: SpurGenerationScavenger>>pastSpaceBytes (in category 'accessing') -----
+ pastSpaceBytes
+ 	^pastSpace limit - pastSpace start!

Item was added:
+ ----- Method: SpurMemoryManager>>isInSurvivorSpace: (in category 'object testing') -----
+ isInSurvivorSpace: objOop
+ 	^objOop >= scavenger pastSpace start
+ 	  and: [objOop < scavenger pastSpace limit]!

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."
  	(#(	makeBaseFrameFor:
  		quickFetchInteger:ofObject:
  		frameOfMarriedContext:
  		addressCouldBeClassObj:
  		isMarriedOrWidowedContext:
  		shortPrint:
  		bytecodePrimAt
  		commonAt:
  		loadFloatOrIntFrom:
  		positive32BitValueOf:
  		primitiveExternalCall
  		checkedIntegerValueOf:
  		bytecodePrimAtPut
  		commonAtPut:
+ 		primitiveVMParameter
+ 		checkIsStillMarriedContext:currentFP:) includes: thisContext sender method selector) ifFalse:
- 		primitiveVMParameter) includes: thisContext sender method selector) ifFalse:
  		[self halt].
  	^(oop bitAnd: 1) ~= 0!

Item was changed:
  ----- Method: SpurMemoryManager>>tenuringThreshold (in category 'accessing') -----
  tenuringThreshold
  	"In the scavenger the tenuring threshold is effectively a number of bytes of objects,
  	 accessed as a proportion of pastSpace from 0 to 1.   In the Squeak image the tenuring
  	 threshold is an object count. Marry the two notions  by multiplying the proportion by
  	 the size of pastSpace and dividing by the average object size, as derived from observation."
  	| averageObjectSize |
  	averageObjectSize := 8 * self wordSize.
+ 	^scavenger scavengerTenuringThreshold * scavenger pastSpaceBytes // averageObjectSize!
- 	^scavenger scavengerTenuringThreshold * (scavenger pastSpace limit - scavenger pastSpace start) // averageObjectSize!

Item was changed:
  ----- Method: SpurMemoryManager>>tenuringThreshold: (in category 'accessing') -----
  tenuringThreshold: threshold
  	"c.f. tenuringThreshold"
  	scavenger scavengerTenuringThreshold:
  		(threshold * 8 * self wordSize) asFloat
+ 		/ scavenger pastSpaceBytes asFloat!
- 		/ (scavenger pastSpace limit - scavenger pastSpace start) asFloat!

Item was changed:
  ----- Method: StackInterpreter>>checkIsStillMarriedContext:currentFP: (in category 'frame access') -----
  checkIsStillMarriedContext: aContext currentFP: currentFP
  	"Another version of isWidowedContext:currentFP: for debugging.
  	 This will not bereave a widowed context."
  	| thePage theFP limitFP |
  	<inline: false>
  	<var: #currentFP type: #'char *'>
  	<var: #thePage type: #'StackPage *'>
  	<var: #theFP type: #'char *'>
  	<var: #limitFP type: #'char *'>
  	(objectMemory isIntegerObject: (objectMemory fetchPointer: SenderIndex ofObject: aContext)) ifFalse:
  		[^false].
  	theFP := self frameOfMarriedContext: aContext.
  	thePage := stackPages stackPageFor: theFP.
  	limitFP := (thePage = stackPage and: [currentFP notNil])
  				ifTrue: [currentFP]
  				ifFalse: [thePage headFP].
  	^theFP >= limitFP
+ 	   and: [(objectMemory isNonImmediate: (self frameCallerFP: theFP) asInteger)
- 	   and: [(objectMemory isNonIntegerObject: (self frameCallerFP: theFP) asInteger)
  	   and: [(self withSmallIntegerTags: (self frameCallerFP: theFP))
  			= (objectMemory fetchPointer: InstructionPointerIndex ofObject: aContext)
  	   and: [(self frameMethodObject: theFP)
  			= (objectMemory fetchPointer: MethodIndex ofObject: aContext)
  	   and: [(self frameHasContext: theFP)
  	   and: [(self frameContext: theFP) = aContext
  	   and: [objectMemory isContext: aContext]]]]]]!

Item was changed:
  ----- Method: StackInterpreter>>pushNewArrayBytecode (in category 'stack bytecodes') -----
  pushNewArrayBytecode
  	| size popValues array |
  	size := self fetchByte.
  	popValues := size > 127.
  	size := size bitAnd: 127.
  	self fetchNextBytecode.
  	self externalizeIPandSP.
+ 	array := objectMemory
+ 				eeInstantiateClassIndex: ClassArrayCompactIndex
+ 				format: objectMemory arrayFormat
+ 				numSlots: size.
- 	array := objectMemory eeInstantiateClass: (objectMemory splObj: ClassArray) indexableSize: size.
  	self internalizeIPandSP.
  	popValues
  		ifTrue:
  			[0 to: size - 1 do:
  				[:i|
  				"Assume: have just allocated a new Array; it must be young. Thus, can use unchecked stores."
  				objectMemory storePointerUnchecked: i ofObject: array withValue: (self internalStackValue: size - i - 1)].
  			 self internalPop: size]
  		ifFalse:
  			[0 to: size - 1 do:
  				[:i|
  				objectMemory storePointerUnchecked: i ofObject: array withValue: objectMemory nilObject]].
  	self internalPush: array!

Item was changed:
  ----- Method: StackInterpreter>>shortPrintOop: (in category 'debug printing') -----
  shortPrintOop: oop
  	<inline: false>
  	self printHex: oop.
  	(objectMemory isImmediate: oop) ifTrue:
  		[(objectMemory isImmediateCharacter: oop) ifTrue:
  			[^self
  				cCode: 'printf("=$%ld ($%c)\n", (long)characterValueOf(oop), (long)characterValueOf(oop))'
  				inSmalltalk: [self print: (self shortPrint: oop); cr]].
  		 ^self
  			cCode: 'printf("=%ld\n", (long)integerValueOf(oop))'
  			inSmalltalk: [self print: (self shortPrint: oop); cr]].
  	(objectMemory addressCouldBeObj: oop) ifFalse:
  		[self print: ((oop bitAnd: objectMemory allocationUnit - 1) ~= 0
  						ifTrue: [' is misaligned']
  						ifFalse: [' is not on the heap']); cr.
  		 ^nil].
  	self print: ': a(n) '.
+ 	self printNameOfClass: (objectMemory fetchClassOfNonImm: oop) count: 5.
- 	self printNameOfClass: (objectMemory fetchClassOf: oop) count: 5.
  	self cr!



More information about the Vm-dev mailing list