[Vm-dev] VM Maker: VMMaker.oscog-nice.2000.mcz

commits at source.squeak.org commits at source.squeak.org
Mon Nov 21 21:35:38 UTC 2016


Nicolas Cellier uploaded a new version of VMMaker to project VM Maker:
http://source.squeak.org/VMMaker/VMMaker.oscog-nice.2000.mcz

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

Name: VMMaker.oscog-nice.2000
Author: nice
Time: 21 November 2016, 10:33:51.689082 pm
UUID: 7fa7f632-9ec2-4121-a764-e6ca3280a679
Ancestors: VMMaker.oscog-eem.1999

Now that the surface functions take int pointer, we'd better pass int pointer rather than sqInt pointer. Hence declare some BitBlt variable appropriately.

Rather than coercing to unsigned, just declare unsigned in absoluteSquared8Dot24:
Note that this could be simply replaced by an unsigned 64bit multiplication then shift nowadays, if someone is willing to measure time spent.

Do to signed32BitValueOf: what has been done to signed32BitIntegerFor:
only invoke noInlineSigned32BitValueGutsOf: for the case of LargeInteger deciphering.
When the oop is a 31bits SmallInteger, don't bother entering such function - just inline

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

Item was changed:
  ----- Method: BalloonEnginePlugin>>absoluteSquared8Dot24: (in category 'private') -----
  absoluteSquared8Dot24: value
  	"Compute the squared value of a 8.24 number with 0.0 <= value < 1.0,
  	e.g., compute (value * value) bitShift: -24"
  	| word1 word2 |
  	<inline: true>
+ 	<var: 'word1' type: #'unsigned int'>
+ 	<var: 'word2' type: #'unsigned int'>
  	word1 := value bitAnd: 16rFFFF.
  	word2 := (value bitShift: -16) bitAnd: 255.
+ 	^(( (word1 * word1) bitShift: -16) +
- 	^(( (self cCoerce: (word1 * word1) to:'unsigned') bitShift: -16) +
  		((word1 * word2) * 2) +
  			((word2 * word2) bitShift: 16)) bitShift: -8!

Item was changed:
  ----- Method: BitBltSimulation class>>declareCVarsIn: (in category 'translation') -----
  declareCVarsIn: aCCodeGenerator
  
  	"add option of  fast path BitBLT code header"
  	aCCodeGenerator
  		addHeaderFile:'#ifdef ENABLE_FAST_BLT
  #include "BitBltDispatch.h"
  #else
  // to handle the unavoidable decl in the spec of copyBitsFallback();
  #define operation_t void
  #endif'.
  		
  	aCCodeGenerator var: 'opTable'
  		declareC: 'void *opTable[' , OpTableSize printString , ']'.
  	aCCodeGenerator var: 'maskTable'
  		declareC:'int maskTable[33] = {
  0, 1, 3, 0, 15, 31, 0, 0, 255, 0, 0, 0, 0, 0, 0, 0, 65535,
  0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, -1
  }'.
  	aCCodeGenerator var: 'ditherMatrix4x4'
  		declareC:'const int ditherMatrix4x4[16] = {
  0,	8,	2,	10,
  12,	4,	14,	6,
  3,	11,	1,	9,
  15,	7,	13,	5
  }'.
  	aCCodeGenerator var: 'ditherThresholds16'
  		declareC:'const int ditherThresholds16[8] = { 0, 2, 4, 6, 8, 12, 14, 16 }'.
  	aCCodeGenerator var: 'ditherValues16'
  		declareC:'const int ditherValues16[32] = {
  0, 0, 1, 2, 3, 4, 5, 6, 7, 8, 9, 10, 11, 12, 13, 14,
  15, 16, 17, 18, 19, 20, 21, 22, 23, 24, 25, 26, 27, 28, 29, 30
  }'.
  
  	aCCodeGenerator var: 'warpBitShiftTable'
  		declareC:'int warpBitShiftTable[32]'.
  
  	aCCodeGenerator var:'cmShiftTable' 
  		type:'int *'.
  	aCCodeGenerator var:'cmMaskTable' 
  		type:'unsigned int *'.
  	aCCodeGenerator var:'cmLookupTable' 
  		type:'unsigned int *'.
  
  	aCCodeGenerator var: 'dither8Lookup'
  		declareC:' unsigned char dither8Lookup[4096]'.
  
  	aCCodeGenerator var:'ungammaLookupTable' 
  		type: 'unsigned char *'.
  	aCCodeGenerator var:'gammaLookupTable' 
  		type: 'unsigned char *'.
  
  	aCCodeGenerator var: 'querySurfaceFn' type: 'void *'.
  	aCCodeGenerator var: 'lockSurfaceFn' type: 'void *'.
+ 	aCCodeGenerator var: 'unlockSurfaceFn' type: 'void *'.
+ 	
+ 	#(sourcePitch sourceWidth sourceHeight sourceDepth sourceMSB sx sy
+ 		destPitch destWidth destHeight destDepth destMSB dx dy bbW bbH)
+ 		do: [:ivar | aCCodeGenerator var: ivar type: 'int'.]!
- 	aCCodeGenerator var: 'unlockSurfaceFn' type: 'void *'!

