[pypy-commit] lang-smalltalk default: add BitBlt, GrafPort, Form, and Canvas classes that work in pure smalltalk

timfel noreply at buildbot.pypy.org
Sun Jan 19 12:17:39 CET 2014


Author: Tim Felgentreff <timfelgentreff at gmail.com>
Branch: 
Changeset: r593:83b3e917889b
Date: 2014-01-19 12:13 +0100
http://bitbucket.org/pypy/lang-smalltalk/changeset/83b3e917889b/

Log:	add BitBlt, GrafPort, Form, and Canvas classes that work in pure
	smalltalk

diff too long, truncating to 2000 out of 5739 lines

diff --git a/images/BitBltPureSmalltalk.st b/images/BitBltPureSmalltalk.st
new file mode 100644
--- /dev/null
+++ b/images/BitBltPureSmalltalk.st
@@ -0,0 +1,1 @@
+Object subclass: #BitBltPure
	instanceVariableNames: 'destForm sourceForm halftoneForm combinationRule destX destY width height sourceX sourceY clipX clipY clipWidth clipHeight colorMap sourceWidth sourceHeight sourceDepth sourcePitch sourceBits sourcePPW sourceMSB destWidth destHeight destDepth destPitch destBits destPPW destMSB bitCount skew mask1 mask2 preload nWords destMask hDir vDir sourceIndex sourceDelta destIndex destDelta sx sy dx dy bbW bbH halftoneHeight noSource noHalftone halftoneBase sourceAlpha srcBitShift dstBitShift bitBltOop affectedL affectedR affectedT affectedB opTable maskTable ditherMatrix4x4 ditherThresholds16 ditherValues16 hasSurfaceLock warpSrcShift warpSrcMask warpAlignShift warpAlignMask warpBitShiftTable querySurfaceFn lockSurfaceFn unlockSurfaceFn isWarping cmFlags cmMask cmShiftTable cmMaskTable cmLookupTable cmBitsPerColor dither8Lookup componentAlphaModeColor componentAlphaModeAlpha ungammaLookupTable gammaLookupTable'
	classVariableNames: 'AllOnes AlphaIndex BBClipHeightIndex BBClipWidthIndex BBClipXIndex BBClipYIndex BBColorMapIndex BBDestFormIndex BBDestXIndex BBDestYIndex BBHalftoneFormIndex BBHeightIndex BBLastIndex BBRuleIndex BBSourceFormIndex BBSourceXIndex BBSourceYIndex BBWarpBase BBWidthIndex BBXTableIndex BinaryPoint BlueIndex ColorMapFixedPart ColorMapIndexedPart ColorMapNewStyle ColorMapPresent CrossedX Dither8Lookup DitherMatrix4x4 DitherThresholds16 DitherValues16 EndOfRun FixedPt1 FormBitsIndex FormDepthIndex FormHeightIndex FormWidthIndex GreenIndex JitBltHookSize MaskTable OpTable OpTableSize RedIndex'
	poolDictionaries: ''
	category: 'BitBltPureSmalltalk'!
!BitBltPure commentStamp: '<historical>' prior: 0!
This class implements BitBlt, much as specified in the Blue Book spec.

Performance has been enhanced through the use of pointer variables such as sourceIndex and destIndex, and by separating several special cases of the inner loop.

Operation has been extended to color, with support for 1, 2, 4, 8, 16, and 32-bit pixel sizes.  Conversion between different pixel sizes is facilitated by accepting an optional color map.

In addition to the original 16 combination rules, this BitBlt supports
	16	fail (for old paint mode)
	17	fail (for old mask mode)
	18	sourceWord + destinationWord
	19	sourceWord - destinationWord
	20	rgbAdd: sourceWord with: destinationWord
	21	rgbSub: sourceWord with: destinationWord
	22	OLDrgbDiff: sourceWord with: destinationWord
	23	OLDtallyIntoMap: destinationWord -- old vers doesn't clip to bit boundary
	24	alphaBlend: sourceWord with: destinationWord
	25	pixPaint: sourceWord with: destinationWord
	26	pixMask: sourceWord with: destinationWord
	27	rgbMax: sourceWord with: destinationWord
	28	rgbMin: sourceWord with: destinationWord
	29	rgbMin: sourceWord bitInvert32 with: destinationWord
	30	alphaBlendConst: sourceWord with: destinationWord -- alpha passed as an arg
	31	alphaPaintConst: sourceWord with: destinationWord -- alpha passed as an arg
	32	rgbDiff: sourceWord with: destinationWord
	33	tallyIntoMap: destinationWord
	34	alphaBlendScaled: sourceWord with: destinationWord
	35 alphaBlendScaled: sourceWord with:	"unused here - only used by FXBlt"
	36 alphaBlendScaled: sourceWord with:	"unused here - only used by FXBlt"
	37 rgbMul: sourceWord with: destinationWord
	38 pixSwap: sourceWord with: destinationWord
	39 pixClear: sourceWord with: destinationWord
	40 fixAlpha: sourceWord with: destinationWord
	41 rgbComponentAlpha: sourceWord with: destinationWord

This implementation has also been fitted with an experimental "warp drive" that allows abritrary scaling and rotation (and even limited affine deformations) with all BitBlt storage modes supported.

To add a new rule to BitBlt...
	1.  add the new rule method or methods in the category 'combination rules' of BBSim
	2.  describe it in the class comment  of BBSim and in the class comment for BitBlt
	3.  add refs to initializeRuleTable in proper positions
	4.  add refs to initBBOpTable, following the pattern
!


!BitBltPure methodsFor: 'combination rules' stamp: 'tfel 1/17/2014 19:01'!
OLDrgbDiff: sourceWord with: destinationWord
	"Subract the pixels in the source and destination, color by color,
	and return the sum of the absolute value of all the differences.
	For non-rgb, XOR the two and return the number of differing pixels.
	Note that the region is not clipped to bit boundaries, but only to the
	nearest (enclosing) word.  This is because copyLoop does not do
	pre-merge masking.  For accurate results, you must subtract the
	values obtained from the left and right fringes."
	| diff pixMask |
	destDepth < 16 ifTrue:
		["Just xor and count differing bits if not RGB"
		diff := sourceWord bitXor: destinationWord.
		pixMask := maskTable at: destDepth.
		[diff = 0] whileFalse:
			[(diff bitAnd: pixMask) ~= 0 ifTrue: [bitCount := bitCount + 1].
			diff := diff >> destDepth].
		^ destinationWord "for no effect"].
 	destDepth = 16
		ifTrue:
		[diff := (self partitionedSub: sourceWord from: destinationWord
						nBits: 5 nPartitions: 3).
		bitCount := bitCount + (diff bitAnd: 16r1F)
							+ (diff>>5 bitAnd: 16r1F)
							+ (diff>>10 bitAnd: 16r1F).
		diff := (self partitionedSub: sourceWord>>16 from: destinationWord>>16
						nBits: 5 nPartitions: 3).
		bitCount := bitCount + (diff bitAnd: 16r1F)
							+ (diff>>5 bitAnd: 16r1F)
							+ (diff>>10 bitAnd: 16r1F)]
		ifFalse:
		[diff := (self partitionedSub: sourceWord from: destinationWord
						nBits: 8 nPartitions: 3).
		bitCount := bitCount + (diff bitAnd: 16rFF)
							+ (diff>>8 bitAnd: 16rFF)
							+ (diff>>16 bitAnd: 16rFF)].
	^ destinationWord  "For no effect on dest"! !

!BitBltPure methodsFor: 'combination rules' stamp: 'tfel 1/17/2014 19:01'!
OLDtallyIntoMap: sourceWord with: destinationWord
	"Tally pixels into the color map.  Note that the source should be 
	specified = destination, in order for the proper color map checks 
	to be performed at setup.
	Note that the region is not clipped to bit boundaries, but only to the
	nearest (enclosing) word.  This is because copyLoop does not do
	pre-merge masking.  For accurate results, you must subtract the
	values obtained from the left and right fringes."
	| mapIndex pixMask shiftWord |
	(cmFlags bitAnd: (ColorMapPresent bitOr: ColorMapIndexedPart)) =
		(ColorMapPresent bitOr: ColorMapIndexedPart)
			ifFalse: [^ destinationWord "no op"].
	destDepth < 16 ifTrue:
		["loop through all packed pixels."
		pixMask := (maskTable at: destDepth) bitAnd: cmMask.
		shiftWord := destinationWord.
		1 to: destPPW do:
			[:i |
			mapIndex := shiftWord bitAnd: pixMask.
			self tallyMapAt: mapIndex put: (self tallyMapAt: mapIndex) + 1.
			shiftWord := shiftWord >> destDepth].
		^ destinationWord].
	destDepth = 16 ifTrue:
		["Two pixels  Tally the right half..."
		mapIndex := self rgbMap: (destinationWord bitAnd: 16rFFFF) from: 5 to: cmBitsPerColor.
		self tallyMapAt: mapIndex put: (self tallyMapAt: mapIndex) + 1.
		"... and then left half"
		mapIndex := self rgbMap: destinationWord>>16 from: 5 to: cmBitsPerColor.
		self tallyMapAt: mapIndex put: (self tallyMapAt: mapIndex) + 1]
	ifFalse:
		["Just one pixel."
		mapIndex := self rgbMap: destinationWord from: 8 to: cmBitsPerColor.
		self tallyMapAt: mapIndex put: (self tallyMapAt: mapIndex) + 1].
	^ destinationWord  "For no effect on dest"! !

!BitBltPure methodsFor: 'combination rules' stamp: 'tfel 1/17/2014 19:01'!
addWord: sourceWord with: destinationWord
	^sourceWord + destinationWord! !

!BitBltPure methodsFor: 'combination rules' stamp: 'tfel 1/17/2014 19:01'!
alphaBlend: sourceWord with: destinationWord
	"Blend sourceWord with destinationWord, assuming both are 32-bit pixels.
	The source is assumed to have 255*alpha in the high 8 bits of each pixel,
	while the high 8 bits of the destinationWord will be ignored.
	The blend produced is alpha*source + (1-alpha)*dest, with
	the computation being performed independently on each color
	component.  The high byte of the result will be 0."
	| alpha unAlpha colorMask result blend shift |
	alpha := sourceWord >> 24.  "High 8 bits of source pixel"
	alpha = 0 ifTrue: [ ^ destinationWord ].
	alpha = 255 ifTrue: [ ^ sourceWord ].
	unAlpha := 255 - alpha.
	colorMask := 16rFF.
	result := 0.

	"red"
	shift := 0.
	blend := ((sourceWord >> shift bitAnd: colorMask) * alpha) +
				((destinationWord>>shift bitAnd: colorMask) * unAlpha)
			 	+ 254 // 255 bitAnd: colorMask.
	result := result bitOr: blend << shift.
	"green"
	shift := 8.
	blend := ((sourceWord >> shift bitAnd: colorMask) * alpha) +
				((destinationWord>>shift bitAnd: colorMask) * unAlpha)
			 	+ 254 // 255 bitAnd: colorMask.
	result := result bitOr: blend << shift.
	"blue"
	shift := 16.
	blend := ((sourceWord >> shift bitAnd: colorMask) * alpha) +
				((destinationWord>>shift bitAnd: colorMask) * unAlpha)
			 	+ 254 // 255 bitAnd: colorMask.
	result := result bitOr: blend << shift.
	"alpha (pre-multiplied)"
	shift := 24.
	blend := (alpha * 255) +
				((destinationWord>>shift bitAnd: colorMask) * unAlpha)
			 	+ 254 // 255 bitAnd: colorMask.
	result := result bitOr: blend << shift.
	^ result
