[ANN] FreeType Plus release

Andrew Tween amtween at hotmail.com
Mon Apr 30 14:38:15 UTC 2007


Hi Damien,
----- Original Message ----- 
From: "Damien Pollet" <damien.pollet at gmail.com>
To: "The general-purpose Squeak developers list"
<squeak-dev at lists.squeakfoundation.org>
Sent: Monday, April 30, 2007 2:54 PM
Subject: Re: [ANN] FreeType Plus release


> On 29/04/07, Andrew Tween <amtween at hotmail.com> wrote:
> > This requires a modified BitBltPlugin. This is currently available for
> > Windows/Linux only, and is installed via the FreeType Plus (plugins
installer)
> > package. If anybody wishes to attempt compile it for Macs, then please let
me
> > know.
>
> I'd like to give this a try, where can I get the source ?

The required modifications to BitBltSimulation are in a changeset that I have
attached.

Cheers,
Andy
-------------- next part --------------
'From Squeak3.7 of ''4 September 2004'' [latest update: #5989] on 4 August 2006 at 10:49:42 am'!
InterpreterPlugin subclass: #BitBltSimulation
	instanceVariableNames: 'destForm sourceForm halftoneForm combinationRule destX destY width height sourceX sourceY clipX clipY clipWidth clipHeight 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 componentAlphaModeAlpha componentAlphaModeColor 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 EndOfRun FixedPt1 FormBitsIndex FormDepthIndex FormHeightIndex FormWidthIndex GreenIndex JitBltHookSize OpTable OpTableSize RedIndex '
	poolDictionaries: ''
	category: 'VMMaker-Interpreter'!

!BitBltSimulation methodsFor: 'combination rules' stamp: 'tween 7/23/2006 23:56'!
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
! !

!BitBltSimulation methodsFor: 'combination rules' stamp: 'tween 7/23/2006 23:11'!
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 |
	self inline: false.	"Do NOT inline this into optimized loops"
		
	alpha := sourceWord.
	alpha = 0 ifTrue:[^destinationWord].
	^self partitionedRgbComponentAlpha: sourceWord dest: destinationWord nBits: destDepth nPartitions: destPPW.! !

!BitBltSimulation methodsFor: 'combination rules' stamp: 'tween 7/23/2006 23:07'!
rgbComponentAlphaOLD: 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 |
	self inline: false.	"Do NOT inline this into optimized loops"
		
	alpha := sourceWord.
	alpha = 0 ifTrue:[^destinationWord].
	destDepth = 16 
		ifTrue:[
			"source word has already been converted to dest depth.
			convert source word from 16 bit to 32 bit word"
			alpha _ (self rgbMap16To32: alpha) bitOr: 16rFF000000]. 	
	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.
	b _ ((dstMask bitAnd: 255) * (255 - aB) >> 8) + ((srcColor bitAnd: 255) * aB >> 8).
	b > 255 ifTrue:[b _ 255].
	dstMask _ dstMask >> 8.
	srcColor _ srcColor >> 8.
	g _ ((dstMask bitAnd: 255) * (255 - aG) >> 8) + ((srcColor bitAnd: 255) * aG >> 8).
	g > 255 ifTrue:[g _ 255].
	dstMask _ dstMask >> 8.
	srcColor _ srcColor >> 8.
	r _ ((dstMask bitAnd: 255) * (255 - aR) >> 8) + ((srcColor bitAnd: 255) * aR >> 8).
	r > 255 ifTrue:[r _ 255].
	dstMask _ dstMask >> 8.
	srcColor _ srcColor >> 8.
	a _ ((dstMask bitAnd: 255) * (255 - aA) >> 8) + aA.
	a > 255 ifTrue:[a _ 255].
	answer := (((((a << 8) + r) << 8) + g) << 8) + b.
	destDepth = 16 
		ifTrue:["map answer from 32 bit back to 16 bit"
			answer _ self rgbMap: (answer bitAnd: 16rFFFFFF) from: 8 to: 5].
	^answer	! !

