[Vm-dev] VM Maker: VMMaker-dtl.293.mcz

commits at source.squeak.org commits at source.squeak.org
Sun Dec 30 00:50:32 UTC 2012


David T. Lewis uploaded a new version of VMMaker to project VM Maker:
http://source.squeak.org/VMMaker/VMMaker-dtl.293.mcz

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

Name: VMMaker-dtl.293
Author: dtl
Time: 29 December 2012, 7:48:13.152 pm
UUID: 9849f935-60c7-49f4-9aac-ce84daab399f
Ancestors: VMMaker-dtl.292

VMMaker 4.10.7

Bitshift optimizations by Nicolas Cellier. Use #>> or #<< operator rather than #bitShift: in cases where shift direction is known in order to eliminate runtime check for shift direction.

Discussion thread: http://lists.squeakfoundation.org/pipermail/vm-dev/2012-December/011688.html

Change sets: http://code.google.com/p/cog/issues/detail?id=111

Follow up required: Nicolas' changes for the sound primitives should also be adopted. These are methods in package Sound that are translated from the image into primitives for ADPCMCodecPlugin. Add these to Squeak trunk after the next release (Squeak 4.4).

=============== Diff against VMMaker-dtl.292 ===============

Item was changed:
  ----- Method: DeflatePlugin>>nextZipBits:put: (in category 'encoding') -----
  nextZipBits: nBits put: value
  	"Require:
  		zipCollection, zipCollectionSize, zipPosition,
  		zipBitBuf, zipBitPos.
  	"
  	<inline: true>
  	(value >= 0 and:[(1 << nBits) > value])
  		ifFalse:[^interpreterProxy primitiveFail].
+ 	zipBitBuf := zipBitBuf bitOr: value << zipBitPos.
- 	zipBitBuf := zipBitBuf bitOr: (value bitShift: zipBitPos).
  	zipBitPos := zipBitPos + nBits.
  	[zipBitPos >= 8 and:[zipPosition < zipCollectionSize]] whileTrue:[
  		zipCollection at: zipPosition put: (zipBitBuf bitAnd: 255).
  		zipPosition := zipPosition + 1.
  		zipBitBuf := zipBitBuf >> 8.
  		zipBitPos := zipBitPos - 8].
  !

Item was changed:
  ----- Method: DeflatePlugin>>updateHash: (in category 'deflating') -----
  updateHash: nextValue
  	"Update the running hash value based on the next input byte.
  	Return the new updated hash value."
+ 	^((zipHashValue << DeflateHashShift) bitXor: nextValue) bitAnd: DeflateHashMask.!
- 	^((zipHashValue bitShift: DeflateHashShift) bitXor: nextValue) bitAnd: DeflateHashMask.!

Item was changed:
  ----- Method: FFTPlugin>>transformForward: (in category 'transforming') -----
  transformForward: forward
  	| lev lev1 ip theta realU imagU realT imagT i fftSize2 fftSize4 fftScale ii |
