[squeak-dev] The Inbox: Graphics-wiz.183.mcz

Bert Freudenberg bert at freudenbergs.de
Tue May 24 09:47:42 UTC 2011


Hi Jerome,

since BitBlt only works on integer coordinates anyway, and even accepts nil instead ints, why should you want to spend all that effort of converting Fractions to Floats?

E.g., in loadBitBltFrom:warping: you will find

	destX := self fetchIntOrFloat: BBDestXIndex ofObject: bitBltOop ifNil: 0.

And looking at that method:

fetchIntOrFloat: fieldIndex ofObject: objectPointer ifNil: defaultValue
	"Return the integer value of the given field of the given object. If the field contains a Float, truncate it and return its integral part. Fail if the given field does not contain a small integer or Float, or if the truncated Float is out of the range of small integers."

So it only uses an Integer, but accepts a Float which will be truncated.

The only reason BitBlt accepts Floats in addition to Integers is to avoid having to sprinkle "rounded" sends everywhere. 

Sorry for not mentioning this earlier, but I thought this was obvious. There are no half pixels.

- Bert -


On 24.05.2011, at 00:47, commits at source.squeak.org wrote:

> A new version of Graphics was added to project The Inbox:
> http://source.squeak.org/inbox/Graphics-wiz.183.mcz
> 
> ==================== Summary ====================
> 
> Name: Graphics-wiz.183
> Author: wiz
> Time: 23 May 2011, 8:55:06.627 pm
> UUID: de71490d-a20e-4413-b8b0-8bc9ae3bfdb9
> Ancestors: Graphics-nice.182
> 
> The last of three pieces fixing M7635.
> 
> adjustOrigins and adjustExtent assure parameters are defined and not in class Fraction form.
> clipRange has had lazy initialization factored out by useing the adjust methods.
> copyBits now tries the two adjust methods before trying cliprange. It also now tries clipRange without the horrible roundVariables method. As a last resort it sends and error method before proceeding to try the roundVariables method.
> 
> That should do it.
> 
> Oh yeah be sure to load the other two parts first. Everything will depend on the presense of asNonFraction.
> 
> =============== Diff against Graphics-nice.182 ===============
> 
> Item was added:
> + ----- Method: BitBlt>>adjustExtents (in category 'accessing') -----
> + adjustExtents
> + "Answer if any of the extent numbers were class fraction or undefined. 
> + Assure all  extent numbers are  defined and non-fractional."
> + 
> + 	| answer |
> + 	(answer := width isFraction | height isFraction | clipWidth isFraction | clipHeight isFraction
> + 	| width isNil | height isNil | clipWidth isNil | clipHeight isNil) ifFalse: [ ^answer ] .
> + 	width := ( width ifNil: [ destForm width ] ) asNonFraction .
> + 	height := ( height ifNil: [ destForm height ] ) asNonFraction .
> + 	clipWidth := (clipWidth ifNil:[clipWidth := destForm width]) asNonFraction .
> + 	clipHeight := (clipHeight ifNil:[clipHeight := destForm height]) asNonFraction .
> + 	^answer !
> 
> Item was added:
> + ----- Method: BitBlt>>adjustOrigins (in category 'accessing') -----
> + adjustOrigins
> + "Answer if any of the origin numbers were class Fraction or undefined. Assure all  origin numbers are non-fractional and defined."
> + 
> + 	| answer |
> + 	(answer := destX isFraction 	| destY isFraction 
> + 				| sourceX isFraction | sourceY isFraction
> + 				| clipX isFraction 	| clipY isFraction
> + 				| destX isNil 		| destY isNil 
> + 				| sourceX isNil		| sourceY isNil
> + 				| clipX isNil 			| clipY isNil ) 
> + 					ifFalse: [ ^answer ] .
> + 	
> + 	destX :=( destX ifNil:[ 0]) asNonFraction .
> + 	destY := (destY  ifNil:[ 0]) asNonFraction .
> + 	sourceX := (sourceX  ifNil:[ 0]) asNonFraction .
> + 	sourceY := (sourceY  ifNil:[ 0]) asNonFraction .
> + 	clipX := (clipX  ifNil:[0]) asNonFraction .
> + 	clipY := (clipY  ifNil:[0]) asNonFraction .
> + 	^ answer!
> 
> Item was changed:
>  ----- Method: BitBlt>>clipRange (in category 'private') -----
>  clipRange
> + 	"Fill in the lazy state if needed and insure no numbers are class Fraction.
> + 	Clip and adjust source origin and extent appropriately"
> + 	
> - 	"clip and adjust source origin and extent appropriately"
> - 	"first in x"
>  	| sx sy dx dy bbW bbH |
> + 	self adjustExtents | self adjustOrigins . "True when something changed."
> - 	"fill in the lazy state if needed"
> - 	destX ifNil:[destX := 0].
> - 	destY ifNil:[destY := 0].
> - 	width ifNil:[width := destForm width].
> - 	height ifNil:[height := destForm height].
> - 	sourceX ifNil:[sourceX := 0].
> - 	sourceY ifNil:[sourceY := 0].
> - 	clipX ifNil:[clipX := 0].
> - 	clipY ifNil:[clipY := 0].
> - 	clipWidth ifNil:[clipWidth := destForm width].
> - 	clipHeight ifNil:[clipHeight := destForm height].
> 
> + 	"first in x"
>  	destX >= clipX
>  		ifTrue: [sx := sourceX.
>  				dx := destX.
>  				bbW := width]
>  		ifFalse: [sx := sourceX + (clipX - destX).
>  				bbW := width - (clipX - destX).
>  				dx := clipX].
>  	(dx + bbW) > (clipX + clipWidth)
>  		ifTrue: [bbW := bbW - ((dx + bbW) - (clipX + clipWidth))].
>  	"then in y"
>  	destY >= clipY
>  		ifTrue: [sy := sourceY.
>  				dy := destY.
>  				bbH := height]
>  		ifFalse: [sy := sourceY + clipY - destY.
>  				bbH := height - (clipY - destY).
>  				dy := clipY].
>  	(dy + bbH) > (clipY + clipHeight)
>  		ifTrue: [bbH := bbH - ((dy + bbH) - (clipY + clipHeight))].
>  	sourceForm ifNotNil:[
>  		sx < 0
>  			ifTrue: [dx := dx - sx.
>  					bbW := bbW + sx.
>  					sx := 0].
>  		sx + bbW > sourceForm width
>  			ifTrue: [bbW := bbW - (sx + bbW - sourceForm width)].
>  		sy < 0
>  			ifTrue: [dy := dy - sy.
>  					bbH := bbH + sy.
>  					sy := 0].
>  		sy + bbH > sourceForm height
>  			ifTrue: [bbH := bbH - (sy + bbH - sourceForm height)].
>  	].
>  	(bbW <= 0 or:[bbH <= 0]) ifTrue:[
>  		sourceX := sourceY := destX := destY := clipX := clipY := width := height := 0.
>  		^true].
>  	(sx = sourceX 
>  		and:[sy = sourceY 
>  		and:[dx = destX 
>  		and:[dy = destY 
>  		and:[bbW = width 
>  		and:[bbH = height]]]]]) ifTrue:[^false].
>  	sourceX := sx.
>  	sourceY := sy.
>  	destX := dx.
>  	destY := dy.
>  	width := bbW.
>  	height := bbH.
>  	^true!
> 
> Item was changed:
>  ----- Method: BitBlt>>copyBits (in category 'copying') -----
>  copyBits
>  	"Primitive. Perform the movement of bits from the source form to the 
>  	destination form. Fail if any variables are not of the right type (Integer, 
>  	Float, or Form) or if the combination rule is not implemented. 
>  	In addition to the original 16 combination rules, this BitBlt supports
>  	16	fail (to simulate paint)
>  	17	fail (to simulate mask)
>  	18	sourceWord + destinationWord
>  	19	sourceWord - destinationWord
>  	20	rgbAdd: sourceWord with: destinationWord
>  	21	rgbSub: sourceWord with: destinationWord
>  	22	rgbDiff: sourceWord with: destinationWord
>  	23	tallyIntoMap: destinationWord
>  	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
>  "
>  	<primitive: 'primitiveCopyBits' module: 'BitBltPlugin'>
> 
>  	"Check for compressed source, destination or halftone forms"
>  	(combinationRule >= 30 and: [combinationRule <= 31]) ifTrue:
>  		["No alpha specified -- re-run with alpha = 1.0"
>  		^ self copyBitsTranslucent: 255].
>  	((sourceForm isForm) and: [sourceForm unhibernate])
>  		ifTrue: [^ self copyBits].
>  	((destForm isForm) and: [destForm unhibernate])
>  		ifTrue: [^ self copyBits].
>  	((halftoneForm isForm) and: [halftoneForm unhibernate])
>  		ifTrue: [^ self copyBits].
> 
>  	"Check for unimplmented rules"
>  	combinationRule = Form oldPaint ifTrue: [^ self paintBits].
>  	combinationRule = Form oldErase1bitShape ifTrue: [^ self eraseBits].
> 
>  	"Check if BitBlt doesn't support full color maps"
>  	(colorMap notNil and:[colorMap isColormap]) ifTrue:[
>  		colorMap := colorMap colors.
>  		^self copyBits].
> + 	"Check for class Fraction numbers and undefined paramenters."
> + 	self adjustExtents ifTrue: [ ^self copyBits ].
> + 	self adjustOrigins ifTrue: [ ^self copyBits ].
> + 	
>  	"Check if clipping gots us way out of range"
> + 	self clipRange ifTrue:[ ^self copyBits].
> - 	self clipRange ifTrue:[self roundVariables. ^self copyBitsAgain].
> 
> + 	self error: 'Bad BitBlt arg; proceed to round args..'.
> - 	self error: 'Bad BitBlt arg (Fraction?); proceed to convert.'.
>  	"Convert all numeric parameters to integers and try again."
>  	self roundVariables.
>  	^ self copyBitsAgain!
> 
> 




More information about the Squeak-dev mailing list