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

commits at source.squeak.org commits at source.squeak.org
Fri Sep 20 22:47:26 UTC 2013


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

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

Name: VMMaker.oscog-eem.398
Author: eem
Time: 20 September 2013, 3:44:40.472 pm
UUID: 64814c0c-d38d-4665-9e06-a93bdc68cc80
Ancestors: VMMaker.oscog-eem.397

Add remap buffer support.

More protocol.  Spur VM gets to first bitblt.

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

Item was changed:
  ----- Method: InterpreterPrimitives>>primitiveShortAt (in category 'sound primitives') -----
  primitiveShortAt
  	"Treat the receiver, which can be indexible by either bytes or words, as an array of signed 16-bit values. Return the contents of the given index. Note that the index specifies the i-th 16-bit entry, not the i-th byte or word."
  
  	| index rcvr sz addr value |
  	index := self stackIntegerValue: 0.
  	self successful ifFalse:
  		[^self primitiveFailFor: PrimErrBadArgument].
  	rcvr := self stackValue: 1.
+ 	(objectMemory isWordsOrBytes: rcvr) ifFalse:
- 	((objectMemory isIntegerObject: rcvr)
- 	or: [(objectMemory isWordsOrBytes: rcvr) not]) ifTrue:
  		[^self primitiveFailFor: PrimErrInappropriate].
+ 	sz := (objectMemory numSlotsOf: rcvr) * objectMemory bytesPerOop // 2.  "number of 16-bit fields"
- 	sz := ((objectMemory sizeBitsOf: rcvr) - BaseHeaderSize) // 2.  "number of 16-bit fields"
  	((index >= 1) and: [index <= sz]) ifFalse:
  		[^self primitiveFailFor: PrimErrBadIndex].
+ 	addr := rcvr + objectMemory baseHeaderSize + (2 * (index - 1)).
- 	addr := rcvr + BaseHeaderSize + (2 * (index - 1)).
  	value := objectMemory shortAt: addr.
  	self pop: 2 thenPushInteger: value!

Item was added:
+ ----- Method: Spur32BitMMLESimulator>>fetchInteger:ofObject: (in category 'simulation only') -----
+ fetchInteger: fieldIndex ofObject: objectPointer
+ 	"hack around the CoInterpreter/ObjectMemory split refactoring"
+ 	^coInterpreter fetchInteger: fieldIndex ofObject: objectPointer!

Item was added:
+ ----- Method: Spur32BitMMLESimulator>>primitiveFail (in category 'simulation only') -----
+ primitiveFail
+ 	"hack around the CoInterpreter/ObjectMemory split refactoring"
+ 	^coInterpreter primitiveFail!

Item was added:
+ ----- Method: Spur32BitMMLESimulator>>shortAt: (in category 'memory access') -----
+ shortAt: byteAddress
+     "Return the half-word at byteAddress which must be even."
+ 	| lowBits long |
+ 	lowBits := byteAddress bitAnd: 2.
+ 	long := self longAt: byteAddress - lowBits.
+ 	^ lowBits = 2
+ 		ifTrue: [ long bitShift: -16 ]
+ 		ifFalse: [ long bitAnd: 16rFFFF ]!

Item was added:
+ ----- Method: Spur32BitMMLESimulator>>showDisplayBits:Left:Top:Right:Bottom: (in category 'simulation only') -----
+ showDisplayBits: aForm Left: l Top: t Right: r Bottom: b
+ 	"hack around the CoInterpreter/ObjectMemory split refactoring"
+ 	^coInterpreter showDisplayBits: aForm Left: l Top: t Right: r Bottom: b!

Item was added:
+ ----- Method: Spur32BitMMLESimulator>>transcript (in category 'simulation only') -----
+ transcript
+ 	"hack around the CoInterpreter/ObjectMemory split refactoring"
+ 	^coInterpreter transcript!

Item was changed:
  CogClass subclass: #SpurMemoryManager
(excessive size, no diff calculated)

Item was changed:
  ----- Method: SpurMemoryManager class>>initialize (in category 'class initialization') -----
  initialize
  	"CogObjectMemory initialize"
  	NumFreeLists := 65. "One for each size up to and including 64 slots. One for sizes > 64 slots."
+ 	CheckObjectOverwrite := true.
+ 
+ 	"The remap buffer support is for compatibility; Spur doesn't GC during allocation.
+ 	 Eventually this should die."
+ 	RemapBufferSize := 25!
- 	CheckObjectOverwrite := true!

Item was added:
+ ----- Method: SpurMemoryManager>>classArray (in category 'plugin support') -----
+ classArray
+ 	"a.k.a. self fetchPointer: ClassArrayCompactIndex ofObject: classTableFirstPage"
+ 	^self splObj: ClassArray!