Item was added:
+ ----- Method: InterpreterPrimitives>>noInlineSigned32BitValueGutsOf: (in category 'primitive support') -----
+ noInlineSigned32BitValueGutsOf: oop
+ 	"Convert the given object into an integer value.
+ 	The object may be a four-byte LargeInteger."
+ 	| value negative ok magnitude |
+ 	<notOption: #Spur64BitMemoryManager>
+ 	<inline: false>
+ 	<returnTypeC: #int>
+ 	<var: #value type: #int>
+ 	<var: #magnitude type: #'unsigned int'>
+ 	self deny: objectMemory hasSixtyFourBitImmediates.
+ 	self deny: (objectMemory isIntegerValue: oop).
+ 
+ 	(objectMemory isNonIntegerImmediate: oop) ifTrue:
+ 		[self primitiveFail.
+ 		 ^0].
+ 
+ 	ok := objectMemory
+ 			isClassOfNonImm: oop
+ 			equalTo: (objectMemory splObj: ClassLargePositiveInteger)
+ 			compactClassIndex: ClassLargePositiveIntegerCompactIndex.
+ 	ok
+ 		ifTrue: [negative := false]
+ 		ifFalse:
+ 			[negative := true.
+ 			 ok := objectMemory isClassOfNonImm: oop
+ 							equalTo: (objectMemory splObj: ClassLargeNegativeInteger)
+ 							compactClassIndex: ClassLargeNegativeIntegerCompactIndex.
+ 			 ok ifFalse:
+ 				[self primitiveFail.
+ 				 ^0]].
+ 	(objectMemory numBytesOfBytes: oop) > 4 ifTrue:
+ 		[^self primitiveFail].
+ 
+ 	magnitude := self cCoerceSimple: (objectMemory byteSwapped32IfBigEndian: (objectMemory fetchLong32: 0 ofObject: oop)) to: #'unsigned int'.
+ 
+ 	(negative
+ 		ifTrue: [magnitude > 16r80000000]
+ 		ifFalse: [magnitude >= 16r80000000])
+ 			ifTrue:
+ 				[self primitiveFail.
+ 				^0].
+ 	negative
+ 		ifTrue: [value := 0 - magnitude]
+ 		ifFalse: [value := magnitude].
+ 	^value!

Item was removed:
- ----- Method: InterpreterPrimitives>>noInlineSigned32BitValueOf: (in category 'primitive support') -----
- noInlineSigned32BitValueOf: oop
- 	"Convert the given object into an integer value.
- 	The object may be either a SmallInteger or a four-byte LargeInteger."
- 	| value negative ok magnitude |
- 	<notOption: #Spur64BitMemoryManager>
- 	<inline: false>
- 	<returnTypeC: #int>
- 	<var: #value type: #int>
- 	<var: #magnitude type: #'unsigned int'>
- 	self deny: objectMemory hasSixtyFourBitImmediates.
- 	(objectMemory isIntegerObject: oop) ifTrue:
- 		[^objectMemory integerValueOf: oop].
- 
- 	(objectMemory isNonIntegerImmediate: oop) ifTrue:
- 		[self primitiveFail.
- 		 ^0].
- 
- 	ok := objectMemory
- 			isClassOfNonImm: oop
- 			equalTo: (objectMemory splObj: ClassLargePositiveInteger)
- 			compactClassIndex: ClassLargePositiveIntegerCompactIndex.
- 	ok
- 		ifTrue: [negative := false]
- 		ifFalse:
- 			[negative := true.
- 			 ok := objectMemory isClassOfNonImm: oop
- 							equalTo: (objectMemory splObj: ClassLargeNegativeInteger)
- 							compactClassIndex: ClassLargeNegativeIntegerCompactIndex.
- 			 ok ifFalse:
- 				[self primitiveFail.
- 				 ^0]].
- 	(objectMemory numBytesOfBytes: oop) > 4 ifTrue:
- 		[^self primitiveFail].
- 
- 	magnitude := self cCoerceSimple: (objectMemory byteSwapped32IfBigEndian: (objectMemory fetchLong32: 0 ofObject: oop)) to: #'unsigned int'.
- 
- 	(negative
- 		ifTrue: [magnitude > 16r80000000]
- 		ifFalse: [magnitude >= 16r80000000])
- 			ifTrue:
- 				[self primitiveFail.
- 				^0].
- 	negative
- 		ifTrue: [value := 0 - magnitude]
- 		ifFalse: [value := magnitude].
- 	^value!

Item was changed:
  ----- Method: InterpreterPrimitives>>signed32BitValueOf: (in category 'primitive support') -----
  signed32BitValueOf: oop
  	"Convert the given object into an integer value.
  	The object may be either a SmallInteger or a four-byte LargeInteger."
  	<returnTypeC: #int>
  	
  	objectMemory hasSixtyFourBitImmediates
  		ifTrue:
  			[(objectMemory isIntegerObject: oop) ifTrue:
  				[| value64 |
  				 value64 := objectMemory integerValueOf: oop.
  				 (self cCode: [(self cCoerceSimple: value64 to: #int) ~= value64]
  						inSmalltalk: [value64 >> 31 ~= 0 and: [value64 >> 31 ~= -1]]) ifTrue:
  					[self primitiveFail. value64 := 0].
  				 ^value64].
  			self primitiveFail.
  		 	^0]
  		ifFalse:
+ 			[(objectMemory isIntegerObject: oop) ifTrue:
+ 				[^objectMemory integerValueOf: oop].
+ 			^self noInlineSigned32BitValueGutsOf: oop]!
- 			[^self noInlineSigned32BitValueOf: oop]!



More information about the Vm-dev mailing list