!BitBltSimulation methodsFor: 'combination rules' stamp: 'tween 7/24/2006 11:32'!
tryCopyingBitsQuickly
	"Shortcut for stuff that's being run from the balloon engine.
	Since we do this at each scan line we should avoid the expensive 
	setup for source and destination."
	self inline: true.
	"We need a source."
	noSource ifTrue:[^false].
	"We handle only combinationRule 34 and combinationRule 41"	
	(combinationRule = 34 or:[combinationRule = 41]) ifFalse:[^false].
	"We handle only sourceDepth 32"
	(sourceDepth = 32) ifFalse:[^false].
	"We don't handle overlaps"
	(sourceForm = destForm) ifTrue:[^false].
	(combinationRule = 41)
		ifTrue:[
			destDepth = 32 
				ifTrue:[
					self rgbComponentAlpha32.
					affectedL _ dx.
					affectedR _ dx + bbW.
					affectedT _ dy.
					affectedB _ dy + bbH.
					^true].
			destDepth = 16 
				ifTrue:[
					self rgbComponentAlpha16.
					affectedL _ dx.
					affectedR _ dx + bbW.
					affectedT _ dy.
					affectedB _ dy + bbH.
					^true].
			destDepth = 8 
				ifTrue:[
					self rgbComponentAlpha8.
					affectedL _ dx.
					affectedR _ dx + bbW.
					affectedT _ dy.
					affectedB _ dy + bbH.
					^true].
			^false].
	"We need at least 8bit deep dest forms"
	(destDepth < 8) ifTrue:[^false].
	"If 8bit, then we want a color map"
	(destDepth = 8 and:[(cmFlags bitAnd: ColorMapPresent) = 0]) ifTrue:[^false].
	destDepth = 32 
		ifTrue:[self alphaSourceBlendBits32].
	destDepth = 16
		ifTrue:[self alphaSourceBlendBits16].
	destDepth = 8
		ifTrue:[self alphaSourceBlendBits8].
	affectedL _ dx.
	affectedR _ dx + bbW.
	affectedT _ dy.
	affectedB _ dy + bbH.
	^true! !

!BitBltSimulation methodsFor: 'pixel mapping' stamp: 'tween 7/29/2006 08:57'!
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 |
	self inline: false.	"Do NOT inline this into optimized loops"
		
	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	! !

!BitBltSimulation methodsFor: 'setup' stamp: 'tween 7/28/2006 18:52'!
copyBitsLockedAndClipped
	"Perform the actual copyBits operation.
	Assume: Surfaces have been locked and clipping was performed."
	| done gammaLookupTableOop ungammaLookupTableOop |
	self inline: true.
	combinationRule = 41
		ifTrue:["fetch the forecolor into componentAlphaModeColor."
			componentAlphaModeAlpha _ 255.
			componentAlphaModeColor _ 16777215.
			gammaLookupTable _ nil.
			ungammaLookupTable _ nil.
			interpreterProxy methodArgumentCount >= 2
				ifTrue:[
					componentAlphaModeAlpha _ interpreterProxy stackIntegerValue: (interpreterProxy methodArgumentCount - 2).
					(interpreterProxy failed not)
						ifFalse: [^ interpreterProxy primitiveFail].
					componentAlphaModeColor _ interpreterProxy stackIntegerValue: (interpreterProxy methodArgumentCount - 1).
					(interpreterProxy failed not)
						ifFalse: [^ interpreterProxy primitiveFail].
					interpreterProxy methodArgumentCount = 4
						ifTrue:[
							gammaLookupTableOop _ interpreterProxy stackObjectValue: 1.
							(interpreterProxy isBytes: gammaLookupTableOop) 
								ifTrue:[gammaLookupTable _ interpreterProxy firstIndexableField: gammaLookupTableOop.].
							ungammaLookupTableOop _ interpreterProxy stackObjectValue: 0.
							(interpreterProxy isBytes: ungammaLookupTableOop) 
								ifTrue:[ungammaLookupTable _ interpreterProxy firstIndexableField: ungammaLookupTableOop]]]
				ifFalse:[
					interpreterProxy methodArgumentCount = 1
						ifTrue: [
							componentAlphaModeColor _ interpreterProxy stackIntegerValue: 0.
							(interpreterProxy failed not)
								ifFalse: [^ interpreterProxy primitiveFail]]
						ifFalse:[^ interpreterProxy primitiveFail]]].
	"Try a shortcut for stuff that should be run as quickly as possible"
 	done _ self tryCopyingBitsQuickly.
	done ifTrue:[^nil].

	(combinationRule = 30) | (combinationRule = 31) ifTrue:
		["Check and fetch source alpha parameter for alpha blend"
		interpreterProxy methodArgumentCount = 1
			ifTrue: [sourceAlpha _ interpreterProxy stackIntegerValue: 0.
					(interpreterProxy failed not and: [(sourceAlpha >= 0) & (sourceAlpha <= 255)])
						ifFalse: [^ interpreterProxy primitiveFail]]
			ifFalse: [^ interpreterProxy primitiveFail]].

	bitCount _ 0.
	"Choose and perform the actual copy loop."
	self performCopyLoop.

	(combinationRule = 22) | (combinationRule = 32) ifTrue:
		["zero width and height; return the count"
		affectedL _ affectedR _ affectedT _ affectedB _ 0]. 
	hDir > 0
		ifTrue: [affectedL _ dx.
				affectedR _ dx + bbW]
		ifFalse: [affectedL _ dx - bbW + 1.
				affectedR _ dx + 1].
	vDir > 0
		ifTrue: [affectedT _ dy.
				affectedB _ dy + bbH]
		ifFalse: [affectedT _ dy - bbH + 1.
				affectedB _ dy + 1]! !