Item was added:
+ ----- Method: SpurMemoryManager>>classByteArray (in category 'interpreter access') -----
+ classByteArray
+ 	"a.k.a. self fetchPointer: ClassByteArrayCompactIndex ofObject: classTableFirstPage"
+ 	^self splObj: ClassByteArray!

Item was changed:
  ----- Method: SpurMemoryManager>>initialize (in category 'initialization') -----
  initialize
+ 	"We can put all initializatins that set something to 0 or to false here.
+ 	 In C all global variables are initialized to 0, and 0 is false."
  	freeLists := CArrayAccessor on: (Array new: NumFreeLists withAll: 0).
+ 	remapBuffer := Array new: RemapBufferSize.
+ 	remapBufferCount := 0.
  	freeListsMask := 0.
  	checkForLeaks := 0.
  	needGCFlag := signalLowSpace := scavengeInProgress := false.
  	becomeEffectsFlags := 0.
- 	heapMap := self wordSize = 4 ifTrue: [CogCheck32BitHeapMap new].
  	statScavenges := statIncrGCs := statFullGCs := 0.
  	statScavengeGCUsecs := statIncrGCUsecs := statFullGCUsecs := 0.
+ 	statSGCDeltaUsecs := statIGCDeltaUsecs := statFGCDeltaUsecs := 0.
+ 
+ 	"We can also initialize here anything that is only for simulation."
+ 	heapMap := self wordSize = 4 ifTrue: [CogCheck32BitHeapMap new]!
- 	statSGCDeltaUsecs := statIGCDeltaUsecs := statFGCDeltaUsecs := 0!

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."
  	| sel |
  	sel := thisContext sender method selector.
  	(#(	DoIt
  		DoItIn:
  		on:do: "from the debugger"
  		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
  		primitiveAsCharacter
  		primitiveInputSemaphore
  		baseFrameReturn
  		primitiveExternalCall
  		primDigitCompare:
  		isLiveContext:
  		numPointerSlotsOf:
+ 		fileValueOf:
+ 		loadBitBltDestForm
+ 		fetchIntOrFloat:ofObject:ifNil:
+ 		fetchIntOrFloat:ofObject:
+ 		loadBitBltSourceForm) includes: sel) ifFalse:
- 		fileValueOf:) includes: sel) ifFalse:
  		[self halt].
  	^(oop bitAnd: 1) ~= 0!

Item was added:
+ ----- Method: SpurMemoryManager>>isWordsOrBytes: (in category 'object testing') -----
+ isWordsOrBytes: oop
+ 	^(self isNonImmediate: oop)
+ 	  and: [self isWordsOrBytesNonImm: oop]!

Item was added:
+ ----- Method: SpurMemoryManager>>isWordsOrBytesNonImm: (in category 'object testing') -----
+ isWordsOrBytesNonImm: objOop
+ 	^(self formatOf: objOop) > self lastPointerFormat!

Item was added:
+ ----- Method: SpurMemoryManager>>popRemappableOop (in category 'interpreter access') -----
+ popRemappableOop
+ 	"Pop and return the possibly remapped object from the remap buffer.
+ 	 We support this excessence for compatibility with ObjectMemory.
+ 	 Spur doesn't GC during allocation."
+ 	<api>
+ 	| oop |
+ 	oop := remapBuffer at: remapBufferCount.
+ 	remapBufferCount := remapBufferCount - 1.
+ 	^oop!

Item was added:
+ ----- Method: SpurMemoryManager>>pushRemappableOop: (in category 'interpreter access') -----
+ pushRemappableOop: oop
+ 	"Record the given object in a the remap buffer. Objects in this buffer are remapped
+ 	 when a compaction occurs. This facility is used by the interpreter to ensure that
+ 	 objects in temporary variables are properly remapped.
+ 	 We support this excessence for compatibility with ObjectMemory.
+ 	 Spur doesn't GC during allocation."
+ 	<api>
+ 	self assert: (self addressCouldBeOop: oop).
+ 	remapBuffer at: (remapBufferCount := remapBufferCount + 1) put: oop.
+ 	remapBufferCount <= RemapBufferSize ifFalse:
+ 		[self error: 'remapBuffer overflow']!

Item was added:
+ ----- Method: SpurMemoryManager>>remapBuffer (in category 'interpreter access') -----
+ remapBuffer
+ 	"We support this excessence for compatibility with ObjectMemory.
+ 	 Spur doesn't GC during allocation."
+ 	^remapBuffer!

Item was changed:
  ----- Method: SpurMemoryManager>>sufficientSpaceAfterGC: (in category 'generation scavenging') -----
  sufficientSpaceAfterGC: numBytes
  	"This is ObjectMemory's funky entry-point into its incremental GC,
  	 which is a stop-the-world a young generation reclaimer.  In Spur
  	 we run the scavenger."
  	self assert: numBytes = 0.
