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

commits at source.squeak.org commits at source.squeak.org
Tue Sep 10 23:06:27 UTC 2013


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

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

Name: VMMaker.oscog-eem.365
Author: eem
Time: 10 September 2013, 4:03:44.067 pm
UUID: 204f4b62-3c38-42d8-bab5-2f8d04c98f79
Ancestors: VMMaker.oscog-eem.364

Fix bug in SpurMemoryManager>>lengthOf:baseHeader:format: for
32-bit bit-indexable objects.

Make primitiveBeCursor use objectMemory baseHeaderSize et al.

Simplify StackInterpreter>>isFloatObject: now ClassFloatCompactIndex is required to be non-zero.

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

Item was changed:
  ----- Method: InterpreterPrimitives>>primitiveBeCursor (in category 'I/O primitives') -----
  primitiveBeCursor
  	"Set the cursor to the given shape. The Mac only supports 16x16 pixel cursors. Cursor offsets are handled by Smalltalk."
  
  	| cursorObj maskBitsIndex maskObj bitsObj extentX extentY depth offsetObj offsetX offsetY cursorBitsIndex ourCursor |
  
  	argumentCount = 0 ifTrue: [
  		cursorObj := self stackTop.
  		maskBitsIndex := nil].
  	argumentCount = 1 ifTrue: [
  		cursorObj := self stackValue: 1.
  		maskObj := self stackTop].
+ 	self success: argumentCount < 2.
- 	self success: (argumentCount < 2).
  
  	self success: ((objectMemory isPointers: cursorObj) and: [(objectMemory lengthOf: cursorObj) >= 5]).
  	self successful ifTrue: [
  		bitsObj := objectMemory fetchPointer: 0 ofObject: cursorObj.
  		extentX := self fetchInteger: 1 ofObject: cursorObj.
  		extentY := self fetchInteger: 2 ofObject: cursorObj.
  		depth := self fetchInteger: 3 ofObject: cursorObj.
  		offsetObj := objectMemory fetchPointer: 4 ofObject: cursorObj].
  		self success: ((objectMemory isPointers: offsetObj) and: [(objectMemory lengthOf: offsetObj) >= 2]).
  
  	self successful ifTrue: [
  		offsetX := self fetchInteger: 0 ofObject: offsetObj.
  		offsetY := self fetchInteger: 1 ofObject: offsetObj.
  		(argumentCount = 0 and: [depth = 32])
  			ifTrue: [
  				"Support arbitrary-sized 32 bit ARGB forms --bf 3/1/2007 23:51"
  				self success: ((extentX > 0) and: [extentY > 0]).
  				self success: ((offsetX >= (extentX * -1)) and: [offsetX <= 0]).
  				self success: ((offsetY >= (extentY * -1)) and: [offsetY <= 0]).
  				self success: ((objectMemory isWords: bitsObj) and: [(objectMemory lengthOf: bitsObj) = (extentX * extentY)]).
  				cursorBitsIndex := bitsObj + BaseHeaderSize.
  				self cCode: '' inSmalltalk:
  					[ourCursor := Cursor
  						extent: extentX @ extentY
  						depth: 32
  						fromArray: ((1 to: extentX * extentY) collect: [:i |
  							objectMemory fetchLong32: i-1 ofObject: bitsObj])
  						offset: offsetX  @ offsetY]]
  			ifFalse: [
  				self success: ((extentX = 16) and: [extentY = 16 and: [depth = 1]]).
  				self success: ((offsetX >= -16) and: [offsetX <= 0]).
  				self success: ((offsetY >= -16) and: [offsetY <= 0]).
  				self success: ((objectMemory isWords: bitsObj) and: [(objectMemory lengthOf: bitsObj) = 16]).
+ 				cursorBitsIndex := bitsObj + objectMemory baseHeaderSize.
- 				cursorBitsIndex := bitsObj + BaseHeaderSize.
  				self cCode: '' inSmalltalk:
  					[ourCursor := Cursor
  						extent: extentX @ extentY
  						fromArray: ((1 to: 16) collect: [:i |
+ 							((objectMemory fetchLong32: i-1 ofObject: bitsObj) >> (objectMemory wordSize*8 - 16)) bitAnd: 16rFFFF])
- 							((objectMemory fetchLong32: i-1 ofObject: bitsObj) >> (BytesPerWord*8 - 16)) bitAnd: 16rFFFF])
  						offset: offsetX  @ offsetY]]].
  
  	argumentCount = 1 ifTrue: [
  		self success: ((objectMemory isPointers: maskObj) and: [(objectMemory lengthOf: maskObj) >= 5]).
  		self successful ifTrue: [
  			bitsObj := objectMemory fetchPointer: 0 ofObject: maskObj.
  			extentX := self fetchInteger: 1 ofObject: maskObj.
  			extentY := self fetchInteger: 2 ofObject: maskObj.
  			depth := self fetchInteger: 3 ofObject: maskObj].
  
  		self successful ifTrue: [
  			self success: ((extentX = 16) and: [extentY = 16 and: [depth = 1]]).
  			self success: ((objectMemory isWords: bitsObj) and: [(objectMemory lengthOf: bitsObj) = 16]).
+ 			maskBitsIndex := bitsObj + objectMemory baseHeaderSize]].
- 			maskBitsIndex := bitsObj + BaseHeaderSize]].
  
  	self successful ifTrue: [
  		argumentCount = 0
  			ifTrue: [
  				depth = 32
  					ifTrue: [(self cCode: 'ioSetCursorARGB(cursorBitsIndex, extentX, extentY, offsetX, offsetY)'
  						inSmalltalk: [ourCursor show. Cursor currentCursor == ourCursor])	
  							ifFalse: [^self success: false]]
  					ifFalse: [self cCode: 'ioSetCursor(cursorBitsIndex, offsetX, offsetY)'
  						inSmalltalk: [ourCursor show]]]
  			ifFalse: [self cCode: 'ioSetCursorWithMask(cursorBitsIndex, maskBitsIndex, offsetX, offsetY)'
  						inSmalltalk: [cursorBitsIndex == maskBitsIndex. "placate compiler"
  									ourCursor show]].
  		self pop: argumentCount]!