! !

!BitBltPure methodsFor: 'combination rules' stamp: 'tfel 1/17/2014 19:01'!
alphaBlendConst: sourceWord with: destinationWord

	^ self alphaBlendConst: sourceWord with: destinationWord paintMode: false! !

!BitBltPure methodsFor: 'combination rules' stamp: 'tfel 1/17/2014 19:01'!
alphaBlendConst: sourceWord with: destinationWord paintMode: paintMode
	"Blend sourceWord with destinationWord using a constant alpha.
	Alpha is encoded as 0 meaning 0.0, and 255 meaning 1.0.
	The blend produced is alpha*source + (1.0-alpha)*dest, with the
	computation being performed independently on each color component.
	This function could eventually blend into any depth destination,
	using the same color averaging and mapping as warpBlt.
	paintMode = true means do nothing if the source pixel value is zero."

	"This first implementation works with dest depths of 16 and 32 bits only.
	Normal color mapping will allow sources of lower depths in this case,
	and results can be mapped directly by truncation, so no extra color maps are needed.
	To allow storing into any depth will require subsequent addition of two other
	colormaps, as is the case with WarpBlt."

	| pixMask destShifted sourceShifted destPixVal rgbMask sourcePixVal unAlpha result pixBlend shift blend maskShifted bitsPerColor |
	destDepth < 16 ifTrue: [^ destinationWord "no-op"].
	unAlpha := 255 - sourceAlpha.
	pixMask := maskTable at: destDepth.
	destDepth = 16 
		ifTrue: [bitsPerColor := 5]
		ifFalse:[bitsPerColor := 8].
	rgbMask := (1<<bitsPerColor) - 1.
	maskShifted := destMask.
	destShifted := destinationWord.
	sourceShifted := sourceWord.
	result := destinationWord.
	destPPW = 1 ifTrue:["32bpp blends include alpha"
		paintMode & (sourceWord = 0)  "painting a transparent pixel" ifFalse:[
			result := 0.
			1 to: 4 do:[:i|
				shift := (i-1)*8.
				blend := (((sourceWord>>shift bitAnd: rgbMask) * sourceAlpha)
							+ ((destinationWord>>shift bitAnd: rgbMask) * unAlpha))
					 	+ 254 // 255 bitAnd: rgbMask.
				result := result bitOr: blend<<shift].
		].
	] ifFalse:[
		1 to: destPPW do:[:j |
			sourcePixVal := sourceShifted bitAnd: pixMask.
			((maskShifted bitAnd: pixMask) = 0  "no effect if outside of dest rectangle"
				or: [paintMode & (sourcePixVal = 0)  "or painting a transparent pixel"])
			ifFalse:
				[destPixVal := destShifted bitAnd: pixMask.
				pixBlend := 0.
				1 to: 3 do:
					[:i | shift := (i-1)*bitsPerColor.
					blend := (((sourcePixVal>>shift bitAnd: rgbMask) * sourceAlpha)
								+ ((destPixVal>>shift bitAnd: rgbMask) * unAlpha))
						 	+ 254 // 255 bitAnd: rgbMask.
					pixBlend := pixBlend bitOr: blend<<shift].
				destDepth = 16
					ifTrue: [result := (result bitAnd: (pixMask << (j-1*16)) bitInvert32)
										bitOr: pixBlend << (j-1*16)]
					ifFalse: [result := pixBlend]].
			maskShifted := maskShifted >> destDepth.
			sourceShifted := sourceShifted >> destDepth.
			destShifted := destShifted >> destDepth].
	].
	^ result
! !

!BitBltPure methodsFor: 'combination rules' stamp: 'tfel 1/17/2014 19:02'!
alphaBlendScaled: sourceWord with: destinationWord
	"Blend sourceWord with destinationWord using the alpha value from sourceWord.
	Alpha is encoded as 0 meaning 0.0, and 255 meaning 1.0.
	In contrast to alphaBlend:with: the color produced is

		srcColor + (1-srcAlpha) * dstColor

	e.g., it is assumed that the source color is already scaled."
	| unAlpha dstMask srcMask b g r a |
	unAlpha := 255 - (sourceWord >> 24).  "High 8 bits of source pixel"
	dstMask := destinationWord.
	srcMask := sourceWord.
	b := (dstMask bitAnd: 255) * unAlpha >> 8 + (srcMask bitAnd: 255).
	b > 255 ifTrue:[b := 255].
	dstMask := dstMask >> 8.
	srcMask := srcMask >> 8.
	g := (dstMask bitAnd: 255) * unAlpha >> 8 + (srcMask bitAnd: 255).
	g > 255 ifTrue:[g := 255].
	dstMask := dstMask >> 8.
	srcMask := srcMask >> 8.
	r := (dstMask bitAnd: 255) * unAlpha >> 8 + (srcMask bitAnd: 255).
	r > 255 ifTrue:[r := 255].
	dstMask := dstMask >> 8.
	srcMask := srcMask >> 8.
	a := (dstMask bitAnd: 255) * unAlpha >> 8 + (srcMask bitAnd: 255).
	a > 255 ifTrue:[a := 255].
	^(((((a << 8) + r) << 8) + g) << 8) + b! !

!BitBltPure methodsFor: 'combination rules' stamp: 'tfel 1/17/2014 19:01'!
alphaPaintConst: sourceWord with: destinationWord

	sourceWord = 0 ifTrue: [^ destinationWord  "opt for all-transparent source"].
	^ self alphaBlendConst: sourceWord with: destinationWord paintMode: true! !

!BitBltPure methodsFor: 'combination rules' stamp: 'tfel 1/17/2014 19:01'!
bitAnd: sourceWord with: destinationWord
	^sourceWord bitAnd: destinationWord! !

!BitBltPure methodsFor: 'combination rules' stamp: 'tfel 1/17/2014 19:01'!
bitAndInvert: sourceWord with: destinationWord
	^sourceWord bitAnd: destinationWord bitInvert32! !

!BitBltPure methodsFor: 'combination rules' stamp: 'tfel 1/17/2014 19:01'!
bitInvertAnd: sourceWord with: destinationWord
	^sourceWord bitInvert32 bitAnd: destinationWord! !

!BitBltPure methodsFor: 'combination rules' stamp: 'tfel 1/17/2014 19:01'!
bitInvertAndInvert: sourceWord with: destinationWord
	^sourceWord bitInvert32 bitAnd: destinationWord bitInvert32! !

!BitBltPure methodsFor: 'combination rules' stamp: 'tfel 1/17/2014 19:01'!
bitInvertDestination: sourceWord with: destinationWord
	^destinationWord bitInvert32! !

!BitBltPure methodsFor: 'combination rules' stamp: 'tfel 1/17/2014 19:01'!
bitInvertOr: sourceWord with: destinationWord
	^sourceWord bitInvert32 bitOr: destinationWord! !

!BitBltPure methodsFor: 'combination rules' stamp: 'tfel 1/17/2014 19:01'!
bitInvertOrInvert: sourceWord with: destinationWord
	^sourceWord bitInvert32 bitOr: destinationWord bitInvert32! !

!BitBltPure methodsFor: 'combination rules' stamp: 'tfel 1/17/2014 19:01'!
bitInvertSource: sourceWord with: destinationWord
	^sourceWord bitInvert32! !

!BitBltPure methodsFor: 'combination rules' stamp: 'tfel 1/17/2014 19:01'!
bitInvertXor: sourceWord with: destinationWord
	^sourceWord bitInvert32 bitXor: destinationWord! !

!BitBltPure methodsFor: 'combination rules' stamp: 'tfel 1/17/2014 19:01'!
bitOr: sourceWord with: destinationWord
	^sourceWord bitOr: destinationWord! !

!BitBltPure methodsFor: 'combination rules' stamp: 'tfel 1/17/2014 19:01'!
bitOrInvert: sourceWord with: destinationWord
	^sourceWord bitOr: destinationWord bitInvert32! !

!BitBltPure methodsFor: 'combination rules' stamp: 'tfel 1/17/2014 19:01'!
bitXor: sourceWord with: destinationWord
	^sourceWord bitXor: destinationWord! !

!BitBltPure methodsFor: 'combination rules' stamp: 'tfel 1/17/2014 19:01'!
clearWord: source with: destination
	^ 0! !

!BitBltPure methodsFor: 'combination rules' stamp: 'tfel 1/17/2014 19:01'!
destinationWord: sourceWord with: destinationWord
	^destinationWord! !

!BitBltPure methodsFor: 'combination rules' stamp: 'tfel 1/17/2014 19:01'!
fixAlpha: sourceWord with: destinationWord
	"For any non-zero pixel value in destinationWord with zero alpha channel take the alpha from sourceWord and fill it in. Intended for fixing alpha channels left at zero during 16->32 bpp conversions."
	destDepth = 32 ifFalse:[^destinationWord]. "no-op for non 32bpp"
	destinationWord = 0 ifTrue:[^0].
	(destinationWord bitAnd: 16rFF000000) = 0 ifFalse:[^destinationWord].
	^destinationWord bitOr: (sourceWord bitAnd: 16rFF000000)
! !

!BitBltPure methodsFor: 'combination rules' stamp: 'tfel 1/17/2014 19:02'!
merge: sourceWord with: destinationWord
	"Sender warpLoop is too big to include this in-line"
	^ self mergeFn: sourceWord with: destinationWord! !

!BitBltPure methodsFor: 'combination rules' stamp: 'tfel 1/17/2014 20:04'!
mergeFn: arg1 with: arg2
	^ self perform: (OpTable at: combinationRule+1) with: arg1 with: arg2! !

!BitBltPure methodsFor: 'combination rules' stamp: 'tfel 1/17/2014 19:01'!
partitionedAND: word1 to: word2 nBits: nBits nPartitions: nParts
	"AND word1 to word2 as nParts partitions of nBits each.
	Any field of word1 not all-ones is treated as all-zeroes.
	Used for erasing, eg, brush shapes prior to ORing in a color"
	| mask result |
	mask := maskTable at: nBits.  "partition mask starts at the right"
	result := 0.
	1 to: nParts do:
		[:i |
		(word1 bitAnd: mask) = mask
			ifTrue: [result := result bitOr: (word2 bitAnd: mask)].
		mask := mask << nBits  "slide left to next partition"].
	^ result