+ 	<var: #realU type:'float '>
+ 	<var: #realT type:'float '>
+ 	<var: #imagU type:'float '>
+ 	<var: #imagT type:'float '>
- 	<var: #realU type: 'float '>
- 	<var: #realT type: 'float '>
- 	<var: #imagU type: 'float '>
- 	<var: #imagT type: 'float '>
  	fftSize2 := fftSize // 2.
  	fftSize4 := fftSize // 4.
  	1 to: nu do:
  		[:level |
+ 		lev := 1 << level.
- 		lev := 1 bitShift: level.
  		lev1 := lev // 2.
  		fftScale := fftSize // lev.
  		1 to: lev1 do:
  			[:j |
  			theta := j-1 * fftScale.   "pi * (j-1) / lev1 mapped onto 0..n/2"
  			theta < fftSize4  "Compute U, the complex multiplier for each level"
  				ifTrue:
  					[realU := sinTable at: sinTableSize - theta - 1.
  					imagU := sinTable at: theta]
  				ifFalse:
  					[realU := 0.0 - (sinTable at: theta - fftSize4).
  					imagU := sinTable at: fftSize2 - theta].
  			forward ifFalse: [imagU := 0.0 - imagU].
  "
  			Here is the inner loop...
  			j to: n by: lev do:
  				[:i |   hand-transformed to whileTrue...
  "
  			i := j.
  			[i <= fftSize] whileTrue:
  				[ip := i + lev1 - 1.
  				ii := i-1.
  				realT := ((realData at: ip) * realU) - ((imagData at: ip) * imagU).
  				imagT := ((realData at: ip) * imagU) + ((imagData at: ip) * realU).
  				realData at: ip put: (realData at: ii) - realT.
  				imagData at: ip put: (imagData at: ii) - imagT.
  				realData at: ii put: (realData at: ii) + realT.
  				imagData at: ii put: (imagData at: ii) + imagT.
  				i := i + lev]]].!

Item was changed:
  ----- Method: InterpreterPrimitives>>primitiveBitShift (in category 'arithmetic integer primitives') -----
  primitiveBitShift 
  	| integerReceiver integerArgument shifted |
  	integerArgument := self popInteger.
  	integerReceiver := self popPos32BitInteger.
  	self successful ifTrue: [
  		integerArgument >= 0 ifTrue: [
  			"Left shift -- must fail if we lose bits beyond 32"
  			self success: integerArgument <= 31.
  			shifted := integerReceiver << integerArgument.
  			self success: (shifted >> integerArgument) = integerReceiver.
  		] ifFalse: [
  			"Right shift -- OK to lose bits"
  			self success: integerArgument >= -31.
+ 			shifted := integerReceiver >> (0 - integerArgument).
- 			shifted := integerReceiver bitShift: integerArgument.
  		].
  	].
  	self successful
  		ifTrue: [self push: (self positive32BitIntegerFor: shifted)]
  		ifFalse: [self unPop: 2]!

Item was changed:
  ----- Method: JPEGReaderPlugin>>getBits: (in category 'stream support') -----
  getBits: requestedBits
  	| value |
  	requestedBits > jsBitCount ifTrue:[
  		self fillBuffer.
  		requestedBits > jsBitCount ifTrue:[^-1]].
- 	value := jsBitBuffer bitShift: (requestedBits - jsBitCount).
- 	jsBitBuffer := jsBitBuffer bitAnd: (1 bitShift: (jsBitCount - requestedBits)) -1.
  	jsBitCount := jsBitCount - requestedBits.
+ 	value := jsBitBuffer >> jsBitCount.
+ 	jsBitBuffer := jsBitBuffer bitAnd: (1 << jsBitCount) -1.
  	^ value!

Item was changed:
  ----- Method: JPEGReaderPlugin>>idctBlockInt:qt: (in category 'decoding') -----
  idctBlockInt: anArray qt: qt
  	| ws anACTerm dcval z2 z3 z1 t2 t3 t0 t1 t10 t13 t11 t12 z4 z5 v |
  	<var: #anArray type: 'int *'>
  	<var: #qt type: 'int *'>
  	<var: #ws declareC: 'int ws[64]'>
  	self cCode:'' inSmalltalk:[ws := CArrayAccessor on: (IntegerArray new: 64)].
  	"Pass 1: process columns from anArray, store into work array"
  	0 to: DCTSize-1 do:[:i |
  		anACTerm := -1.
  		1 to: DCTSize-1 do:[:row|
  			anACTerm = -1 ifTrue:[
  				(anArray at: row * DCTSize + i) = 0 ifFalse:[anACTerm := row]]].
  		anACTerm = -1 ifTrue:[
+ 			dcval := (anArray at: i) * (qt at: 0) << Pass1Bits.
- 			dcval := (anArray at: i) * (qt at: 0) bitShift: Pass1Bits.
  			0 to: DCTSize-1 do: [:j | ws at: (j * DCTSize + i) put: dcval]
  		] ifFalse:[
  			z2 := (anArray at: (DCTSize * 2 + i)) * (qt at: (DCTSize * 2 + i)).
  			z3 := (anArray at: (DCTSize * 6 + i)) * (qt at: (DCTSize * 6 + i)).
  			z1 := (z2 + z3) * FIXn0n541196100.
  			t2 := z1 + (z3 * (0 - FIXn1n847759065)).
  			t3 := z1 + (z2 * FIXn0n765366865).
  			z2 := (anArray at: i) * (qt at: i).
  			z3 := (anArray at: (DCTSize * 4 + i)) * (qt at: (DCTSize * 4 + i)).
+ 			t0 := (z2 + z3) << ConstBits.
+ 			t1 := (z2 - z3) << ConstBits.
- 			t0 := (z2 + z3) bitShift: ConstBits.
- 			t1 := (z2 - z3) bitShift: ConstBits.
  			t10 := t0 + t3.
  			t13 := t0 - t3.
  			t11 := t1 + t2.
  			t12 := t1 - t2.
  			t0 := (anArray at: (DCTSize * 7 + i)) * (qt at: (DCTSize * 7 + i)).
  			t1 := (anArray at: (DCTSize * 5 + i)) * (qt at: (DCTSize * 5 + i)).
  			t2 := (anArray at: (DCTSize * 3 + i)) * (qt at: (DCTSize * 3 + i)).
  			t3 := (anArray at: (DCTSize + i)) * (qt at: (DCTSize + i)).
  			z1 := t0 + t3.
  			z2 := t1 + t2.
  			z3 := t0 + t2.
  			z4 := t1 + t3.
  			z5 := (z3 + z4) * FIXn1n175875602.
  			t0 := t0 * FIXn0n298631336.
  			t1 := t1 * FIXn2n053119869.
  			t2 := t2 * FIXn3n072711026.
  			t3 := t3 * FIXn1n501321110.
  			z1 := z1 * (0 - FIXn0n899976223).
  			z2 := z2 * (0 - FIXn2n562915447).
  			z3 := z3 * (0 - FIXn1n961570560).
  			z4 := z4 * (0 - FIXn0n390180644).
  			z3 := z3 + z5.
  			z4 := z4 + z5.
  			t0 := t0 + z1 + z3.
  			t1 := t1 +z2 +z4.
  			t2 := t2 + z2 + z3.
  			t3 := t3 + z1 + z4.
  			ws at: i put: (t10 + t3) // Pass1Div.
  			ws at: (DCTSize * 7 + i) put: (t10 - t3) // Pass1Div.
  			ws at: (DCTSize * 1 + i) put: (t11 + t2) // Pass1Div.
  			ws at: (DCTSize * 6 + i) put: (t11 - t2) // Pass1Div.
  			ws at: (DCTSize * 2 + i) put: (t12 + t1) // Pass1Div.
  			ws at: (DCTSize * 5 + i) put: (t12 - t1) // Pass1Div.
  			ws at: (DCTSize * 3 + i) put: (t13 + t0) // Pass1Div.
  			ws at: (DCTSize * 4 + i) put: (t13 - t0) // Pass1Div]].
  
  	"Pass 2: process rows from work array, store back into anArray"
  	0 to: DCTSize2-DCTSize by: DCTSize do:[:i |
  		z2 := ws at: i + 2.
  		z3 := ws at: i + 6.
  		z1 := (z2 + z3) * FIXn0n541196100.
  		t2 := z1 + (z3 * (0-FIXn1n847759065)).
  		t3 := z1 + (z2 * FIXn0n765366865).
+ 		t0 := (ws at: i) + (ws at: (i + 4)) << ConstBits.
+ 		t1 := (ws at: i) - (ws at: (i + 4)) << ConstBits.
- 		t0 := (ws at: i) + (ws at: (i + 4)) bitShift: ConstBits.
- 		t1 := (ws at: i) - (ws at: (i + 4)) bitShift: ConstBits.
  		t10 := t0 + t3.
  		t13 := t0 - t3.
  		t11 := t1 + t2.
  		t12 := t1 -t2.
  		t0 := ws at: (i + 7).
  		t1 := ws at: (i + 5).
  		t2 := ws at: (i + 3).
  		t3 := ws at: (i + 1).
  		z1 := t0 + t3.
  		z2 := t1 + t2.
  		z3 := t0 + t2.
  		z4 := t1 + t3.
  		z5 := (z3 + z4) * FIXn1n175875602.
  		t0 := t0 * FIXn0n298631336.
  		t1 := t1 * FIXn2n053119869.
  		t2 := t2 * FIXn3n072711026.
  		t3 := t3 * FIXn1n501321110.
  		z1 := z1 * (0-FIXn0n899976223).
  		z2 := z2 * (0-FIXn2n562915447).
  		z3 := z3 * (0-FIXn1n961570560).
  		z4 := z4 * (0-FIXn0n390180644).
  		z3 := z3 + z5.
  		z4 := z4 + z5.
  		t0 := t0 + z1 + z3.
  		t1 := t1 + z2 + z4.
  		t2 := t2 + z2 + z3.
  		t3 := t3 + z1 + z4.
  		v := (t10 + t3) // Pass2Div + SampleOffset.
  		v := v min: MaxSample. v := v max: 0.
  		anArray at: i put: v.
  		v := (t10 - t3) // Pass2Div + SampleOffset.
  		v := v min: MaxSample. v := v max: 0.
  		anArray at: (i + 7) put: v.
  		v := (t11 + t2) // Pass2Div + SampleOffset. 
  		v := v min: MaxSample. v := v max: 0.
  		anArray at: (i + 1) put: v.
  		v := (t11 - t2) // Pass2Div + SampleOffset.
  		v := v min: MaxSample. v := v max: 0.
  		anArray at: (i + 6) put: v.
  		v :=  (t12 + t1) // Pass2Div + SampleOffset.
  		v := v min: MaxSample. v := v max: 0.
  		anArray at: (i + 2) put: v.
  		v :=  (t12 - t1) // Pass2Div + SampleOffset.
  		v := v min: MaxSample. v := v max: 0.
  		anArray at: (i + 5) put: v.
  		v := (t13 + t0) // Pass2Div + SampleOffset.
  		v := v min: MaxSample. v := v max: 0.
  		anArray at: (i + 3) put: v.
  		v := (t13 - t0) // Pass2Div + SampleOffset.
  		v := v min: MaxSample. v := v max: 0.
  		anArray at: (i + 4) put: v].!

Item was changed:
  ----- Method: JPEGReaderPlugin>>scaleAndSignExtend:inFieldWidth: (in category 'decoding') -----
  scaleAndSignExtend: aNumber inFieldWidth: w
  	<inline: true>
+ 	aNumber < (1 << (w - 1))
+ 		ifTrue: [^aNumber - (1 << w) + 1]
- 	aNumber < (1 bitShift: (w - 1))
- 		ifTrue: [^aNumber - (1 bitShift: w) + 1]
  		ifFalse: [^aNumber]!

Item was changed:
  ----- Method: LargeIntegersPlugin>>anyBitOfBytes:from:to: (in category 'util') -----
  anyBitOfBytes: aBytesOop from: start to: stopArg 
  	"Argument has to be aBytesOop!!"
  	"Tests for any magnitude bits in the interval from start to stopArg."
  	| magnitude rightShift leftShift stop firstByteIx lastByteIx |
  	self
  		debugCode: [self msg: 'anyBitOfBytes: aBytesOop from: start to: stopArg'].
  	start < 1 | (stopArg < 1)
  		ifTrue: [^ interpreterProxy primitiveFail].
  	magnitude := aBytesOop.
  	stop := stopArg
  				min: (self highBitOfBytes: magnitude).
  	start > stop
  		ifTrue: [^ false].
  	firstByteIx := start - 1 // 8 + 1.
  	lastByteIx := stop - 1 // 8 + 1.
+ 	rightShift := (start - 1 \\ 8).
- 	rightShift := 0 - (start - 1 \\ 8).
  	leftShift := 7 - (stop - 1 \\ 8).
  	firstByteIx = lastByteIx
  		ifTrue: [| digit mask | 
+ 			mask := (255 << rightShift) bitAnd: (255 >> leftShift).
- 			mask := (255 bitShift: 0 - rightShift)
- 						bitAnd: (255 bitShift: 0 - leftShift).
  			digit := self digitOfBytes: magnitude at: firstByteIx.
  			^ (digit bitAnd: mask)
  				~= 0].
  	((self digitOfBytes: magnitude at: firstByteIx)
+ 			>> rightShift)
- 			bitShift: rightShift)
  			~= 0
  		ifTrue: [^ true].
  	firstByteIx + 1
  		to: lastByteIx - 1
  		do: [:ix | (self digitOfBytes: magnitude at: ix)
  					~= 0
  				ifTrue: [^ true]].
  	(((self digitOfBytes: magnitude at: lastByteIx)
+ 			<< leftShift)
- 			bitShift: leftShift)
  			bitAnd: 255)
  			~= 0
  		ifTrue: [^ true].
  	^ false!

Item was changed:
  ----- Method: LargeIntegersPlugin>>cDigitOfCSI:at: (in category 'C core util') -----
  cDigitOfCSI: csi at: ix 
  	"Answer the value of an indexable field in the receiver.              
  	LargePositiveInteger uses bytes of base two number, and each is a       
  	      'digit' base 256."
  	"ST indexed!!"
+ 	ix < 1 ifTrue: [interpreterProxy primitiveFail].
- 	ix < 0 ifTrue: [interpreterProxy primitiveFail].
  	ix > 4 ifTrue: [^ 0].
  	csi < 0
  		ifTrue: 
  			[self cCode: ''
  				inSmalltalk: [csi = -1073741824 ifTrue: ["SmallInteger minVal"
  						"Can't negate minVal -- treat specially"
  						^ #(0 0 0 64 ) at: ix]].
+ 			^ (0 - csi) >> (ix - 1 * 8)
- 			^ (0 - csi bitShift: 1 - ix * 8)
  				bitAnd: 255]
+ 		ifFalse: [^ csi >> (ix - 1 * 8)
- 		ifFalse: [^ (csi bitShift: 1 - ix * 8)
  				bitAnd: 255]!

Item was changed:
  ----- Method: StackInterpreter>>stackPageByteSize (in category 'stack pages') -----
  stackPageByteSize
  	"Room for 512 bytes of frames gives around 40 frames a page which is a
  	 good compromise between overflow rate and latency in divorcing a page."
  	<inline: false>
+ 	^1 << (512 + self stackLimitOffset + self stackPageHeadroom - 1) highBit!
- 	^1 bitShift: (512 + self stackLimitOffset + self stackPageHeadroom - 1) highBit!

Item was changed:
  ----- Method: VMMaker class>>versionString (in category 'version testing') -----
  versionString
  
  	"VMMaker versionString"
  
+ 	^'4.10.7'!
- 	^'4.10.6'!



More information about the Vm-dev mailing list