Item was added:
+ ----- Method: SpurMemoryManager>>compactClassIndexOf: (in category 'object access') -----
+ compactClassIndexOf: objOop
+ 	^self classIndexOf: objOop!

Item was added:
+ ----- Method: SpurMemoryManager>>instanceSizeOf: (in category 'interpreter access') -----
+ instanceSizeOf: classObj
+ 	<api>
+ 	"Answer the number of slots in a class.  For example the instanceSizeOf: 
+ 	 ClassPoint is 2, for the x & y slots. The instance size of non-pointer classes is 0."
+ 	self assert: (coInterpreter addressCouldBeClassObj: classObj).
+ 
+ 	^(self formatOfClass: classObj) bitAnd: self fixedFieldsOfClassFormatMask!

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

Item was changed:
  ----- Method: SpurMemoryManager>>lengthOf:baseHeader:format: (in category 'object access') -----
  lengthOf: objOop baseHeader: header format: fmt 
  	<var: #header type: #usqLong>
  	"Compatibility; does not really suit the Spur format.
  	 Answer the number of indexable bytes or words in the given object.
  	 For a CompiledMethod, the size of the method header (in bytes) should
  	 be subtracted from the result of this method."
  	| numSlots |
  	<inline: true>
  	<asmLabel: false> 
  	numSlots := self numSlotsOf: objOop.
  	fmt <= self sixtyFourBitIndexableFormat ifTrue:
  		[^numSlots].
  	fmt >= self firstByteFormat ifTrue: "bytes, including CompiledMethod"
  		[^numSlots << self shiftForWord - (fmt bitAnd: 7)].
  	fmt >= self firstShortFormat ifTrue:
  		[^numSlots << (self shiftForWord - 1) - (fmt bitAnd: 3)].
  	"fmt >= self firstLongFormat"
+ 	^numSlots << (self shiftForWord - 2) - (fmt bitAnd: 1)!
- 	^numSlots << (self shiftForWord - 1) - (fmt bitAnd: 1)!

Item was added:
+ ----- Method: SpurMemoryManager>>printHeaderTypeOf: (in category 'debug printing') -----
+ printHeaderTypeOf: objOop
+ 	coInterpreter print: ((self numSlotsOf: objOop) >= self numSlotsMask
+ 							ifTrue: ['8 byte header']
+ 							ifFalse: ['16 byte header'])!

Item was changed:
  ----- Method: StackInterpreter>>isFloatObject: (in category 'internal interpreter access') -----
  isFloatObject: oop
+ 	^(objectMemory isNonImmediate: oop)
+ 	   and: [ClassFloatCompactIndex = (objectMemory compactClassIndexOf: oop)]!
- 	^(objectMemory isNonIntegerObject: oop)
- 	   and: [ClassFloatCompactIndex ~= 0
- 			ifTrue: [(objectMemory compactClassIndexOf: oop) = ClassFloatCompactIndex]
- 			ifFalse: [(objectMemory fetchClassOfNonImm: oop) = objectMemory classFloat]]!

Item was added:
+ ----- Method: StackInterpreterSimulator>>primitiveBeCursor (in category 'debugging traps') -----
+ primitiveBeCursor
+ 	self halt.
+ 	^super primitiveBeCursor!



More information about the Vm-dev mailing list