!BitBltSimulation methodsFor: 'inner loop' stamp: 'tween 7/24/2006 11:07'!
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 |
	self inline: false. "This particular method should be optimized in itself"
	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).
			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.
	].! !

!BitBltSimulation methodsFor: 'inner loop' stamp: 'tween 7/24/2006 10:37'!
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 |
	self inline: false. "This particular method should be optimized in itself"

	"Give the compile a couple of hints"
	self var: #sourceWord declareC:'register int sourceWord'.
	self var: #deltaX declareC:'register int deltaX'.

	"The following should be declared as pointers so the compiler will
	notice that they're used for accessing memory locations 
	(good to know on an Intel architecture) but then the increments
	would be different between ST code and C code so must hope the
	compiler notices what happens (MS Visual C does)"
	self var: #srcIndex declareC:'register int srcIndex'.
	self var: #dstIndex declareC:'register int dstIndex'.

	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.
	].! !

!BitBltSimulation methodsFor: 'inner loop' stamp: 'tween 7/24/2006 11:44'!
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 |
	self inline: false. "This particular method should be optimized in itself"
	self var: #mappingTable declareC:'unsigned int *mappingTable'.
	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.
	].! !

!BitBltSimulation methodsFor: 'initialize-release' stamp: 'tween 2/26/2006 14:59'!
initBBOpTable
	self cCode: 'opTable[0+1] = (int)clearWordwith'.
	self cCode: 'opTable[1+1] = (int)bitAndwith'.
	self cCode: 'opTable[2+1] = (int)bitAndInvertwith'.
	self cCode: 'opTable[3+1] = (int)sourceWordwith'.
	self cCode: 'opTable[4+1] = (int)bitInvertAndwith'.
	self cCode: 'opTable[5+1] = (int)destinationWordwith'.
	self cCode: 'opTable[6+1] = (int)bitXorwith'.
	self cCode: 'opTable[7+1] = (int)bitOrwith'.
	self cCode: 'opTable[8+1] = (int)bitInvertAndInvertwith'.
	self cCode: 'opTable[9+1] = (int)bitInvertXorwith'.
	self cCode: 'opTable[10+1] = (int)bitInvertDestinationwith'.
	self cCode: 'opTable[11+1] = (int)bitOrInvertwith'.
	self cCode: 'opTable[12+1] = (int)bitInvertSourcewith'.
	self cCode: 'opTable[13+1] = (int)bitInvertOrwith'.
	self cCode: 'opTable[14+1] = (int)bitInvertOrInvertwith'.
	self cCode: 'opTable[15+1] = (int)destinationWordwith'.
	self cCode: 'opTable[16+1] = (int)destinationWordwith'.
	self cCode: 'opTable[17+1] = (int)destinationWordwith'.
	self cCode: 'opTable[18+1] = (int)addWordwith'.
	self cCode: 'opTable[19+1] = (int)subWordwith'.
	self cCode: 'opTable[20+1] = (int)rgbAddwith'.
	self cCode: 'opTable[21+1] = (int)rgbSubwith'.
	self cCode: 'opTable[22+1] = (int)OLDrgbDiffwith'.
	self cCode: 'opTable[23+1] = (int)OLDtallyIntoMapwith'.
	self cCode: 'opTable[24+1] = (int)alphaBlendwith'.
	self cCode: 'opTable[25+1] = (int)pixPaintwith'.
	self cCode: 'opTable[26+1] = (int)pixMaskwith'.
	self cCode: 'opTable[27+1] = (int)rgbMaxwith'.
	self cCode: 'opTable[28+1] = (int)rgbMinwith'.
	self cCode: 'opTable[29+1] = (int)rgbMinInvertwith'.
	self cCode: 'opTable[30+1] = (int)alphaBlendConstwith'.
	self cCode: 'opTable[31+1] = (int)alphaPaintConstwith'.
	self cCode: 'opTable[32+1] = (int)rgbDiffwith'.
	self cCode: 'opTable[33+1] = (int)tallyIntoMapwith'.
	self cCode: 'opTable[34+1] = (int)alphaBlendScaledwith'.
	self cCode: 'opTable[35+1] = (int)alphaBlendScaledwith'.
	self cCode: 'opTable[36+1] = (int)alphaBlendScaledwith'.	
	self cCode: 'opTable[37+1] = (int)rgbMulwith'.
	self cCode: 'opTable[38+1] = (int)pixSwapwith'.
	self cCode: 'opTable[39+1] = (int)pixClearwith'.
	self cCode: 'opTable[40+1] = (int)fixAlphawith'.
	self cCode: 'opTable[41+1] = (int)rgbComponentAlphawith'.
	! !