! !

!BitBltPure methodsFor: 'combination rules' stamp: 'tfel 1/17/2014 19:03'!
partitionedAdd: word1 to: word2 nBits: nBits nPartitions: nParts
	"Add word1 to word2 as nParts partitions of nBits each.
	This is useful for packed pixels, or packed colors"
	| mask sum result maskedWord1 |
	"In C, most arithmetic operations answer the same bit pattern regardless of the operands being signed or unsigned ints
	(this is due to the way 2's complement numbers work). However, comparisions might fail. Add the proper declaration of
	words as unsigned int in those cases where comparisions are done (jmv)"
	mask := maskTable at: nBits.  "partition mask starts at the right"
	result := 0.
	1 to: nParts do:
		[:i |
		maskedWord1 := word1 bitAnd: mask.
		sum := maskedWord1 + (word2 bitAnd: mask).
		(sum <= mask "result must not carry out of partition"
				and: [ sum >= maskedWord1 ])	"This is needed because in C, integer arithmetic overflows silently!! (jmv)"
			ifTrue: [result := result bitOr: sum]
			ifFalse: [result := result bitOr: mask].
		mask := mask << nBits  "slide left to next partition"].
	^ result
! !

!BitBltPure methodsFor: 'combination rules' stamp: 'tfel 1/17/2014 19:03'!
partitionedMax: word1 with: word2 nBits: nBits nPartitions: nParts
	"Max word1 to word2 as nParts partitions of nBits each"
	| mask result |
	"In C, most arithmetic operations answer the same bit pattern regardless of the operands being signed or unsigned ints
	(this is due to the way 2's complement numbers work). However, comparisions might fail. Add the proper declaration of
	words as unsigned int in those cases where comparisions are done (jmv)"
	mask := maskTable at: nBits.  "partition mask starts at the right"
	result := 0.
	1 to: nParts do:
		[:i |
		result := result bitOr: ((word2 bitAnd: mask) max: (word1 bitAnd: mask)).
		mask := mask << nBits  "slide left to next partition"].
	^ result
! !

!BitBltPure methodsFor: 'combination rules' stamp: 'tfel 1/17/2014 19:03'!
partitionedMin: word1 with: word2 nBits: nBits nPartitions: nParts
	"Min word1 to word2 as nParts partitions of nBits each"
	| mask result |
	"In C, most arithmetic operations answer the same bit pattern regardless of the operands being signed or unsigned ints
	(this is due to the way 2's complement numbers work). However, comparisions might fail. Add the proper declaration of
	words as unsigned int in those cases where comparisions are done (jmv)"
	mask := maskTable at: nBits.  "partition mask starts at the right"
	result := 0.
	1 to: nParts do:
		[:i |
		result := result bitOr: ((word2 bitAnd: mask) min: (word1 bitAnd: mask)).
		mask := mask << nBits  "slide left to next partition"].
	^ result
! !

!BitBltPure methodsFor: 'combination rules' stamp: 'tfel 1/17/2014 19:01'!
partitionedMul: word1 with: word2 nBits: nBits nPartitions: nParts
	"Multiply word1 with word2 as nParts partitions of nBits each.
	This is useful for packed pixels, or packed colors.
	Bug in loop version when non-white background"

	| sMask product result dMask |
	"In C, integer multiplication might answer a wrong value if the unsigned values are declared as signed.
	This problem does not affect this method, because the most significant bit (i.e. the sign bit) will
	always be zero (jmv)"
	sMask := maskTable at: nBits.  "partition mask starts at the right"
	dMask :=  sMask << nBits.
	result := (((word1 bitAnd: sMask)+1) * ((word2 bitAnd: sMask)+1) - 1 
				bitAnd: dMask) >> nBits.	"optimized first step"
	nParts = 1
		ifTrue: [ ^result ].
	product := (((word1>>nBits bitAnd: sMask)+1) * ((word2>>nBits bitAnd: sMask)+1) - 1 bitAnd: dMask).
	result := result bitOr: product.
	nParts = 2
		ifTrue: [ ^result ].
	product := (((word1>>(2*nBits) bitAnd: sMask)+1) * ((word2>>(2*nBits) bitAnd: sMask)+1) - 1 bitAnd: dMask).
	result := result bitOr: product << nBits.
	nParts = 3
		ifTrue: [ ^result ].
	product := (((word1>>(3*nBits) bitAnd: sMask)+1) * ((word2>>(3*nBits) bitAnd: sMask)+1) - 1 bitAnd: dMask).
	result := result bitOr: product << (2*nBits).
	^ result

"	| sMask product result dMask |
	sMask := maskTable at: nBits.  'partition mask starts at the right'
	dMask :=  sMask << nBits.
	result := (((word1 bitAnd: sMask)+1) * ((word2 bitAnd: sMask)+1) - 1 
				bitAnd: dMask) >> nBits.	'optimized first step'
	nBits to: nBits * (nParts-1) by: nBits do: [:ofs |
		product := (((word1>>ofs bitAnd: sMask)+1) * ((word2>>ofs bitAnd: sMask)+1) - 1 bitAnd: dMask).
		result := result bitOr: (product bitAnd: dMask) << (ofs-nBits)].
	^ result"! !

!BitBltPure methodsFor: 'combination rules' stamp: 'tfel 1/17/2014 19:01'!
partitionedRgbComponentAlpha: sourceWord dest: destWord nBits: nBits nPartitions: nParts
	| mask result p1 p2 v |
	mask := maskTable at: nBits.  "partition mask starts at the right"
	result := 0.
	1 to: nParts do:
		[:i |
		p1 := (sourceWord bitAnd: mask) >> ((i - 1)*nBits).
		p2 := (destWord bitAnd: mask) >> ((i - 1)*nBits).
		nBits = 32
			ifFalse:[
				nBits = 16
					ifTrue:[
						p1 := (self rgbMap16To32: p1) bitOr: 16rFF000000.
						p2 := (self rgbMap16To32: p2) bitOr: 16rFF000000]
					ifFalse:[
						p1 := (self rgbMap: p1 from: nBits to: 32) bitOr: 16rFF000000.
						p2 := (self rgbMap: p2 from: nBits to: 32) bitOr: 16rFF000000.]].
		v := self rgbComponentAlpha32: p1 with: p2.
		nBits = 32
			ifFalse:[
				v := self rgbMap: v from: 32 to: nBits].
		result := result bitOr: (v <<  ((i - 1)*nBits)). 
		mask := mask << nBits  "slide left to next partition"].
	^ result
! !

!BitBltPure methodsFor: 'combination rules' stamp: 'tfel 1/17/2014 19:03'!
partitionedSub: word1 from: word2 nBits: nBits nPartitions: nParts
	"Subtract word1 from word2 as nParts partitions of nBits each.
	This is useful for packed pixels, or packed colors"
	| mask result p1 p2 |
	"In C, most arithmetic operations answer the same bit pattern regardless of the operands being signed or unsigned ints
	(this is due to the way 2's complement numbers work). However, comparisions might fail. Add the proper declaration of
	words as unsigned int in those cases where comparisions are done (jmv)"
	mask := maskTable at: nBits.  "partition mask starts at the right"
	result := 0.
	1 to: nParts do:
		[:i |
		p1 := word1 bitAnd: mask.
		p2 := word2 bitAnd: mask.
		p1 < p2  "result is really abs value of thedifference"
			ifTrue: [result := result bitOr: p2 - p1]
			ifFalse: [result := result bitOr: p1 - p2].
		mask := mask << nBits  "slide left to next partition"].
	^ result
! !

!BitBltPure methodsFor: 'combination rules' stamp: 'tfel 1/18/2014 15:47'!
pickSourcePixels: nPixels flags: mapperFlags srcMask: srcMask destMask: dstMask srcShiftInc: srcShiftInc dstShiftInc: dstShiftInc
	"Pick nPix pixels starting at srcBitIndex from the source, map by the
	color map, and justify them according to dstBitIndex in the resulting destWord."
	| sourceWord destWord sourcePix destPix srcShift dstShift nPix |
	sourceWord := self srcLongAt: sourceIndex.
	destWord := 0.
	srcShift := srcBitShift. "Hint: Keep in register"
	dstShift := dstBitShift. "Hint: Keep in register"
	nPix := nPixels. "always > 0 so we can use do { } while(--nPix);"
	(mapperFlags = (ColorMapPresent bitOr: ColorMapIndexedPart)) ifTrue:[
		"a little optimization for (pretty crucial) blits using indexed lookups only"
		[	"grab, colormap and mix in pixel"
			sourcePix := sourceWord >> srcShift bitAnd: srcMask.
			destPix := cmLookupTable at: (sourcePix bitAnd: cmMask).
			destWord := destWord bitOr: (destPix bitAnd: dstMask) << dstShift.
			"adjust dest pix index"
			dstShift := dstShift + dstShiftInc.
			"adjust source pix index"
			((srcShift := srcShift + srcShiftInc) bitAnd: 16rFFFFFFE0) = 0 ifFalse:[
				sourceMSB ifTrue:[srcShift := srcShift + 32] ifFalse:[srcShift := srcShift - 32].
				sourceWord := self srcLongAt: (sourceIndex := sourceIndex + 1)].
		(nPix := nPix - 1) = 0] whileFalse.
	] ifFalse:[
		[	"grab, colormap and mix in pixel"
			sourcePix := sourceWord >> srcShift bitAnd: srcMask.
			destPix := self mapPixel: sourcePix flags: mapperFlags.
			destWord := destWord bitOr: (destPix bitAnd: dstMask) << dstShift.
			"adjust dest pix index"
			dstShift := dstShift + dstShiftInc.
			"adjust source pix index"
			((srcShift := srcShift + srcShiftInc) bitAnd: 16rFFFFFFE0) = 0 ifFalse:[
				sourceMSB ifTrue:[srcShift := srcShift + 32] ifFalse:[srcShift := srcShift - 32].
				sourceWord := self srcLongAt: (sourceIndex := sourceIndex + 1)].
		(nPix := nPix - 1) = 0] whileFalse.
	].
	srcBitShift := srcShift. "Store back"
	^destWord
! !

!BitBltPure methodsFor: 'combination rules' stamp: 'tfel 1/17/2014 19:03'!
pixClear: sourceWord with: destinationWord
	"Clear all pixels in destinationWord for which the pixels of sourceWord have the same values. Used to clear areas of some constant color to zero."
	| mask result nBits pv |
	destDepth = 32 ifTrue:[
		sourceWord = destinationWord ifTrue:[^0] ifFalse:[^destinationWord].
	].
	nBits := destDepth.
	mask := maskTable at: nBits.  "partition mask starts at the right"
	result := 0.
	1 to: destPPW do:[:i |
		pv := destinationWord bitAnd: mask.
		(sourceWord bitAnd: mask) = pv ifTrue:[pv := 0].
		result := result bitOr: pv.
		mask := mask << nBits "slide left to next partition"].
	^ result! !

!BitBltPure methodsFor: 'combination rules' stamp: 'tfel 1/17/2014 19:03'!
pixMask: sourceWord with: destinationWord

	^ self partitionedAND: sourceWord bitInvert32 to: destinationWord
					nBits: destDepth nPartitions: destPPW! !

!BitBltPure methodsFor: 'combination rules' stamp: 'tfel 1/17/2014 19:03'!
pixPaint: sourceWord with: destinationWord

	sourceWord = 0 ifTrue: [^ destinationWord].
	^ sourceWord bitOr:
		(self partitionedAND: sourceWord bitInvert32 to: destinationWord
						nBits: destDepth nPartitions: destPPW)! !

!BitBltPure methodsFor: 'combination rules' stamp: 'tfel 1/17/2014 19:04'!
pixSwap: sourceWord with: destWord
	"Swap the pixels in destWord"
	| result shift lowMask highMask |
	destPPW = 1 ifTrue:[^destWord]. "a single pixel per word"
	result := 0.
	lowMask := (1 << destDepth) - 1. "mask low pixel"
	highMask := lowMask << (destPPW-1 * destDepth). "mask high pixel"
	shift := 32 - destDepth.
	result := result bitOr: (
				(destWord bitAnd: lowMask) << shift bitOr:
					(destWord bitAnd: highMask) >> shift).
	destPPW <= 2 ifTrue:[^result].
	2 to: destPPW // 2 do:[:i|
		lowMask := lowMask << destDepth.
		highMask := highMask >> destDepth.
		shift := shift - (destDepth * 2).
		result := result bitOr: (
					(destWord bitAnd: lowMask) << shift bitOr:
						(destWord bitAnd: highMask) >> shift)].
	^result! !

!BitBltPure methodsFor: 'combination rules' stamp: 'tfel 1/17/2014 19:04'!
rgbAdd: sourceWord with: destinationWord

	destDepth < 16 ifTrue:
		["Add each pixel separately"
		^ self partitionedAdd: sourceWord to: destinationWord
						nBits: destDepth nPartitions: destPPW].
	destDepth = 16 ifTrue:
		["Add RGB components of each pixel separately"
		^ (self partitionedAdd: sourceWord to: destinationWord
						nBits: 5 nPartitions: 3)
		+ ((self partitionedAdd: sourceWord>>16 to: destinationWord>>16
						nBits: 5 nPartitions: 3) << 16)]
	ifFalse:
		["Add RGBA components of the pixel separately"
		^ self partitionedAdd: sourceWord to: destinationWord
						nBits: 8 nPartitions: 4]! !

!BitBltPure methodsFor: 'combination rules' stamp: 'tfel 1/18/2014 15:05'!
rgbComponentAlpha16
	"This version assumes 
		combinationRule = 41
		sourcePixSize = 32
		destPixSize = 16
		sourceForm ~= destForm.
	"
	
	| srcIndex dstIndex sourceWord srcAlpha destWord deltaX deltaY 
	srcY dstY dstMask srcShift ditherBase ditherIndex ditherThreshold |

	deltaY := bbH + 1. "So we can pre-decrement"
	srcY := sy.
	dstY := dy.
	srcShift := (dx bitAnd: 1) * 16.
	destMSB ifTrue:[srcShift := 16 - srcShift].
	mask1 := 16rFFFF << (16 - srcShift).
	"This is the outer loop"
	[(deltaY := deltaY - 1) ~= 0] whileTrue:[
		srcIndex := sourceBits + (srcY * sourcePitch) + (sx * 4).
		dstIndex := destBits + (dstY * destPitch) + (dx // 2 * 4).
		ditherBase := (dstY bitAnd: 3) * 4.
		ditherIndex := (sx bitAnd: 3) - 1. "For pre-increment"
		deltaX := bbW + 1. "So we can pre-decrement"
		dstMask := mask1.
		dstMask = 16rFFFF ifTrue:[srcShift := 16] ifFalse:[srcShift := 0].

		"This is the inner loop"
		[(deltaX := deltaX - 1) ~= 0] whileTrue:[
			ditherThreshold := ditherMatrix4x4 at: ditherBase + (ditherIndex := ditherIndex + 1 bitAnd: 3) + 1.
			sourceWord := self srcLongAt: srcIndex.
			srcAlpha := sourceWord bitAnd: 16rFFFFFF.
				srcAlpha = 0 ifFalse:[ "0 < srcAlpha"
					"If we have to mix colors then just copy a single word"
					destWord := self dstLongAt: dstIndex.
					destWord := destWord bitAnd: dstMask bitInvert32.
					destWord := destWord >> srcShift.
					"Expand from 16 to 32 bit by adding zero bits"
					destWord := (((destWord bitAnd: 16r7C00) bitShift: 9) bitOr:
									((destWord bitAnd: 16r3E0) bitShift: 6)) bitOr:
								(((destWord bitAnd: 16r1F) bitShift: 3) bitOr:
									16rFF000000).
					"Mix colors"
					sourceWord := self rgbComponentAlpha32: sourceWord with: destWord.
					"And dither"
					sourceWord := self dither32To16: sourceWord threshold: ditherThreshold.
					sourceWord = 0 
						ifTrue:[sourceWord := 1 << srcShift]
						ifFalse:[sourceWord := sourceWord << srcShift].
					"Store back"
					self dstLongAt: dstIndex put: sourceWord mask: dstMask.
				].
			srcIndex := srcIndex + 4.
			destMSB
				ifTrue:[srcShift = 0 ifTrue:[dstIndex := dstIndex + 4]]
				ifFalse:[srcShift = 0 ifFalse:[dstIndex := dstIndex + 4]].
			srcShift := srcShift bitXor: 16. "Toggle between 0 and 16"
			dstMask := dstMask bitInvert32. "Mask other half word"
		].
		srcY := srcY + 1.
		dstY := dstY + 1.
	].
! !

!BitBltPure methodsFor: 'combination rules' stamp: 'tfel 1/17/2014 19:04'!
rgbComponentAlpha32
	"This version assumes 
		combinationRule = 41
		sourcePixSize = destPixSize = 32
		sourceForm ~= destForm.
	Note: The inner loop has been optimized for dealing
		with the special case of aR = aG = aB = 0 
	"
	| srcIndex dstIndex sourceWord srcAlpha destWord deltaX deltaY srcY dstY |
	deltaY := bbH + 1. "So we can pre-decrement"
	srcY := sy.
	dstY := dy.

	"This is the outer loop"
	[(deltaY := deltaY - 1) ~= 0] whileTrue:[
		srcIndex := sourceBits + (srcY * sourcePitch) + (sx * 4).
		dstIndex := destBits + (dstY * destPitch) + (dx * 4).
		deltaX := bbW + 1. "So we can pre-decrement"

		"This is the inner loop"
		[(deltaX := deltaX - 1) ~= 0] whileTrue:[
			sourceWord := self srcLongAt: srcIndex.
			srcAlpha := sourceWord bitAnd:16rFFFFFF.
				srcAlpha = 0 ifTrue:[
					srcIndex := srcIndex + 4.
					dstIndex := dstIndex + 4.
					"Now skip as many words as possible,"
					[(deltaX := deltaX - 1) ~= 0 and:[
						((sourceWord := self srcLongAt: srcIndex) bitAnd:16rFFFFFF) = 0]]
						whileTrue:[
							srcIndex := srcIndex + 4.
							dstIndex := dstIndex + 4.
						].
					"Adjust deltaX"
					deltaX := deltaX + 1.
				] ifFalse:[ "0 < srcAlpha"
					"If we have to mix colors then just copy a single word"
					destWord := self dstLongAt: dstIndex.
					destWord := self rgbComponentAlpha32: sourceWord with: destWord.
					self dstLongAt: dstIndex put: destWord.
					srcIndex := srcIndex + 4.
					dstIndex := dstIndex + 4.
				].
		].
		srcY := srcY + 1.
		dstY := dstY + 1.
	].! !

!BitBltPure methodsFor: 'combination rules' stamp: 'tfel 1/17/2014 19:05'!
rgbComponentAlpha32: sourceWord with: destinationWord
	"
	componentAlphaModeColor is the color,
	sourceWord contains an alpha value for each component of RGB
	each of which is encoded as0 meaning 0.0 and 255 meaning 1.0 .
	the rule is...
	
	color = componentAlphaModeColor.
	colorAlpha = componentAlphaModeAlpha.
	mask = sourceWord.
	dst.A =  colorAlpha + (1 - colorAlpha) * dst.A
      dst.R = color.R * mask.R * colorAlpha + (1 - (mask.R * colorAlpha)) * dst.R
      dst.G = color.G * mask.G * colorAlpha + (1 - (mask.G* colorAlpha)) * dst.G
      dst.B = color.B * mask.B * colorAlpha + (1 - (mask.B* colorAlpha)) * dst.B
	"
	| alpha dstMask srcColor srcAlpha b g r a aB aG aR aA answer s d |
		
	alpha := sourceWord.
	alpha = 0 ifTrue:[^destinationWord].
	srcColor := componentAlphaModeColor.
	srcAlpha := componentAlphaModeAlpha bitAnd: 255.
	
	aB := alpha bitAnd: 255.
	alpha := alpha >> 8.
	aG := alpha bitAnd: 255.
	alpha := alpha >> 8.
	aR := alpha bitAnd: 255.
	alpha := alpha >> 8.
	aA := alpha bitAnd: 255.	

	srcAlpha = 255 
		ifFalse:[
			aA := aA * srcAlpha >> 8.
			aR := aR * srcAlpha >> 8.
			aG := aG * srcAlpha >> 8.
			aB := aB * srcAlpha >> 8].
			
	dstMask := destinationWord.
	d := dstMask bitAnd: 255.
	s := srcColor bitAnd: 255.
	ungammaLookupTable == nil
		ifFalse:[
			d := ungammaLookupTable at: d.
			s := ungammaLookupTable at: s.].
	b := (d * (255 - aB) >> 8) + (s * aB >> 8).
	b > 255 ifTrue:[b := 255].
	gammaLookupTable == nil
		ifFalse:[	
			b := gammaLookupTable at: b].
	dstMask := dstMask >> 8.
	srcColor := srcColor >> 8.
	d := dstMask bitAnd: 255.
	s := srcColor bitAnd: 255.
	ungammaLookupTable == nil
		ifFalse:[
			d := ungammaLookupTable at: d.
			s := ungammaLookupTable at: s.].
	g := (d * (255 - aG) >> 8) + (s * aG >> 8).
	g > 255 ifTrue:[g := 255].
	gammaLookupTable == nil
		ifFalse:[	
			g := gammaLookupTable at: g].
	dstMask := dstMask >> 8.
	srcColor := srcColor >> 8.
	d := dstMask bitAnd: 255.
	s := srcColor bitAnd: 255.
	ungammaLookupTable == nil
		ifFalse:[
			d := ungammaLookupTable at: d.
			s := ungammaLookupTable at: s.].
	r := (d * (255 - aR) >> 8) + (s * aR >> 8).
	r > 255 ifTrue:[r := 255].
	gammaLookupTable == nil
		ifFalse:[	
			r := gammaLookupTable at: r].
	dstMask := dstMask >> 8.
	srcColor := srcColor >> 8.
	a := ((dstMask bitAnd: 255) * (255 - aA) >> 8) + aA. "no need to gamma correct alpha value ?"
	a > 255 ifTrue:[a := 255].
	answer := (((((a << 8) + r) << 8) + g) << 8) + b.
	^answer	! !

!BitBltPure methodsFor: 'combination rules' stamp: 'tfel 1/17/2014 19:05'!
rgbComponentAlpha8
	"This version assumes 
		combinationRule = 41
		sourcePixSize = 32
		destPixSize = 8
		sourceForm ~= destForm.
	Note: This is not real blending since we don't have the source colors available.
	"
	
	| srcIndex dstIndex sourceWord srcAlpha destWord deltaX deltaY 
	srcY dstY dstMask srcShift adjust mappingTable mapperFlags |
	
	mappingTable := self default8To32Table.
	mapperFlags := cmFlags bitAnd: ColorMapNewStyle bitInvert32.
	deltaY := bbH + 1. "So we can pre-decrement"
	srcY := sy.
	dstY := dy.
	mask1 := ((dx bitAnd: 3) * 8).
	destMSB ifTrue:[mask1 := 24 - mask1].
	mask2 := AllOnes bitXor:(16rFF << mask1).
	(dx bitAnd: 1) = 0 
		ifTrue:[adjust := 0]
		ifFalse:[adjust := 16r1F1F1F1F].
	(dy bitAnd: 1) = 0
		ifTrue:[adjust := adjust bitXor: 16r1F1F1F1F].
	"This is the outer loop"
	[(deltaY := deltaY - 1) ~= 0] whileTrue:[
		adjust := adjust bitXor: 16r1F1F1F1F.
		srcIndex := sourceBits + (srcY * sourcePitch) + (sx * 4).
		dstIndex := destBits + (dstY * destPitch) + (dx // 4 * 4).
		deltaX := bbW + 1. "So we can pre-decrement"
		srcShift := mask1.
		dstMask := mask2.

		"This is the inner loop"
		[(deltaX := deltaX - 1) ~= 0] whileTrue:[
			sourceWord := ((self srcLongAt: srcIndex) bitAnd: (adjust bitInvert32)) + adjust.
			srcAlpha := sourceWord bitAnd: 16rFFFFFF.
			"set srcAlpha to the average of the 3 separate aR,Ag,AB values"
			srcAlpha := ((srcAlpha >> 16) + (srcAlpha >> 8 bitAnd: 16rFF) + (srcAlpha bitAnd: 16rFF)) // 3.
			srcAlpha > 31 ifTrue:["Everything below 31 is transparent"
				srcAlpha > 224 
					ifTrue: ["treat everything above 224 as opaque"
						sourceWord := 16rFFFFFFFF].
				destWord := self dstLongAt: dstIndex.
				destWord := destWord bitAnd: dstMask bitInvert32.
				destWord := destWord >> srcShift.
				destWord := mappingTable at: destWord.
				sourceWord := self rgbComponentAlpha32: sourceWord with: destWord.
				sourceWord := self mapPixel: sourceWord flags: mapperFlags.
				sourceWord := sourceWord << srcShift.
				"Store back"
				self dstLongAt: dstIndex put: sourceWord mask: dstMask.
			].
			srcIndex := srcIndex + 4.
			destMSB ifTrue:[
				srcShift = 0 
					ifTrue:[dstIndex := dstIndex + 4.
							srcShift := 24.
							dstMask := 16r00FFFFFF]
					ifFalse:[srcShift := srcShift - 8.
							dstMask := (dstMask >> 8) bitOr: 16rFF000000].
			] ifFalse:[
				srcShift = 32
					ifTrue:[dstIndex := dstIndex + 4.
							srcShift := 0.
							dstMask := 16rFFFFFF00]
					ifFalse:[srcShift := srcShift + 8.
							dstMask := dstMask << 8 bitOr: 255].
			].
			adjust := adjust bitXor: 16r1F1F1F1F.
		].
		srcY := srcY + 1.
		dstY := dstY + 1.
	].
! !

!BitBltPure methodsFor: 'combination rules' stamp: 'tfel 1/17/2014 19:05'!
rgbComponentAlpha: sourceWord with: destinationWord
	"
	componentAlphaModeColor is the color,
	sourceWord contains an alpha value for each component of RGB
	each of which is encoded as0 meaning 0.0 and 255 meaning 1.0 .
	the rule is...
	
	color = componentAlphaModeColor.
	colorAlpha = componentAlphaModeAlpha.
	mask = sourceWord.
	dst.A =  colorAlpha + (1 - colorAlpha) * dst.A
      dst.R = color.R * mask.R * colorAlpha + (1 - (mask.R * colorAlpha)) * dst.R
      dst.G = color.G * mask.G * colorAlpha + (1 - (mask.G* colorAlpha)) * dst.G
      dst.B = color.B * mask.B * colorAlpha + (1 - (mask.B* colorAlpha)) * dst.B
	"
	| alpha |
		
	alpha := sourceWord.
	alpha = 0 ifTrue:[^destinationWord].
	^self partitionedRgbComponentAlpha: sourceWord dest: destinationWord nBits: destDepth nPartitions: destPPW.! !

!BitBltPure methodsFor: 'combination rules' stamp: 'tfel 1/17/2014 19:05'!
rgbDiff: sourceWord with: destinationWord
	"Subract the pixels in the source and destination, color by color,
	and return the sum of the absolute value of all the differences.
	For non-rgb, return the number of differing pixels."
	| pixMask destShifted sourceShifted destPixVal bitsPerColor rgbMask sourcePixVal diff maskShifted |
	pixMask := maskTable at: destDepth.
	destDepth = 16
		ifTrue: [bitsPerColor := 5.  rgbMask := 16r1F]
		ifFalse: [bitsPerColor := 8.  rgbMask := 16rFF].
	maskShifted := destMask.
	destShifted := destinationWord.
	sourceShifted := sourceWord.
	1 to: destPPW do:
		[:i |
		(maskShifted bitAnd: pixMask) > 0 ifTrue:
			["Only tally pixels within the destination rectangle"
			destPixVal := destShifted bitAnd: pixMask.
			sourcePixVal := sourceShifted bitAnd: pixMask.
			destDepth < 16
				ifTrue: [sourcePixVal = destPixVal
							ifTrue: [diff := 0]
							ifFalse: [diff := 1]]
				ifFalse: [diff := (self partitionedSub: sourcePixVal from: destPixVal
								nBits: bitsPerColor nPartitions: 3).
						diff := (diff bitAnd: rgbMask)
							+ (diff>>bitsPerColor bitAnd: rgbMask)
							+ ((diff>>bitsPerColor)>>bitsPerColor bitAnd: rgbMask)].
			bitCount := bitCount + diff].
		maskShifted := maskShifted >> destDepth.
		sourceShifted := sourceShifted >> destDepth.
		destShifted := destShifted >> destDepth].
	^ destinationWord  "For no effect on dest"
! !

!BitBltPure methodsFor: 'combination rules' stamp: 'tfel 1/17/2014 19:06'!
rgbMax: sourceWord with: destinationWord

	destDepth < 16 ifTrue:
		["Max each pixel separately"
		^ self partitionedMax: sourceWord with: destinationWord
						nBits: destDepth nPartitions: destPPW].
	destDepth = 16 ifTrue:
		["Max RGB components of each pixel separately"
		^ (self partitionedMax: sourceWord with: destinationWord
						nBits: 5 nPartitions: 3)
		+ ((self partitionedMax: sourceWord>>16 with: destinationWord>>16
						nBits: 5 nPartitions: 3) << 16)]
	ifFalse:
		["Max RGBA components of the pixel separately"
		^ self partitionedMax: sourceWord with: destinationWord
						nBits: 8 nPartitions: 4]! !

!BitBltPure methodsFor: 'combination rules' stamp: 'tfel 1/17/2014 19:06'!
rgbMin: sourceWord with: destinationWord

	destDepth < 16 ifTrue:
		["Min each pixel separately"
		^ self partitionedMin: sourceWord with: destinationWord
						nBits: destDepth nPartitions: destPPW].
	destDepth = 16 ifTrue:
		["Min RGB components of each pixel separately"
		^ (self partitionedMin: sourceWord with: destinationWord
						nBits: 5 nPartitions: 3)
		+ ((self partitionedMin: sourceWord>>16 with: destinationWord>>16
						nBits: 5 nPartitions: 3) << 16)]
	ifFalse:
		["Min RGBA components of the pixel separately"
		^ self partitionedMin: sourceWord with: destinationWord
						nBits: 8 nPartitions: 4]! !

!BitBltPure methodsFor: 'combination rules' stamp: 'tfel 1/17/2014 19:06'!
rgbMinInvert: wordToInvert with: destinationWord
	| sourceWord |

	sourceWord := wordToInvert bitInvert32.
	destDepth < 16 ifTrue:
		["Min each pixel separately"
		^ self partitionedMin: sourceWord with: destinationWord
						nBits: destDepth nPartitions: destPPW].
	destDepth = 16 ifTrue:
		["Min RGB components of each pixel separately"
		^ (self partitionedMin: sourceWord with: destinationWord
						nBits: 5 nPartitions: 3)
		+ ((self partitionedMin: sourceWord>>16 with: destinationWord>>16
						nBits: 5 nPartitions: 3) << 16)]
	ifFalse:
		["Min RGBA components of the pixel separately"
		^ self partitionedMin: sourceWord with: destinationWord
						nBits: 8 nPartitions: 4]! !

!BitBltPure methodsFor: 'combination rules' stamp: 'tfel 1/17/2014 19:06'!
rgbMul: sourceWord with: destinationWord

	destDepth < 16 ifTrue:
		["Mul each pixel separately"
		^ self partitionedMul: sourceWord with: destinationWord
						nBits: destDepth nPartitions: destPPW].
	destDepth = 16 ifTrue:
		["Mul RGB components of each pixel separately"
		^ (self partitionedMul: sourceWord with: destinationWord
						nBits: 5 nPartitions: 3)
		+ ((self partitionedMul: sourceWord>>16 with: destinationWord>>16
						nBits: 5 nPartitions: 3) << 16)]
	ifFalse:
		["Mul RGBA components of the pixel separately"
		^ self partitionedMul: sourceWord with: destinationWord
						nBits: 8 nPartitions: 4]

"	| scanner |
	Display repaintMorphicDisplay.
	scanner := DisplayScanner quickPrintOn: Display.
	MessageTally time: [0 to: 760 by: 4 do:  [:y |scanner drawString: 'qwrepoiuasfd=)(/&()=#!!°lkjzxv.,mn124+09857907QROIYTOAFDJZXNBNB,M-.,Mqwrepoiuasfd=)(/&()=#!!°lkjzxv.,mn124+09857907QROIYTOAFDJZXNBNB,M-.,M1234124356785678' at: 0 at y]]. "! !

!BitBltPure methodsFor: 'combination rules' stamp: 'tfel 1/17/2014 19:06'!
rgbSub: sourceWord with: destinationWord

	destDepth < 16 ifTrue:
		["Sub each pixel separately"
		^ self partitionedSub: sourceWord from: destinationWord
						nBits: destDepth nPartitions: destPPW].
	destDepth = 16 ifTrue:
		["Sub RGB components of each pixel separately"
		^ (self partitionedSub: sourceWord from: destinationWord
						nBits: 5 nPartitions: 3)
		+ ((self partitionedSub: sourceWord>>16 from: destinationWord>>16
						nBits: 5 nPartitions: 3) << 16)]
	ifFalse:
		["Sub RGBA components of the pixel separately"
		^ self partitionedSub: sourceWord from: destinationWord
						nBits: 8 nPartitions: 4]! !

!BitBltPure methodsFor: 'combination rules' stamp: 'tfel 1/17/2014 19:01'!
sourceWord: sourceWord with: destinationWord
	^sourceWord! !

!BitBltPure methodsFor: 'combination rules' stamp: 'tfel 1/17/2014 19:01'!
subWord: sourceWord with: destinationWord
	^sourceWord - destinationWord! !

!BitBltPure methodsFor: 'combination rules' stamp: 'tfel 1/17/2014 19:06'!
tallyIntoMap: sourceWord with: destinationWord
	"Tally pixels into the color map.  Those tallied are exactly those
	in the destination rectangle.  Note that the source should be 
	specified == destination, in order for the proper color map checks 
	to be performed at setup."
	| mapIndex pixMask destShifted maskShifted pixVal |

	(cmFlags bitAnd: (ColorMapPresent bitOr: ColorMapIndexedPart)) = 
		(ColorMapPresent bitOr: ColorMapIndexedPart)
			ifFalse: [^ destinationWord "no op"].
	pixMask := maskTable at: destDepth.
	destShifted := destinationWord.
	maskShifted := destMask.
	1 to: destPPW do:
		[:i |
		(maskShifted bitAnd: pixMask) = 0 ifFalse:
			["Only tally pixels within the destination rectangle"
			pixVal := destShifted bitAnd: pixMask.
			destDepth < 16
				ifTrue: [mapIndex := pixVal]
				ifFalse: [destDepth = 16
					ifTrue: [mapIndex := self rgbMap: pixVal from: 5 to: cmBitsPerColor]
					ifFalse: [mapIndex := self rgbMap: pixVal from: 8 to: cmBitsPerColor]].
			self tallyMapAt: mapIndex put: (self tallyMapAt: mapIndex) + 1].
		maskShifted := maskShifted >> destDepth.
		destShifted := destShifted >> destDepth].
	^ destinationWord  "For no effect on dest"! !


!BitBltPure methodsFor: 'accessing' stamp: 'tfel 1/17/2014 19:47'!
affectedB

	^ affectedB! !

!BitBltPure methodsFor: 'accessing' stamp: 'tfel 1/17/2014 19:47'!
affectedB: anObject

	affectedB := anObject! !

!BitBltPure methodsFor: 'accessing' stamp: 'tfel 1/17/2014 19:01'!
affectedBottom

	^affectedB! !

!BitBltPure methodsFor: 'accessing' stamp: 'tfel 1/17/2014 19:47'!
affectedL

	^ affectedL! !

!BitBltPure methodsFor: 'accessing' stamp: 'tfel 1/17/2014 19:47'!
affectedL: anObject

	affectedL := anObject! !

!BitBltPure methodsFor: 'accessing' stamp: 'tfel 1/17/2014 19:01'!
affectedLeft

	^affectedL! !

!BitBltPure methodsFor: 'accessing' stamp: 'tfel 1/17/2014 19:47'!
affectedR

	^ affectedR! !

!BitBltPure methodsFor: 'accessing' stamp: 'tfel 1/17/2014 19:47'!
affectedR: anObject

	affectedR := anObject! !

!BitBltPure methodsFor: 'accessing' stamp: 'tfel 1/17/2014 19:01'!
affectedRight

	^affectedR! !

!BitBltPure methodsFor: 'accessing' stamp: 'tfel 1/17/2014 19:47'!
affectedT

	^ affectedT! !

!BitBltPure methodsFor: 'accessing' stamp: 'tfel 1/17/2014 19:47'!
affectedT: anObject

	affectedT := anObject! !

!BitBltPure methodsFor: 'accessing' stamp: 'tfel 1/17/2014 19:01'!
affectedTop

	^affectedT! !

!BitBltPure methodsFor: 'accessing' stamp: 'tfel 1/17/2014 19:47'!
bbH

	^ bbH! !

!BitBltPure methodsFor: 'accessing' stamp: 'tfel 1/17/2014 19:47'!
bbH: anObject

	bbH := anObject! !

!BitBltPure methodsFor: 'accessing' stamp: 'tfel 1/17/2014 19:47'!
bbW

	^ bbW! !

!BitBltPure methodsFor: 'accessing' stamp: 'tfel 1/17/2014 19:47'!
bbW: anObject

	bbW := anObject! !

!BitBltPure methodsFor: 'accessing' stamp: 'tfel 1/17/2014 19:47'!
bitBltOop

	^ bitBltOop! !

!BitBltPure methodsFor: 'accessing' stamp: 'tfel 1/17/2014 19:47'!
bitBltOop: anObject

	bitBltOop := anObject! !

!BitBltPure methodsFor: 'accessing' stamp: 'tfel 1/17/2014 19:47'!
bitCount

	^ bitCount! !

!BitBltPure methodsFor: 'accessing' stamp: 'tfel 1/17/2014 19:47'!
bitCount: anObject

	bitCount := anObject! !

!BitBltPure methodsFor: 'accessing' stamp: 'tfel 1/17/2014 19:47'!
clipHeight

	^ clipHeight! !

!BitBltPure methodsFor: 'accessing' stamp: 'tfel 1/17/2014 19:47'!
clipHeight: anObject

	clipHeight := anObject! !

!BitBltPure methodsFor: 'accessing' stamp: 'tfel 1/17/2014 19:47'!
clipWidth

	^ clipWidth! !

!BitBltPure methodsFor: 'accessing' stamp: 'tfel 1/17/2014 19:47'!
clipWidth: anObject

	clipWidth := anObject! !

!BitBltPure methodsFor: 'accessing' stamp: 'tfel 1/17/2014 19:47'!
clipX

	^ clipX! !

!BitBltPure methodsFor: 'accessing' stamp: 'tfel 1/17/2014 19:47'!
clipX: anObject

	clipX := anObject! !

!BitBltPure methodsFor: 'accessing' stamp: 'tfel 1/17/2014 19:47'!
clipY

	^ clipY! !

!BitBltPure methodsFor: 'accessing' stamp: 'tfel 1/17/2014 19:47'!
clipY: anObject

	clipY := anObject! !

!BitBltPure methodsFor: 'accessing' stamp: 'tfel 1/17/2014 19:47'!
cmBitsPerColor

	^ cmBitsPerColor! !

!BitBltPure methodsFor: 'accessing' stamp: 'tfel 1/17/2014 19:47'!
cmBitsPerColor: anObject

	cmBitsPerColor := anObject! !

!BitBltPure methodsFor: 'accessing' stamp: 'tfel 1/17/2014 19:47'!
cmFlags

	^ cmFlags! !

!BitBltPure methodsFor: 'accessing' stamp: 'tfel 1/17/2014 19:47'!
cmFlags: anObject

	cmFlags := anObject! !

!BitBltPure methodsFor: 'accessing' stamp: 'tfel 1/17/2014 19:47'!
cmLookupTable

	^ cmLookupTable! !

!BitBltPure methodsFor: 'accessing' stamp: 'tfel 1/17/2014 19:47'!
cmLookupTable: anObject

	cmLookupTable := anObject! !

!BitBltPure methodsFor: 'accessing' stamp: 'tfel 1/17/2014 19:47'!
cmMask

	^ cmMask! !

!BitBltPure methodsFor: 'accessing' stamp: 'tfel 1/17/2014 19:47'!
cmMask: anObject

	cmMask := anObject! !

!BitBltPure methodsFor: 'accessing' stamp: 'tfel 1/17/2014 19:47'!
cmMaskTable

	^ cmMaskTable! !

!BitBltPure methodsFor: 'accessing' stamp: 'tfel 1/17/2014 19:47'!
cmMaskTable: anObject

	cmMaskTable := anObject! !

!BitBltPure methodsFor: 'accessing' stamp: 'tfel 1/17/2014 19:47'!
cmShiftTable

	^ cmShiftTable! !

!BitBltPure methodsFor: 'accessing' stamp: 'tfel 1/17/2014 19:47'!
cmShiftTable: anObject

	cmShiftTable := anObject! !

!BitBltPure methodsFor: 'accessing' stamp: 'tfel 1/17/2014 19:50'!
colorMap

	^ colorMap! !

!BitBltPure methodsFor: 'accessing' stamp: 'tfel 1/17/2014 19:50'!
colorMap: anObject

	colorMap := anObject! !

!BitBltPure methodsFor: 'accessing' stamp: 'tfel 1/17/2014 19:47'!
combinationRule

	^ combinationRule! !

!BitBltPure methodsFor: 'accessing' stamp: 'tfel 1/17/2014 19:47'!
combinationRule: anObject

	combinationRule := anObject! !

!BitBltPure methodsFor: 'accessing' stamp: 'tfel 1/17/2014 19:47'!
componentAlphaModeAlpha

	^ componentAlphaModeAlpha! !

!BitBltPure methodsFor: 'accessing' stamp: 'tfel 1/17/2014 19:47'!
componentAlphaModeAlpha: anObject

	componentAlphaModeAlpha := anObject! !

!BitBltPure methodsFor: 'accessing' stamp: 'tfel 1/17/2014 19:47'!
componentAlphaModeColor

	^ componentAlphaModeColor! !

!BitBltPure methodsFor: 'accessing' stamp: 'tfel 1/17/2014 19:47'!
componentAlphaModeColor: anObject

	componentAlphaModeColor := anObject! !

!BitBltPure methodsFor: 'accessing' stamp: 'tfel 1/17/2014 19:47'!
destBits

	^ destBits! !

!BitBltPure methodsFor: 'accessing' stamp: 'tfel 1/17/2014 19:47'!
destBits: anObject

	destBits := anObject! !

!BitBltPure methodsFor: 'accessing' stamp: 'tfel 1/17/2014 19:47'!
destDelta

	^ destDelta! !

!BitBltPure methodsFor: 'accessing' stamp: 'tfel 1/17/2014 19:47'!
destDelta: anObject

	destDelta := anObject! !

!BitBltPure methodsFor: 'accessing' stamp: 'tfel 1/17/2014 19:47'!
destDepth

	^ destDepth! !

!BitBltPure methodsFor: 'accessing' stamp: 'tfel 1/17/2014 19:47'!
destDepth: anObject

	destDepth := anObject! !

!BitBltPure methodsFor: 'accessing' stamp: 'tfel 1/17/2014 19:47'!
destForm

	^ destForm! !

!BitBltPure methodsFor: 'accessing' stamp: 'tfel 1/17/2014 19:47'!
destForm: anObject

	destForm := anObject! !

!BitBltPure methodsFor: 'accessing' stamp: 'tfel 1/17/2014 19:47'!
destHeight

	^ destHeight! !

!BitBltPure methodsFor: 'accessing' stamp: 'tfel 1/17/2014 19:47'!
destHeight: anObject

	destHeight := anObject! !

!BitBltPure methodsFor: 'accessing' stamp: 'tfel 1/17/2014 19:47'!
destIndex

	^ destIndex! !

!BitBltPure methodsFor: 'accessing' stamp: 'tfel 1/17/2014 19:47'!
destIndex: anObject

	destIndex := anObject! !

!BitBltPure methodsFor: 'accessing' stamp: 'tfel 1/17/2014 19:47'!
destMSB

	^ destMSB! !

!BitBltPure methodsFor: 'accessing' stamp: 'tfel 1/17/2014 19:47'!
destMSB: anObject

	destMSB := anObject! !

!BitBltPure methodsFor: 'accessing' stamp: 'tfel 1/17/2014 19:47'!
destMask

	^ destMask! !

!BitBltPure methodsFor: 'accessing' stamp: 'tfel 1/17/2014 19:47'!
destMask: anObject

	destMask := anObject! !

!BitBltPure methodsFor: 'accessing' stamp: 'tfel 1/17/2014 19:47'!
destPPW

	^ destPPW! !

!BitBltPure methodsFor: 'accessing' stamp: 'tfel 1/17/2014 19:47'!
destPPW: anObject

	destPPW := anObject! !

!BitBltPure methodsFor: 'accessing' stamp: 'tfel 1/17/2014 19:47'!
destPitch

	^ destPitch! !

!BitBltPure methodsFor: 'accessing' stamp: 'tfel 1/17/2014 19:47'!
destPitch: anObject

	destPitch := anObject! !

!BitBltPure methodsFor: 'accessing' stamp: 'tfel 1/17/2014 19:47'!
destWidth

	^ destWidth! !

!BitBltPure methodsFor: 'accessing' stamp: 'tfel 1/17/2014 19:47'!
destWidth: anObject

	destWidth := anObject! !

!BitBltPure methodsFor: 'accessing' stamp: 'tfel 1/17/2014 19:47'!
destX

	^ destX! !

!BitBltPure methodsFor: 'accessing' stamp: 'tfel 1/17/2014 19:47'!
destX: anObject

	destX := anObject! !

!BitBltPure methodsFor: 'accessing' stamp: 'tfel 1/17/2014 19:47'!
destY

	^ destY! !

!BitBltPure methodsFor: 'accessing' stamp: 'tfel 1/17/2014 19:47'!
destY: anObject

	destY := anObject! !

!BitBltPure methodsFor: 'accessing' stamp: 'tfel 1/17/2014 19:47'!
dither8Lookup

	^ dither8Lookup! !

!BitBltPure methodsFor: 'accessing' stamp: 'tfel 1/17/2014 19:47'!
dither8Lookup: anObject

	dither8Lookup := anObject! !

!BitBltPure methodsFor: 'accessing' stamp: 'tfel 1/17/2014 19:47'!
ditherMatrix4x4

	^ ditherMatrix4x4! !

!BitBltPure methodsFor: 'accessing' stamp: 'tfel 1/17/2014 19:47'!
ditherMatrix4x4: anObject

	ditherMatrix4x4 := anObject! !

!BitBltPure methodsFor: 'accessing' stamp: 'tfel 1/17/2014 19:47'!
ditherThresholds16

	^ ditherThresholds16! !

!BitBltPure methodsFor: 'accessing' stamp: 'tfel 1/17/2014 19:47'!
ditherThresholds16: anObject

	ditherThresholds16 := anObject! !

!BitBltPure methodsFor: 'accessing' stamp: 'tfel 1/17/2014 19:47'!
ditherValues16

	^ ditherValues16! !

!BitBltPure methodsFor: 'accessing' stamp: 'tfel 1/17/2014 19:47'!
ditherValues16: anObject

	ditherValues16 := anObject! !

!BitBltPure methodsFor: 'accessing' stamp: 'tfel 1/17/2014 19:47'!
dstBitShift

	^ dstBitShift! !

!BitBltPure methodsFor: 'accessing' stamp: 'tfel 1/17/2014 19:47'!
dstBitShift: anObject

	dstBitShift := anObject! !

!BitBltPure methodsFor: 'accessing' stamp: 'tfel 1/17/2014 19:47'!
dx

	^ dx! !

!BitBltPure methodsFor: 'accessing' stamp: 'tfel 1/17/2014 19:47'!
dx: anObject

	dx := anObject! !

!BitBltPure methodsFor: 'accessing' stamp: 'tfel 1/17/2014 19:47'!
dy

	^ dy! !

!BitBltPure methodsFor: 'accessing' stamp: 'tfel 1/17/2014 19:47'!
dy: anObject

	dy := anObject! !

!BitBltPure methodsFor: 'accessing' stamp: 'tfel 1/17/2014 19:47'!
gammaLookupTable

	^ gammaLookupTable! !

!BitBltPure methodsFor: 'accessing' stamp: 'tfel 1/17/2014 19:47'!
gammaLookupTable: anObject

	gammaLookupTable := anObject! !

!BitBltPure methodsFor: 'accessing' stamp: 'tfel 1/17/2014 19:47'!
hDir

	^ hDir! !

!BitBltPure methodsFor: 'accessing' stamp: 'tfel 1/17/2014 19:47'!
hDir: anObject

	hDir := anObject! !

!BitBltPure methodsFor: 'accessing' stamp: 'tfel 1/17/2014 19:47'!
halftoneBase

	^ halftoneBase! !

!BitBltPure methodsFor: 'accessing' stamp: 'tfel 1/17/2014 19:47'!
halftoneBase: anObject

	halftoneBase := anObject! !

!BitBltPure methodsFor: 'accessing' stamp: 'tfel 1/17/2014 19:47'!
halftoneForm

	^ halftoneForm! !

!BitBltPure methodsFor: 'accessing' stamp: 'tfel 1/17/2014 19:47'!
halftoneForm: anObject

	halftoneForm := anObject! !

!BitBltPure methodsFor: 'accessing' stamp: 'tfel 1/17/2014 19:47'!
halftoneHeight

	^ halftoneHeight! !

!BitBltPure methodsFor: 'accessing' stamp: 'tfel 1/17/2014 19:47'!
halftoneHeight: anObject

	halftoneHeight := anObject! !

!BitBltPure methodsFor: 'accessing' stamp: 'tfel 1/17/2014 19:47'!
hasSurfaceLock

	^ hasSurfaceLock! !

!BitBltPure methodsFor: 'accessing' stamp: 'tfel 1/17/2014 19:47'!
hasSurfaceLock: anObject

	hasSurfaceLock := anObject! !

!BitBltPure methodsFor: 'accessing' stamp: 'tfel 1/17/2014 19:47'!
height

	^ height! !

!BitBltPure methodsFor: 'accessing' stamp: 'tfel 1/17/2014 19:47'!
height: anObject

	height := anObject! !

!BitBltPure methodsFor: 'accessing' stamp: 'tfel 1/17/2014 19:47'!
isWarping

	^ isWarping! !

!BitBltPure methodsFor: 'accessing' stamp: 'tfel 1/17/2014 19:47'!
isWarping: anObject

	isWarping := anObject! !

!BitBltPure methodsFor: 'accessing' stamp: 'tfel 1/17/2014 19:47'!
lockSurfaceFn

	^ lockSurfaceFn! !

!BitBltPure methodsFor: 'accessing' stamp: 'tfel 1/17/2014 19:47'!
lockSurfaceFn: anObject

	lockSurfaceFn := anObject! !

!BitBltPure methodsFor: 'accessing' stamp: 'tfel 1/17/2014 19:47'!
mask1

	^ mask1! !

!BitBltPure methodsFor: 'accessing' stamp: 'tfel 1/17/2014 19:47'!
mask1: anObject

	mask1 := anObject! !

!BitBltPure methodsFor: 'accessing' stamp: 'tfel 1/17/2014 19:47'!
mask2

	^ mask2! !

!BitBltPure methodsFor: 'accessing' stamp: 'tfel 1/17/2014 19:47'!
mask2: anObject

	mask2 := anObject! !

!BitBltPure methodsFor: 'accessing' stamp: 'tfel 1/17/2014 19:47'!
maskTable

	^ maskTable! !

!BitBltPure methodsFor: 'accessing' stamp: 'tfel 1/17/2014 19:47'!
maskTable: anObject

	maskTable := anObject! !

!BitBltPure methodsFor: 'accessing' stamp: 'tfel 1/17/2014 19:47'!
nWords

	^ nWords! !

!BitBltPure methodsFor: 'accessing' stamp: 'tfel 1/17/2014 19:47'!
nWords: anObject

	nWords := anObject! !

!BitBltPure methodsFor: 'accessing' stamp: 'tfel 1/17/2014 19:47'!
noHalftone

	^ noHalftone! !

!BitBltPure methodsFor: 'accessing' stamp: 'tfel 1/17/2014 19:47'!
noHalftone: anObject

	noHalftone := anObject! !

!BitBltPure methodsFor: 'accessing' stamp: 'tfel 1/17/2014 19:47'!
noSource

	^ noSource! !

!BitBltPure methodsFor: 'accessing' stamp: 'tfel 1/17/2014 19:47'!
noSource: anObject

	noSource := anObject! !

!BitBltPure methodsFor: 'accessing' stamp: 'tfel 1/17/2014 19:47'!
opTable

	^ opTable! !

!BitBltPure methodsFor: 'accessing' stamp: 'tfel 1/17/2014 19:47'!
opTable: anObject

	opTable := anObject! !

!BitBltPure methodsFor: 'accessing' stamp: 'tfel 1/17/2014 19:47'!
preload

	^ preload! !

!BitBltPure methodsFor: 'accessing' stamp: 'tfel 1/17/2014 19:47'!
preload: anObject

	preload := anObject! !

!BitBltPure methodsFor: 'accessing' stamp: 'tfel 1/17/2014 19:47'!
querySurfaceFn

	^ querySurfaceFn! !

!BitBltPure methodsFor: 'accessing' stamp: 'tfel 1/17/2014 19:47'!
querySurfaceFn: anObject

	querySurfaceFn := anObject! !

!BitBltPure methodsFor: 'accessing' stamp: 'tfel 1/17/2014 19:47'!
skew

	^ skew! !

!BitBltPure methodsFor: 'accessing' stamp: 'tfel 1/17/2014 19:47'!
skew: anObject

	skew := anObject! !

!BitBltPure methodsFor: 'accessing' stamp: 'tfel 1/17/2014 19:47'!
sourceAlpha

	^ sourceAlpha! !

!BitBltPure methodsFor: 'accessing' stamp: 'tfel 1/17/2014 19:47'!
sourceAlpha: anObject

	sourceAlpha := anObject! !

!BitBltPure methodsFor: 'accessing' stamp: 'tfel 1/17/2014 19:47'!
sourceBits

	^ sourceBits! !

!BitBltPure methodsFor: 'accessing' stamp: 'tfel 1/17/2014 19:47'!
sourceBits: anObject

	sourceBits := anObject! !

!BitBltPure methodsFor: 'accessing' stamp: 'tfel 1/17/2014 19:47'!
sourceDelta

	^ sourceDelta! !

!BitBltPure methodsFor: 'accessing' stamp: 'tfel 1/17/2014 19:47'!
sourceDelta: anObject

	sourceDelta := anObject! !

!BitBltPure methodsFor: 'accessing' stamp: 'tfel 1/17/2014 19:47'!
sourceDepth

	^ sourceDepth! !

!BitBltPure methodsFor: 'accessing' stamp: 'tfel 1/17/2014 19:47'!
sourceDepth: anObject

	sourceDepth := anObject! !

!BitBltPure methodsFor: 'accessing' stamp: 'tfel 1/17/2014 19:47'!
sourceForm

	^ sourceForm! !

!BitBltPure methodsFor: 'accessing' stamp: 'tfel 1/17/2014 19:47'!
sourceForm: anObject

	sourceForm := anObject! !

!BitBltPure methodsFor: 'accessing' stamp: 'tfel 1/17/2014 19:47'!
sourceHeight

	^ sourceHeight! !

!BitBltPure methodsFor: 'accessing' stamp: 'tfel 1/17/2014 19:47'!
sourceHeight: anObject

	sourceHeight := anObject! !

!BitBltPure methodsFor: 'accessing' stamp: 'tfel 1/17/2014 19:47'!
sourceIndex

	^ sourceIndex! !

!BitBltPure methodsFor: 'accessing' stamp: 'tfel 1/17/2014 19:47'!
sourceIndex: anObject

	sourceIndex := anObject! !

!BitBltPure methodsFor: 'accessing' stamp: 'tfel 1/17/2014 19:47'!
sourceMSB

	^ sourceMSB! !

!BitBltPure methodsFor: 'accessing' stamp: 'tfel 1/17/2014 19:47'!
sourceMSB: anObject

	sourceMSB := anObject! !

!BitBltPure methodsFor: 'accessing' stamp: 'tfel 1/17/2014 19:47'!
sourcePPW

	^ sourcePPW! !

!BitBltPure methodsFor: 'accessing' stamp: 'tfel 1/17/2014 19:47'!
sourcePPW: anObject

	sourcePPW := anObject! !

!BitBltPure methodsFor: 'accessing' stamp: 'tfel 1/17/2014 19:47'!
sourcePitch

	^ sourcePitch! !

!BitBltPure methodsFor: 'accessing' stamp: 'tfel 1/17/2014 19:47'!
sourcePitch: anObject

	sourcePitch := anObject! !

!BitBltPure methodsFor: 'accessing' stamp: 'tfel 1/17/2014 19:47'!
sourceWidth

	^ sourceWidth! !

!BitBltPure methodsFor: 'accessing' stamp: 'tfel 1/17/2014 19:47'!
sourceWidth: anObject

	sourceWidth := anObject! !

!BitBltPure methodsFor: 'accessing' stamp: 'tfel 1/17/2014 19:47'!
sourceX

	^ sourceX! !

!BitBltPure methodsFor: 'accessing' stamp: 'tfel 1/17/2014 19:47'!
sourceX: anObject

	sourceX := anObject! !

!BitBltPure methodsFor: 'accessing' stamp: 'tfel 1/17/2014 19:47'!
sourceY

	^ sourceY! !

!BitBltPure methodsFor: 'accessing' stamp: 'tfel 1/17/2014 19:47'!
sourceY: anObject

	sourceY := anObject! !

!BitBltPure methodsFor: 'accessing' stamp: 'tfel 1/17/2014 19:47'!
srcBitShift

	^ srcBitShift! !

!BitBltPure methodsFor: 'accessing' stamp: 'tfel 1/17/2014 19:47'!
srcBitShift: anObject

	srcBitShift := anObject! !

!BitBltPure methodsFor: 'accessing' stamp: 'tfel 1/17/2014 19:47'!
sx

	^ sx! !

!BitBltPure methodsFor: 'accessing' stamp: 'tfel 1/17/2014 19:47'!
sx: anObject

	sx := anObject! !

!BitBltPure methodsFor: 'accessing' stamp: 'tfel 1/17/2014 19:47'!
sy

	^ sy! !

!BitBltPure methodsFor: 'accessing' stamp: 'tfel 1/17/2014 19:47'!
sy: anObject

	sy := anObject! !

!BitBltPure methodsFor: 'accessing' stamp: 'tfel 1/17/2014 19:47'!
ungammaLookupTable

	^ ungammaLookupTable! !

!BitBltPure methodsFor: 'accessing' stamp: 'tfel 1/17/2014 19:47'!
ungammaLookupTable: anObject

	ungammaLookupTable := anObject! !

!BitBltPure methodsFor: 'accessing' stamp: 'tfel 1/17/2014 19:47'!
unlockSurfaceFn

	^ unlockSurfaceFn! !

!BitBltPure methodsFor: 'accessing' stamp: 'tfel 1/17/2014 19:47'!
unlockSurfaceFn: anObject

	unlockSurfaceFn := anObject! !

!BitBltPure methodsFor: 'accessing' stamp: 'tfel 1/17/2014 19:47'!
vDir

	^ vDir! !

!BitBltPure methodsFor: 'accessing' stamp: 'tfel 1/17/2014 19:47'!
vDir: anObject

	vDir := anObject! !

!BitBltPure methodsFor: 'accessing' stamp: 'tfel 1/17/2014 19:47'!
warpAlignMask

	^ warpAlignMask! !

!BitBltPure methodsFor: 'accessing' stamp: 'tfel 1/17/2014 19:47'!
warpAlignMask: anObject

	warpAlignMask := anObject! !

!BitBltPure methodsFor: 'accessing' stamp: 'tfel 1/17/2014 19:47'!
warpAlignShift

	^ warpAlignShift! !

!BitBltPure methodsFor: 'accessing' stamp: 'tfel 1/17/2014 19:47'!
warpAlignShift: anObject

	warpAlignShift := anObject! !

!BitBltPure methodsFor: 'accessing' stamp: 'tfel 1/17/2014 19:47'!
warpBitShiftTable

	^ warpBitShiftTable! !

!BitBltPure methodsFor: 'accessing' stamp: 'tfel 1/17/2014 19:47'!
warpBitShiftTable: anObject

	warpBitShiftTable := anObject! !

!BitBltPure methodsFor: 'accessing' stamp: 'tfel 1/17/2014 19:47'!
warpSrcMask

	^ warpSrcMask! !

!BitBltPure methodsFor: 'accessing' stamp: 'tfel 1/17/2014 19:47'!
warpSrcMask: anObject

	warpSrcMask := anObject! !

!BitBltPure methodsFor: 'accessing' stamp: 'tfel 1/17/2014 19:47'!
warpSrcShift

	^ warpSrcShift! !

!BitBltPure methodsFor: 'accessing' stamp: 'tfel 1/17/2014 19:47'!
warpSrcShift: anObject

	warpSrcShift := anObject! !

!BitBltPure methodsFor: 'accessing' stamp: 'tfel 1/17/2014 19:47'!
width

	^ width! !

!BitBltPure methodsFor: 'accessing' stamp: 'tfel 1/17/2014 19:47'!
width: anObject

	width := anObject! !


!BitBltPure methodsFor: 'inner loop' stamp: 'tfel 1/18/2014 15:05'!
alphaSourceBlendBits16
	"This version assumes 
		combinationRule = 34
		sourcePixSize = 32
		destPixSize = 16
		sourceForm ~= destForm.
	"
	| srcIndex dstIndex sourceWord srcAlpha destWord deltaX deltaY 
	srcY dstY dstMask srcShift ditherBase ditherIndex ditherThreshold |

	deltaY := bbH + 1. "So we can pre-decrement"
	srcY := sy.
	dstY := dy.
	srcShift := (dx bitAnd: 1) * 16.
	destMSB ifTrue:[srcShift := 16 - srcShift].
	mask1 := 16rFFFF << (16 - srcShift).
	"This is the outer loop"
	[(deltaY := deltaY - 1) ~= 0] whileTrue:[
		srcIndex := sourceBits + (srcY * sourcePitch) + (sx * 4).
		dstIndex := destBits + (dstY * destPitch) + (dx // 2 * 4).
		ditherBase := (dstY bitAnd: 3) * 4.
		ditherIndex := (sx bitAnd: 3) - 1. "For pre-increment"
		deltaX := bbW + 1. "So we can pre-decrement"
		dstMask := mask1.
		dstMask = 16rFFFF ifTrue:[srcShift := 16] ifFalse:[srcShift := 0].

		"This is the inner loop"
		[(deltaX := deltaX - 1) ~= 0] whileTrue:[
			ditherThreshold := ditherMatrix4x4 at: ditherBase + (ditherIndex := ditherIndex + 1 bitAnd: 3) + 1.
			sourceWord := self srcLongAt: srcIndex.
			srcAlpha := sourceWord >> 24.


More information about the pypy-commit mailing list