+ 	self assert: remapBufferCount = 0.
  	"coInterpreter printCallStackFP: coInterpreter framePointer"
  
  	self runLeakCheckerForFullGC: false.
  	coInterpreter preGCAction: GCModeIncr.
  	needGCFlag := false.
  
  	gcStartUsecs := coInterpreter ioUTCMicrosecondsNow.
  
  	scavengeInProgress := true.
  	pastSpaceStart := scavenger scavenge.
  	self assert: (self
  					oop: pastSpaceStart
  					isGreaterThanOrEqualTo: scavenger pastSpace start
  					andLessThanOrEqualTo: scavenger pastSpace limit).
  	freeStart := scavenger eden start.
  	self initSpaceForAllocationCheck: scavenger eden.
  	scavengeInProgress := false.
  
  	statScavenges := statScavenges + 1.
  	statGCEndUsecs := coInterpreter ioUTCMicrosecondsNow.
  	statSGCDeltaUsecs := statGCEndUsecs - gcStartUsecs.
  	statScavengeGCUsecs := statScavengeGCUsecs + statSGCDeltaUsecs.
  
  	coInterpreter postGCAction.
  	self runLeakCheckerForFullGC: false.
  
  	^true!

Item was added:
+ ----- Method: SpurMemoryManager>>topRemappableOop (in category 'interpreter access') -----
+ topRemappableOop
+ 	<api>
+ 	"Answers the top of the remappable oop stack. Useful when writing loops.
+ 	 We support this excessence for compatibility with ObjectMemory.
+ 	 Spur doesn't GC during allocation."
+ 	^remapBuffer at: remapBufferCount!

Item was changed:
  ----- Method: StackInterpreterPrimitives>>primitiveObjectPointsTo (in category 'object access primitives') -----
  primitiveObjectPointsTo
  	"This primitive is assumed to be fast (see e.g. MethodDictionary>>includesKey:) so make it so.
  	 N.B.  Written to use literalHeaderOf: so that in Cog subclasses cogged methods (whose headers
  	 point to the machine code method) are still correctly scanned, for the header as well as literals."
  	| rcvr thang header fmt lastField methodHeader |
  	thang := self stackTop.
  	rcvr := self stackValue: 1.
+ 	(objectMemory isImmediate: rcvr) ifTrue:
- 	(objectMemory isIntegerObject: rcvr) ifTrue:
  		[^self pop: 2 thenPushBool: false].
  
  	"Inlined version of lastPointerOf: for speed in determining if rcvr is a context."
  	header := objectMemory baseHeader: rcvr.
  	fmt := objectMemory formatOfHeader: header.
  	(objectMemory isPointersFormat: fmt)
  		ifTrue:
  			[(fmt = objectMemory indexablePointersFormat
  			  and: [objectMemory isContextHeader: header]) 
  				ifTrue:
  	 				[(self isMarriedOrWidowedContext: rcvr) ifTrue:
  						[self externalWriteBackHeadFramePointers.
  						 (self isStillMarriedContext: rcvr) ifTrue:
  							[^self pop: 2
  									thenPushBool: (self marriedContext: rcvr
  														pointsTo: thang
  														stackDeltaForCurrentFrame: 2)]].
  					"contexts end at the stack pointer"
+ 					lastField := CtxtTempFrameStart + (self fetchStackPointerOf: rcvr) * BytesPerOop]
- 					lastField := CtxtTempFrameStart + (self fetchStackPointerOf: rcvr) * BytesPerWord]
  				ifFalse:
+ 					[lastField := (objectMemory sizeBitsOfSafe: rcvr) - objectMemory baseHeaderSize]]
- 					[lastField := (objectMemory sizeBitsOfSafe: rcvr) - BaseHeaderSize]]
  		ifFalse:
  			[fmt < objectMemory firstCompiledMethodFormat "no pointers" ifTrue:
  				[^self pop: 2 thenPushBool: false].
  			"CompiledMethod: contains both pointers and bytes:"
  			methodHeader := self headerOf: rcvr.
  			methodHeader = thang ifTrue: [^self pop: 2 thenPushBool: true].
+ 			lastField := ((self literalCountOfHeader: methodHeader) + 1) * BytesPerOop].
- 			lastField := ((self literalCountOfHeader: methodHeader) + 1) * BytesPerWord].
  
+ 	objectMemory baseHeaderSize to: lastField by: objectMemory bytesPerOop do:
- 	BaseHeaderSize to: lastField by: BytesPerWord do:
  		[:i |
  		(self longAt: rcvr + i) = thang ifTrue:
  			[^self pop: 2 thenPushBool: true]].
  	self pop: 2 thenPushBool: false!



More information about the Vm-dev mailing list