!BitBltSimulation class methodsFor: 'initialization' stamp: 'tween 2/26/2006 14:53'!
initializeRuleTable
	"BitBltSimulation initializeRuleTable"
	"**WARNING** You MUST change initBBOpTable if you change this"
	OpTable _ #(
		"0" clearWord:with:
		"1" bitAnd:with:
		"2" bitAndInvert:with:
		"3" sourceWord:with:
		"4" bitInvertAnd:with:
		"5" destinationWord:with:
		"6" bitXor:with:
		"7" bitOr:with:
		"8" bitInvertAndInvert:with:
		"9" bitInvertXor:with:
		"10" bitInvertDestination:with:
		"11" bitOrInvert:with:
		"12" bitInvertSource:with:
		"13" bitInvertOr:with:
		"14" bitInvertOrInvert:with:
		"15" destinationWord:with:
		"16" destinationWord:with: "unused - was old paint"
		"17" destinationWord:with: "unused - was old mask"
		"18" addWord:with:
		"19" subWord:with:
		"20" rgbAdd:with:
		"21" rgbSub:with:
		"22" OLDrgbDiff:with:
		"23" OLDtallyIntoMap:with:
		"24" alphaBlend:with:
		"25" pixPaint:with:
		"26" pixMask:with:
		"27" rgbMax:with:
		"28" rgbMin:with:
		"29" rgbMinInvert:with:
		"30" alphaBlendConst:with:
		"31" alphaPaintConst:with:
		"32" rgbDiff:with:
		"33" tallyIntoMap:with:
		"34" alphaBlendScaled:with:

		"35" alphaBlendScaled:with:	"unused here - only used by FXBlt"
		"36" alphaBlendScaled:with:	"unused here - only used by FXBlt"
		"37" rgbMul:with:
		"38" pixSwap:with:
		"39" pixClear:with:
		"40" fixAlpha:with:
		"41" rgbComponentAlpha:with:
	).
	OpTableSize _ OpTable size + 1.  "0-origin indexing"
! !

!BitBltSimulation class methodsFor: 'translation' stamp: 'tween 7/28/2006 19:15'!
declareCVarsIn: aCCodeGenerator
	aCCodeGenerator var: 'opTable'
		declareC: 'int 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' 
		declareC:'int *cmShiftTable'.
	aCCodeGenerator var:'cmMaskTable' 
		declareC:'unsigned int *cmMaskTable'.
	aCCodeGenerator var:'cmLookupTable' 
		declareC:'unsigned int *cmLookupTable'.

	aCCodeGenerator var: 'dither8Lookup'
		declareC:' unsigned char dither8Lookup[4096]'.
	aCCodeGenerator var:'ungammaLookupTable' 
		declareC:'unsigned char *ungammaLookupTable'.
	aCCodeGenerator var:'gammaLookupTable' 
		declareC:'unsigned char *gammaLookupTable'.
! !

BitBltSimulation removeSelector: #partitionedRgbComponentAlpha:from:nBits:nPartitions:!
InterpreterPlugin subclass: #BitBltSimulation
	instanceVariableNames: 'destForm sourceForm halftoneForm combinationRule destX destY width height sourceX sourceY clipX clipY clipWidth clipHeight 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 gammaLookupTable ungammaLookupTable'
	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 EndOfRun FixedPt1 FormBitsIndex FormDepthIndex FormHeightIndex FormWidthIndex GreenIndex JitBltHookSize OpTable OpTableSize RedIndex'
	poolDictionaries: ''
	category: 'VMMaker-Interpreter'!


More information about the Squeak-dev mailing list