[Vm-dev] VM Maker: VMMaker.oscog-eem.3065.mcz

commits at source.squeak.org commits at source.squeak.org
Fri Sep 10 00:31:54 UTC 2021


Eliot Miranda uploaded a new version of VMMaker to project VM Maker:
http://source.squeak.org/VMMaker/VMMaker.oscog-eem.3065.mcz

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

Name: VMMaker.oscog-eem.3065
Author: eem
Time: 9 September 2021, 5:31:43.856202 pm
UUID: 7bb2b446-a76e-44ac-959a-e611865ad123
Ancestors: VMMaker.oscog-eem.3064

BitBlt & B2D Plugins:
clean up typed variable declarations and coercions to use strings for variable names and symbols for types.

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

Item was changed:
  ----- Method: BalloonEngineBase>>colorTransform (in category 'accessing state') -----
  colorTransform
  	<returnTypeC:'float *'>
+ 	^self cCoerce: workBuffer + GWColorTransform to: #'float *'!
- 	^self cCoerce: workBuffer + GWColorTransform to:'float *'!

Item was changed:
  ----- Method: BalloonEngineBase>>edgeTransform (in category 'accessing state') -----
  edgeTransform
  	<returnTypeC:'float *'>
+ 	^self cCoerce: workBuffer + GWEdgeTransform to: #'float *'!
- 	^self cCoerce: workBuffer + GWEdgeTransform to:'float *'!

Item was changed:
  ----- Method: BalloonEngineBase>>fillBitmapSpan:from:to: (in category 'displaying') -----
  fillBitmapSpan: bits from: leftX to: rightX
  	"Fill the span buffer between leftEdge and rightEdge using the given bits.
  	Note: We always start from zero - this avoids using huge bitmap buffers if the bitmap is to be displayed at the very far right hand side and also gives us a chance of using certain bitmaps (e.g., those with depth 32) directly."
  	| x0 x1 x bitX colorMask colorShift baseShift fillValue |
  	<inline: false>
+ 	<var: 'bits' type: #'int *'>
- 	<var: #bits type:'int *'>
  
  	x0 := leftX.
  	x1 := rightX.
  	bitX := -1. "Hack for pre-increment"
  	self aaLevelGet = 1 ifTrue:["Speedy version for no anti-aliasing"
  		[x0 < x1] whileTrue:[
+ 			fillValue := (self cCoerce: bits to: #'int *') at: (bitX := bitX + 1).
- 			fillValue := (self cCoerce: bits to: 'int *') at: (bitX := bitX + 1).
  			spanBuffer at: x0 put: fillValue.
  			x0 := x0 + 1.
  		].
  	] ifFalse:["Generic version with anti-aliasing"
  		colorMask := self aaColorMaskGet.
  		colorShift := self aaColorShiftGet.
  		baseShift := self aaShiftGet.
  		[x0 < x1] whileTrue:[
  			x := x0 >> baseShift.
+ 			fillValue := (self cCoerce: bits to: #'int *') at: (bitX := bitX + 1).
- 			fillValue := (self cCoerce: bits to: 'int *') at: (bitX := bitX + 1).
  			fillValue := (fillValue bitAnd: colorMask) >> colorShift.
  			spanBuffer at: x put: (spanBuffer at: x) + fillValue.
  			x0 := x0 + 1.
  		].
  	].
  	x1 > self spanEndGet ifTrue:[self spanEndPut: x1].
  	x1 > self spanEndAAGet ifTrue:[self spanEndAAPut: x1].!

Item was changed:
  ----- Method: BalloonEngineBase>>fillSorts:before: (in category 'FILL processing') -----
  fillSorts: fillEntry1 before: fillEntry2
  	"Return true if fillEntry1 should be drawn before fillEntry2"
  	| diff |
  	<inline: false>
  	"First check the depth value"
  	diff := (self stackFillDepth: fillEntry1) - (self stackFillDepth: fillEntry2).
  	diff = 0 ifFalse:[^diff > 0].
  	"See the class comment for aetScanningProblems"
+ 	^(self cCoerce: (self makeUnsignedFrom: (self stackFillValue: fillEntry1)) to: #unsigned) <
+ 		(self cCoerce: (self makeUnsignedFrom: (self stackFillValue: fillEntry2)) to: #unsigned)!
- 	^(self cCoerce: (self makeUnsignedFrom: (self stackFillValue: fillEntry1)) to:'unsigned') <
- 		(self cCoerce: (self makeUnsignedFrom: (self stackFillValue: fillEntry2)) to: 'unsigned')!

Item was changed:
  ----- Method: BalloonEngineBase>>fillSpan:from:to: (in category 'displaying') -----
  fillSpan: fill from: leftX to: rightX
  	"Fill the span buffer from leftX to rightX with the given fill.
  	Clip before performing any operations. Return true if the fill must
  	be handled by some Smalltalk code."
  	| x0 x1 type |
+ 	<var: 'fill' type: #'unsigned int'>
- 	<var: #fill type: 'unsigned int'>
  	<inline: false>
  	fill = 0 ifTrue:[^false]. "Nothing to do"
  	"Start from spEnd - we must not paint pixels twice at a scan line"
  	leftX < self spanEndAAGet 
  		ifTrue:[x0 := self spanEndAAGet]
  		ifFalse:[x0 := leftX].
  	rightX > (self spanSizeGet << self aaShiftGet) 
  		ifTrue:[x1 := (self spanSizeGet << self aaShiftGet)]
  		ifFalse:[x1 := rightX].
  
  	"Clip left and right values"
  	x0 < self fillMinXGet ifTrue:[x0 := self fillMinXGet].
  	x1 > self fillMaxXGet ifTrue:[x1 := self fillMaxXGet].
  
  	"Adjust start and end values of span"
  	x0 < self spanStartGet ifTrue:[self spanStartPut: x0].
  	x1 > self spanEndGet ifTrue:[self spanEndPut: x1].
  	x1 > self spanEndAAGet ifTrue:[self spanEndAAPut: x1].
  
  	x0 >= x1 ifTrue:[^false]. "Nothing to do"
  
  	(self isFillColor: fill) ifTrue:[
  		self fillColorSpan: fill from: x0 to: x1.
  	] ifFalse:[
  		"Store the values for the dispatch"
  		self lastExportedFillPut: fill.
  		self lastExportedLeftXPut: x0.
  		self lastExportedRightXPut: x1.
  		type := self fillTypeOf: fill.
  		type <= 1 ifTrue:[^true].
  		self dispatchOn: type in: FillTable.
  	].
  	^false!

Item was changed:
  ----- Method: BalloonEngineBase>>incrementPoint:by: (in category 'transforming') -----
  incrementPoint: point by: delta
+ 	<var: 'point' type: #'int *'>
- 	<var: #point type:'int *'>
  	point at: 0 put: (point at: 0) + delta.
  	point at: 1 put: (point at: 1) + delta.!

Item was changed:
  ----- Method: BalloonEngineBase>>initColorTransform (in category 'other') -----
  initColorTransform
  	| transform |
  	<inline: false>
+ 	<var: 'transform' type: #'float *'>
- 	<var: #transform type:'float *'>
  	transform := self colorTransform.
+ 	transform at: 0 put: (self cCoerce: 1.0 to: #float).
+ 	transform at: 1 put: (self cCoerce: 0.0 to: #float).
+ 	transform at: 2 put: (self cCoerce: 1.0 to: #float).
+ 	transform at: 3 put: (self cCoerce: 0.0 to: #float).
+ 	transform at: 4 put: (self cCoerce: 1.0 to: #float).
+ 	transform at: 5 put: (self cCoerce: 0.0 to: #float).
+ 	transform at: 6 put: (self cCoerce: 1.0 to: #float).
+ 	transform at: 7 put: (self cCoerce: 0.0 to: #float).
- 	transform at: 0 put: (self cCoerce: 1.0 to: 'float').
- 	transform at: 1 put: (self cCoerce: 0.0 to: 'float').
- 	transform at: 2 put: (self cCoerce: 1.0 to: 'float').
- 	transform at: 3 put: (self cCoerce: 0.0 to: 'float').
- 	transform at: 4 put: (self cCoerce: 1.0 to: 'float').
- 	transform at: 5 put: (self cCoerce: 0.0 to: 'float').
- 	transform at: 6 put: (self cCoerce: 1.0 to: 'float').
- 	transform at: 7 put: (self cCoerce: 0.0 to: 'float').
  	self hasColorTransformPut: 0.!

Item was changed:
  ----- Method: BalloonEngineBase>>initEdgeTransform (in category 'other') -----
  initEdgeTransform
  	| transform |
  	<inline: false>
+ 	<var: 'transform' type: #'float *'>
- 	<var: #transform type:'float *'>
  	transform := self edgeTransform.
+ 	transform at: 0 put: (self cCoerce: 1.0 to: #float).
+ 	transform at: 1 put: (self cCoerce: 0.0 to: #float).
+ 	transform at: 2 put: (self cCoerce: 0.0 to: #float).
+ 	transform at: 3 put: (self cCoerce: 0.0 to: #float).
+ 	transform at: 4 put: (self cCoerce: 1.0 to: #float).
+ 	transform at: 5 put: (self cCoerce: 0.0 to: #float).
- 	transform at: 0 put: (self cCoerce: 1.0 to: 'float').
- 	transform at: 1 put: (self cCoerce: 0.0 to: 'float').
- 	transform at: 2 put: (self cCoerce: 0.0 to: 'float').
- 	transform at: 3 put: (self cCoerce: 0.0 to: 'float').
- 	transform at: 4 put: (self cCoerce: 1.0 to: 'float').
- 	transform at: 5 put: (self cCoerce: 0.0 to: 'float').
  	self hasEdgeTransformPut: 0.!

Item was changed:
  ----- Method: BalloonEngineBase>>loadArrayTransformFrom:into:length: (in category 'loading state') -----
  loadArrayTransformFrom: transformOop into: destPtr length: n
  	"Load a transformation from the given array."
  	| value |
  	<inline: false>
+ 	<var: 'destPtr' type: #'float *'>
- 	<var: #destPtr type:'float *'>
  	0 to: n-1 do:[:i|
  		value := interpreterProxy fetchPointer: i ofObject: transformOop.
  		((interpreterProxy isIntegerObject: value) or:[interpreterProxy isFloatObject: value])
  			ifFalse:[^interpreterProxy primitiveFail].
  		(interpreterProxy isIntegerObject: value)
  			ifTrue:[destPtr at: i put: 
+ 				(self cCoerce: (interpreterProxy integerValueOf: value) asFloat to: #float)]
- 				(self cCoerce: (interpreterProxy integerValueOf: value) asFloat to:'float')]
  			ifFalse:[destPtr at: i put: 
+ 				(self cCoerce: (interpreterProxy floatValueOf: value) to: #float)].
- 				(self cCoerce: (interpreterProxy floatValueOf: value) to: 'float')].
  	].!

Item was changed:
  ----- Method: BalloonEngineBase>>loadColorTransformFrom: (in category 'loading state') -----
  loadColorTransformFrom: transformOop
  	"Load a 2x3 transformation matrix from the given oop.
  	Return true if the matrix is not nil, false otherwise"
  	| okay transform |
+ 	<var: 'transform' type: #'float *'>
- 	<var: #transform type:'float *'>
  	transform := self colorTransform.
  	self hasColorTransformPut: 0.
  	okay := self loadTransformFrom: transformOop into: transform length: 8.
  	okay ifFalse:[^false].
  	self hasColorTransformPut: 1.
  	"Scale transform to be in 0-256 range"
+ 	transform at: 1 put: (transform at: 1) * (self cCoerce: 256.0 to: #float).
+ 	transform at: 3 put: (transform at: 3) * (self cCoerce: 256.0 to: #float).
+ 	transform at: 5 put: (transform at: 5) * (self cCoerce: 256.0 to: #float).
+ 	transform at: 7 put: (transform at: 7) * (self cCoerce: 256.0 to: #float).
- 	transform at: 1 put: (transform at: 1) * (self cCoerce: 256.0 to:'float').
- 	transform at: 3 put: (transform at: 3) * (self cCoerce: 256.0 to:'float').
- 	transform at: 5 put: (transform at: 5) * (self cCoerce: 256.0 to:'float').
- 	transform at: 7 put: (transform at: 7) * (self cCoerce: 256.0 to:'float').
  	^okay!

Item was changed:
  ----- Method: BalloonEngineBase>>loadEdgeTransformFrom: (in category 'loading state') -----
  loadEdgeTransformFrom: transformOop
  	"Load a 2x3 transformation matrix from the given oop.
  	Return true if the matrix is not nil, false otherwise"
  	| transform okay |
  	<inline: false>
+ 	<var: 'transform' type: #'float *'>
- 	<var: #transform type:'float *'>
  	self hasEdgeTransformPut: 0.
  	transform := self edgeTransform.
  	okay := self loadTransformFrom: transformOop into: transform length: 6.
  	interpreterProxy failed ifTrue:[^nil].
  	okay ifFalse:[^false].
  	self hasEdgeTransformPut: 1.
  	"Add the fill offset to the matrix"
  	transform at: 2 put: 
+ 		(self cCoerce: (transform at: 2) + self destOffsetXGet asFloat to: #float).
- 		(self cCoerce: (transform at: 2) + self destOffsetXGet asFloat to:'float').
  	transform at: 5 put: 
+ 		(self cCoerce: (transform at: 5) + self destOffsetYGet asFloat to: #float).
- 		(self cCoerce: (transform at: 5) + self destOffsetYGet asFloat to:'float').
  	^true!

Item was changed:
  ----- Method: BalloonEngineBase>>loadPoint:from: (in category 'loading state') -----
  loadPoint: pointArray from: pointOop
  	"Load the contents of pointOop into pointArray"
  	| value |
  	<inline: false>
+ 	<var: 'pointArray' type: #'int *'>
- 	<var: #pointArray type:'int *'>
  	(interpreterProxy fetchClassOf: pointOop) = interpreterProxy classPoint 
  		ifFalse:[^interpreterProxy primitiveFail].
  	value := interpreterProxy fetchPointer: 0 ofObject: pointOop.
  	((interpreterProxy isIntegerObject: value) or:[interpreterProxy isFloatObject: value])
  		ifFalse:[^interpreterProxy primitiveFail].
  	(interpreterProxy isIntegerObject: value)
  		ifTrue:[pointArray at: 0 put: (interpreterProxy integerValueOf: value)]
  		ifFalse:[pointArray at: 0 put: (interpreterProxy floatValueOf: value) asInteger].
  	value := interpreterProxy fetchPointer: 1 ofObject: pointOop.
  	((interpreterProxy isIntegerObject: value) or:[interpreterProxy isFloatObject: value])
  		ifFalse:[^interpreterProxy primitiveFail].
  	(interpreterProxy isIntegerObject: value)
  		ifTrue:[pointArray at: 1 put: (interpreterProxy integerValueOf: value)]
  		ifFalse:[pointArray at: 1 put: (interpreterProxy floatValueOf: value) asInteger].
  !

Item was changed:
  ----- Method: BalloonEngineBase>>loadTransformFrom:into:length: (in category 'loading state') -----
  loadTransformFrom: transformOop into: destPtr length: n
  	"Load a transformation from transformOop into the float array
  	defined by destPtr. The transformation is assumed to be either
  	an array or a FloatArray of length n."
  	<inline: false>
+ 	<var: 'destPtr' type: #'float *'>
- 	<var: #destPtr type:'float *'>
  	transformOop = interpreterProxy nilObject ifTrue:[^false].
  	(interpreterProxy isImmediate: transformOop)
  		ifTrue:[^interpreterProxy primitiveFail].
  	(interpreterProxy slotSizeOf: transformOop) = n 
  		ifFalse:[^interpreterProxy primitiveFail].
  	(interpreterProxy isWords: transformOop) 
  		ifTrue:[self loadWordTransformFrom: transformOop into: destPtr length: n]
  		ifFalse:[self loadArrayTransformFrom: transformOop into: destPtr length: n].
  	^true!

Item was changed:
  ----- Method: BalloonEngineBase>>loadWordTransformFrom:into:length: (in category 'loading state') -----
  loadWordTransformFrom: transformOop into: destPtr length: n
  	"Load a float array transformation from the given oop"
  	| srcPtr |
  	<inline: false>
+ 	<var: 'srcPtr' type: #'float *'>
+ 	<var: 'destPtr' type: #'float *'>
+ 	srcPtr := self cCoerce: (interpreterProxy firstIndexableField: transformOop) to: #'float *'.
- 	<var: #srcPtr type:'float *'>
- 	<var: #destPtr type:'float *'>
- 	srcPtr := self cCoerce: (interpreterProxy firstIndexableField: transformOop) to: 'float *'.
  	0 to: n-1 do:[:i| destPtr at: i put: (srcPtr at: i)].!

Item was changed:
  ----- Method: BalloonEngineBase>>moduleUnloaded: (in category 'initialize-release') -----
  moduleUnloaded: aModuleName
  	"The module with the given name was just unloaded.
  	Make sure we have no dangling references."
  	<export: true>
+ 	<var: 'aModuleName' type: #'char *'>
- 	<var: #aModuleName type: 'char *'>
  	(aModuleName strcmp: bbPluginName) = 0 ifTrue:[
  		"BitBlt just shut down. How nasty."
  		loadBBFn := 0.
  		copyBitsFn := 0.
  	].!

Item was changed:
  ----- Method: BalloonEngineBase>>point1Get (in category 'accessing state') -----
  point1Get
  	<returnTypeC:'int *'>
+ 	^self cCoerce: workBuffer + GWPoint1 to: #'int *'!
- 	^self cCoerce: workBuffer + GWPoint1 to:'int *'!

Item was changed:
  ----- Method: BalloonEngineBase>>point2Get (in category 'accessing state') -----
  point2Get
  	<returnTypeC:'int *'>
+ 	^self cCoerce: workBuffer + GWPoint2 to: #'int *'!
- 	^self cCoerce: workBuffer + GWPoint2 to:'int *'!

Item was changed:
  ----- Method: BalloonEngineBase>>point3Get (in category 'accessing state') -----
  point3Get
  	<returnTypeC:'int *'>
+ 	^self cCoerce: workBuffer + GWPoint3 to: #'int *'!
- 	^self cCoerce: workBuffer + GWPoint3 to:'int *'!

Item was changed:
  ----- Method: BalloonEngineBase>>point4Get (in category 'accessing state') -----
  point4Get
  	<returnTypeC:'int *'>
+ 	^self cCoerce: workBuffer + GWPoint4 to: #'int *'!
- 	^self cCoerce: workBuffer + GWPoint4 to:'int *'!

Item was changed:
  ----- Method: BalloonEngineBase>>primitiveCopyBuffer (in category 'primitives-other') -----
  primitiveCopyBuffer
  	| failCode buf1 buf2 diff src dst |
  	<export: true>
  	<inline: false>
+ 	<var: 'src' type: #'int *'>
+ 	<var: 'dst' type: #'int *'>
- 	<var: #src type:'int * '>
- 	<var: #dst type:'int * '>
  
  	interpreterProxy methodArgumentCount = 2
  		ifFalse:[^interpreterProxy primitiveFailFor: PrimErrBadNumArgs].
  
  	buf2 := interpreterProxy stackValue: 0.
  	buf1 := interpreterProxy stackValue: 1.
  	"Make sure the old buffer is properly initialized"
  	(failCode := self loadWorkBufferFrom: buf1) = 0
  		ifFalse:[^interpreterProxy primitiveFailFor: failCode].
  	"Make sure the buffers are of the same type"
  	(interpreterProxy fetchClassOf: buf1) = (interpreterProxy fetchClassOf: buf2)
  		ifFalse:[^interpreterProxy primitiveFailFor: GEFClassMismatch].
  	"Make sure buf2 is at least of the size of buf1"
  	diff := (interpreterProxy slotSizeOf: buf2) - (interpreterProxy slotSizeOf: buf1).
  	diff < 0 ifTrue:[^interpreterProxy primitiveFailFor: GEFSizeMismatch].
  
  	"Okay - ready for copying. First of all just copy the contents up to wbTop"
  	src := workBuffer.
  	dst := interpreterProxy firstIndexableField: buf2.
  	0 to: self wbTopGet-1 do:[:i|
  		dst at: i put: (src at: i).
  	].
  	"Adjust wbSize and wbTop in the new buffer"
  	dst at: GWBufferTop put: self wbTopGet + diff.
  	dst at: GWSize put: self wbSizeGet + diff.
  	"Now copy the entries from wbTop to wbSize"
  	src := src + self wbTopGet.
  	dst := dst + self wbTopGet + diff.
  	0 to: (self wbSizeGet - self wbTopGet - 1) do:[:i|
  		dst at: i put: (src at: i).
  	].
  	"Okay, done. Check the new buffer by loading the state from it"
  	(failCode := self loadWorkBufferFrom: buf2) = 0
  		ifFalse:[^interpreterProxy primitiveFailFor: failCode].
  	interpreterProxy pop: 2. "Leave rcvr on stack"
  !

Item was changed:
  ----- Method: BalloonEngineBase>>primitiveGetCounts (in category 'primitives-access') -----
  primitiveGetCounts
  	| failureCode statOop stats |
  	<export: true>
  	<inline: false>
+ 	<var: 'stats' type: #'int *'>
- 	<var: #stats type:'int *'>
  
  	interpreterProxy methodArgumentCount = 1
  		ifFalse:[^interpreterProxy primitiveFailFor: PrimErrBadNumArgs].
  
  	(failureCode := self quickLoadEngineFrom: (interpreterProxy stackValue: 1)) = 0
  		ifFalse:[^interpreterProxy primitiveFailFor: failureCode].
  
  	statOop := interpreterProxy stackObjectValue: 0.
  	(interpreterProxy failed not
  	and: [(interpreterProxy isWords: statOop)
  	and: [(interpreterProxy slotSizeOf: statOop) >= 9]])
  		ifFalse:[^interpreterProxy primitiveFailFor: PrimErrBadArgument].
  
  	stats := interpreterProxy firstIndexableField: statOop.
  	stats at: 0 put: (stats at: 0) + (workBuffer at: GWCountInitializing).
  	stats at: 1 put: (stats at: 1) + (workBuffer at: GWCountFinishTest).
  	stats at: 2 put: (stats at: 2) + (workBuffer at: GWCountNextGETEntry).
  	stats at: 3 put: (stats at: 3) + (workBuffer at: GWCountAddAETEntry).
  	stats at: 4 put: (stats at: 4) + (workBuffer at: GWCountNextFillEntry).
  	stats at: 5 put: (stats at: 5) + (workBuffer at: GWCountMergeFill).
  	stats at: 6 put: (stats at: 6) + (workBuffer at: GWCountDisplaySpan).
  	stats at: 7 put: (stats at: 7) + (workBuffer at: GWCountNextAETEntry).
  	stats at: 8 put: (stats at: 8) + (workBuffer at: GWCountChangeAETEntry).
  
  	interpreterProxy pop: 1. "Leave rcvr on stack"!

Item was changed:
  ----- Method: BalloonEngineBase>>primitiveGetTimes (in category 'primitives-access') -----
  primitiveGetTimes
  	| failureCode statOop stats |
  	<export: true>
  	<inline: false>
+ 	<var: 'stats' type: #'int *'>
- 	<var: #stats type:'int *'>
  
  	interpreterProxy methodArgumentCount = 1
  		ifFalse:[^interpreterProxy primitiveFailFor: PrimErrBadNumArgs].
  
  	(failureCode := self quickLoadEngineFrom: (interpreterProxy stackValue: 1)) = 0
  		ifFalse:[^interpreterProxy primitiveFailFor: failureCode].
  
  	statOop := interpreterProxy stackObjectValue: 0.
  	(interpreterProxy failed not
  	and: [(interpreterProxy isWords: statOop)
  	and: [(interpreterProxy slotSizeOf: statOop) >= 9]])
  		ifFalse:[^interpreterProxy primitiveFailFor: PrimErrBadArgument].
  
  	stats := interpreterProxy firstIndexableField: statOop.
  	stats at: 0 put: (stats at: 0) + (workBuffer at: GWTimeInitializing).
  	stats at: 1 put: (stats at: 1) + (workBuffer at: GWTimeFinishTest).
  	stats at: 2 put: (stats at: 2) + (workBuffer at: GWTimeNextGETEntry).
  	stats at: 3 put: (stats at: 3) + (workBuffer at: GWTimeAddAETEntry).
  	stats at: 4 put: (stats at: 4) + (workBuffer at: GWTimeNextFillEntry).
  	stats at: 5 put: (stats at: 5) + (workBuffer at: GWTimeMergeFill).
  	stats at: 6 put: (stats at: 6) + (workBuffer at: GWTimeDisplaySpan).
  	stats at: 7 put: (stats at: 7) + (workBuffer at: GWTimeNextAETEntry).
  	stats at: 8 put: (stats at: 8) + (workBuffer at: GWTimeChangeAETEntry).
  
  	interpreterProxy pop: 1. "Leave rcvr on stack"!

Item was changed:
  ----- Method: BalloonEngineBase>>primitiveSetBitBltPlugin (in category 'primitives-access') -----
  primitiveSetBitBltPlugin
  	"Primitive. Set the BitBlt plugin to use."
  	| pluginName length ptr needReload |
  	<export: true>
+ 	<var: 'ptr' type: #'char *'>
- 	<var: #ptr type:'char *'>
  	pluginName := interpreterProxy stackValue: 0.
  	"Must be string to work"
  	(interpreterProxy isBytes: pluginName) 
  		ifFalse:[^interpreterProxy primitiveFail].
  	length := interpreterProxy byteSizeOf: pluginName.
  	length >= 256 
  		ifTrue:[^interpreterProxy primitiveFail].
  	ptr := interpreterProxy firstIndexableField: pluginName.
  	needReload := false.
  	0 to: length-1 do:[:i|
  		"Compare and store the plugin to be used"
  		(bbPluginName at: i) = (ptr at: i) ifFalse:[
  			bbPluginName at: i put: (ptr at: i).
  			needReload := true]].
  	(bbPluginName at: length) = 0 ifFalse:[
  		bbPluginName at: length put: 0.
  		needReload := true].
  	needReload ifTrue:[
  		self initialiseModule 
  			ifFalse:[^interpreterProxy primitiveFail]].
  	interpreterProxy pop: 1. "Return receiver"!

Item was changed:
  ----- Method: BalloonEngineBase>>quickSortGlobalEdgeTable:from:to: (in category 'GET processing') -----
  quickSortGlobalEdgeTable: array from: i to: j 
  	"Sort elements i through j of self to be nondescending according to
  	sortBlock."
  	"Note: The original loop has been heavily re-written for C translation"
  	| di dij dj tt ij k l n tmp again before |
+ 	<var: 'array' type: #'int *'>
- 	<var: #array type:'int *'>
  	<inline: false>
  	"The prefix d means the data at that index."
  	(n := j + 1  - i) <= 1 ifTrue: [^0].	"Nothing to sort." 
  	 "Sort di,dj."
  	di := array at: i.
  	dj := array at: j.
  	before := self getSorts: di before: dj. "i.e., should di precede dj?"
  	before ifFalse:[
  		tmp := array at: i.
  		array at: i put: (array at: j).
  		array at: j put: tmp.
  		tt := di.	di := dj.	dj := tt].
  	n <= 2 ifTrue:[^0].
  
  	"More than two elements."
  	ij := (i + j) // 2.  "ij is the midpoint of i and j."
  	dij := array at: ij.  "Sort di,dij,dj.  Make dij be their median."
  	before := (self getSorts: di before: dij). "i.e. should di precede dij?"
  	before ifTrue:[
  		before := (self getSorts: dij before: dj). "i.e., should dij precede dj?"
  		before ifFalse:["i.e., should dij precede dj?"
  			tmp := array at: j.
  			array at: j put: (array at: ij).
  			array at: ij put: tmp.
  			dij := dj]
  	] ifFalse:[  "i.e. di should come after dij"
  		tmp := array at: i.
  		array at: i put: (array at: ij).
  		array at: ij put: tmp.
  		 dij := di].
  	n <= 3 ifTrue:[^0].
  
  	 "More than three elements."
  	"Find k>i and l<j such that dk,dij,dl are in reverse order.
  	Swap k and l.  Repeat this procedure until k and l pass each other."
  	k := i.
  	l := j.
  
  	again := true.
  	[again] whileTrue:[
  		before := true.
  		[before] whileTrue:[
  			k <= (l := l - 1)
  				ifTrue:[	tmp := array at: l.
  						before := self getSorts: dij before: tmp]
  				ifFalse:[before := false].
  		].
  		before := true.
  		[before] whileTrue:[
  			(k := k + 1) <= l
  				ifTrue:[	tmp := array at: k.
  						before := self getSorts: tmp before: dij]
  				ifFalse:[before := false]].
  
  		again := k <= l.
  		again ifTrue:[
  			tmp := array at: k.
  			array at: k put: (array at: l).
  			array at: l put: tmp]].
  
  	"Now l<k (either 1 or 2 less), and di through dl are all less than or equal to dk
  	through dj.  Sort those two segments."
  	self quickSortGlobalEdgeTable: array from: i to: l.
  	self quickSortGlobalEdgeTable: array from: k to: j.!

Item was changed:
  ----- Method: BalloonEngineBase>>smallSqrtTable (in category 'other') -----
  smallSqrtTable
  	| theTable |
  	<inline: false>
  	<returnTypeC:'int *'>
+ 	<var: 'theTable' declareC:'static int theTable[32] = 
- 	<var: #theTable declareC:'static int theTable[32] = 
  	{0, 1, 1, 2, 2, 2, 2, 3, 3, 3, 3, 3, 3, 4, 4, 4, 4, 4, 4, 4, 4, 5, 5, 5, 5, 5, 5, 5, 5, 5, 5, 6}'>
  	^theTable!

Item was changed:
  ----- Method: BalloonEngineBase>>transformColor: (in category 'transforming') -----
  transformColor: fillIndex
  	| r g b a transform alphaScale |
+ 	<var: 'transform' type: #'float *'>
+ 	<var: 'alphaScale' type: #double>
- 	<var: #transform type:'float *'>
- 	<var: #alphaScale type:'double '>
  	(fillIndex = 0 or:[self isFillColor: fillIndex]) ifFalse:[^fillIndex].
  	b := fillIndex bitAnd: 255.
  	g := (fillIndex >> 8) bitAnd: 255.
  	r := (fillIndex >> 16) bitAnd: 255.
  	a := (fillIndex >> 24) bitAnd: 255.
  	(self hasColorTransform) ifTrue:[
  		transform := self colorTransform.
  		alphaScale := (a * (transform at: 6) + (transform at: 7)) / a.
  		r := (r * (transform at: 0) + (transform at: 1) * alphaScale) asInteger.
  		g := (g * (transform at: 2) + (transform at: 3) * alphaScale) asInteger.
  		b := (b * (transform at: 4) + (transform at: 5) * alphaScale) asInteger.
  		a := a * alphaScale.
  		r := r max: 0. r := r min: 255.
  		g := g max: 0. g := g min: 255.
  		b := b max: 0. b := b min: 255.
  		a := a max: 0. a := a min: 255.
  	].
  	a < 1 ifTrue:[^0]."ALWAYS return zero for transparent fills"
  	"If alpha is not 255 (or close thereto) then we need to flush the engine before proceeding"
  	(a < 255 and:[self needsFlush]) 
  		ifTrue:[self stopBecauseOf: GErrorNeedFlush].
  	^b + (g << 8) + (r << 16) + (a << 24)!

Item was changed:
  ----- Method: BalloonEngineBase>>transformPoint: (in category 'transforming') -----
  transformPoint: point
  	"Transform the given point. If haveMatrix is true then use the current transformation."
+ 	<var:#point type: #'int *'>
- 	<var:#point type:'int *'>
  	self hasEdgeTransform ifFalse:[
  		"Multiply each component by aaLevel and add a half pixel"
  		point at: 0 put: (point at: 0) + self destOffsetXGet * self aaLevelGet.
  		point at: 1 put: (point at: 1) + self destOffsetYGet * self aaLevelGet.
  	] ifTrue:[
  		"Note: AA adjustment is done in #transformPoint: for higher accuracy"
  		self transformPoint: point into: point.
  	].!

Item was changed:
  ----- Method: BalloonEngineBase>>transformPoint:into: (in category 'transforming') -----
  transformPoint: srcPoint into: dstPoint
  	"Transform srcPoint into dstPoint by using the currently loaded matrix"
  	"Note: This method has been rewritten so that inlining works (e.g., removing
  	the declarations and adding argument coercions at the appropriate points)"
  	<inline: true>
+ 	self transformPointX: ((self cCoerce: srcPoint to: #'int *') at: 0) asFloat 
+ 		y: ((self cCoerce: srcPoint to: #'int *') at: 1) asFloat
+ 		into: (self cCoerce: dstPoint to: #'int *')!
- 	self transformPointX: ((self cCoerce: srcPoint to: 'int *') at: 0) asFloat 
- 		y: ((self cCoerce: srcPoint to:'int *') at: 1) asFloat
- 		into: (self cCoerce: dstPoint to: 'int *')!

Item was changed:
  ----- Method: BalloonEngineBase>>transformPointX:y:into: (in category 'transforming') -----
  transformPointX: xValue y: yValue into: dstPoint
  	"Transform srcPoint into dstPoint by using the currently loaded matrix"
  	"Note: This should be rewritten so that inlining works (e.g., removing
  	the declarations and adding argument coercions at the appropriate points)"
  	| x y transform |
  	<inline: true>
+ 	<var: 'dstPoint' type: #'int *'>
+ 	<var: 'xValue' type: #double>
+ 	<var: 'yValue' type: #double>
+ 	<var: 'transform' type: #'float *'>
- 	<var: #dstPoint type:'int *'>
- 	<var: #xValue type: 'double '>
- 	<var: #yValue type: 'double '>
- 	<var: #transform type:'float *'>
  	transform := self edgeTransform.
  	x := ((((transform at: 0) * xValue) +
  		((transform at: 1) * yValue) +
  		(transform at: 2)) * self aaLevelGet asFloat) asInteger.
  	y := ((((transform at: 3) * xValue) +
  		((transform at: 4) * yValue) +
  		(transform at: 5)) * self aaLevelGet asFloat) asInteger.
  	dstPoint at: 0 put: x.
  	dstPoint at: 1 put: y.!

Item was changed:
  ----- Method: BalloonEngineBase>>transformWidth: (in category 'transforming') -----
  transformWidth: w
  	"Transform the given width"
  	| deltaX deltaY dstWidth dstWidth2 |
  	<inline: false>
+ 	<var: 'deltaX' type: #double>
+ 	<var: 'deltaY' type: #double>
- 	<var: #deltaX type:'double '>
- 	<var: #deltaY type:'double '>
  	w = 0 ifTrue:[^0].
  	self point1Get at: 0 put: 0.
  	self point1Get at: 1 put: 0.
  	self point2Get at: 0 put: w * 256.
  	self point2Get at: 1 put: 0.
  	self point3Get at: 0 put: 0.
  	self point3Get at: 1 put: w * 256.
  	self transformPoints: 3.
  	deltaX := ((self point2Get at: 0) - (self point1Get at: 0)) asFloat.
  	deltaY := ((self point2Get at: 1) - (self point1Get at: 1)) asFloat.
  	dstWidth := (((deltaX * deltaX) + (deltaY * deltaY)) sqrt asInteger + 128) // 256.
  	deltaX := ((self point3Get at: 0) - (self point1Get at: 0)) asFloat.
  	deltaY := ((self point3Get at: 1) - (self point1Get at: 1)) asFloat.
  	dstWidth2 := (((deltaX * deltaX) + (deltaY * deltaY)) sqrt asInteger + 128) // 256.
  	dstWidth2 < dstWidth ifTrue:[dstWidth := dstWidth2].
  	dstWidth = 0
  		ifTrue:[^1]
  		ifFalse:[^dstWidth]!

Item was changed:
  ----- Method: BalloonEngineBase>>uncheckedTransformColor: (in category 'transforming') -----
  uncheckedTransformColor: fillIndex
  	| r g b a transform |
+ 	<var: 'transform' type: #'float *'>
- 	<var: #transform type:'float *'>
  	(self hasColorTransform) ifFalse:[^fillIndex].
  	b := fillIndex bitAnd: 255.
  	g := (fillIndex >> 8) bitAnd: 255.
  	r := (fillIndex >> 16) bitAnd: 255.
  	a := (fillIndex >> 24) bitAnd: 255.
  	transform := self colorTransform.
  	r := (r * (transform at: 0) + (transform at: 1)) asInteger.
  	g := (g * (transform at: 2) + (transform at: 3)) asInteger.
  	b := (b * (transform at: 4) + (transform at: 5)) asInteger.
  	a := (a * (transform at: 6) + (transform at: 7)) asInteger.
  	r := r max: 0. r := r min: 255.
  	g := g max: 0. g := g min: 255.
  	b := b max: 0. b := b min: 255.
  	a := a max: 0. a := a min: 255.
  	a < 16 ifTrue:[^0]."ALWAYS return zero for transparent fills"
  	^b + (g << 8) + (r << 16) + (a << 24)!

Item was changed:
  ----- Method: BalloonEnginePlugin>>allocateBitmapFill:colormap: (in category 'allocation') -----
  allocateBitmapFill: cmSize colormap: cmBits
  	| fill fillSize cm |
+ 	<var:#cm type: #'int *'>
+ 	<var:#cmBits type: #'int *'>
- 	<var:#cm type:'int *'>
- 	<var:#cmBits type:'int *'>
  	fillSize := GBMBaseSize + cmSize.
  	(self allocateObjEntry: fillSize) ifFalse:[^0].
  	fill := objUsed.
  	objUsed := fill + fillSize.
  	self objectTypeOf: fill put: GEPrimitiveClippedBitmapFill.
  	self objectIndexOf: fill put: 0.
  	self objectLengthOf: fill put: fillSize.
  	cm := self colormapOf: fill.
  	self hasColorTransform ifTrue:[
  		0 to: cmSize-1 do:[:i| cm at: i put: (self transformColor: (cmBits at: i))].
  	] ifFalse:[
  		0 to: cmSize-1 do:[:i| cm at: i put: (cmBits at: i)].
  	].
  	self bitmapCmSizeOf: fill put: cmSize.
  	^fill!

Item was changed:
  ----- Method: BalloonEnginePlugin>>allocateGradientFill:rampWidth:isRadial: (in category 'allocation') -----
  allocateGradientFill: ramp rampWidth: rampWidth isRadial: isRadial
  	| fill fillSize rampPtr |
+ 	<var:#ramp type: #'int *'>
+ 	<var:#rampPtr type: #'int *'>
- 	<var:#ramp type:'int *'>
- 	<var:#rampPtr type:'int *'>
  	fillSize := GGBaseSize + rampWidth.
  	(self allocateObjEntry: fillSize) ifFalse:[^0].
  	fill := objUsed.
  	objUsed := fill + fillSize.
  	isRadial
  		ifTrue:[self objectTypeOf: fill put: GEPrimitiveRadialGradientFill]
  		ifFalse:[self objectTypeOf: fill put: GEPrimitiveLinearGradientFill].
  	self objectIndexOf: fill put: 0.
  	self objectLengthOf: fill put: fillSize.
  	rampPtr := self gradientRampOf: fill.
  	self hasColorTransform ifTrue:[
  		0 to: rampWidth-1 do:[:i| rampPtr at: i put: (self transformColor: (ramp at: i))].
  	] ifFalse:[
  		0 to: rampWidth-1 do:[:i| rampPtr at: i put: (ramp at: i)].
  	].
  	self gradientRampLengthOf: fill put: rampWidth.
  	^fill!

Item was changed:
  ----- Method: BalloonEnginePlugin>>bitmapValue:bits:atX:y: (in category 'fills-bitmaps') -----
  bitmapValue: bmFill bits: bits atX: xp y: yp
  
  	| bmDepth bmRaster value rShift cMask r g b a |
  	<inline: true>
  
  	bmDepth := self bitmapDepthOf: bmFill.
  	bmRaster := self bitmapRasterOf: bmFill.
  	bmDepth = 32 ifTrue: [
+ 		value := (self cCoerce: bits to: #'int *') at: (bmRaster * yp) + xp.
- 		value := (self cCoerce: bits to: 'int *') at: (bmRaster * yp) + xp.
  		(value ~= 0 and: [(value bitAnd: 16rFF000000) = 0])
  				ifTrue: [value := value bitOr: 16rFF000000].
  		^self uncheckedTransformColor: value].
  	"rShift - shift value to convert from pixel to word index"
  	rShift := self rShiftTable at: bmDepth.
  	value := self makeUnsignedFrom: 
+ 		((self cCoerce: bits to: #'int *') at: (bmRaster * yp) + (xp >> rShift)).
- 		((self cCoerce: bits to: 'int *') at: (bmRaster * yp) + (xp >> rShift)).
  	"cMask - mask out the pixel from the word"
  	cMask := (1 << bmDepth) - 1.
  	"rShift - shift value to move the pixel in the word to the lowest bit position"
  	rShift := 32 - bmDepth - ((xp bitAnd: (1 << rShift - 1)) * bmDepth).
  	value := (value >> rShift) bitAnd: cMask.
  	bmDepth = 16 ifTrue: [
  		"Must convert by expanding bits"
  		value = 0 ifFalse: [
  			b := (value bitAnd: 31) << 3.		b := b + (b >> 5).
  			g := (value >> 5 bitAnd: 31) << 3.	g := g + (g >> 5).
  			r := (value >> 10 bitAnd: 31) << 3.	r := r + (r >> 5).
  			a := 255.
  			value := b + (g << 8) + (r << 16) + (a << 24)].
  	] ifFalse: [
  		"Must convert by using color map"
  		(self bitmapCmSizeOf: bmFill) = 0
  			ifTrue: [value := 0]
  			ifFalse: [value := self makeUnsignedFrom: ((self colormapOf: bmFill) at: value)].
  	].
  	^self uncheckedTransformColor: value!

Item was changed:
  ----- Method: BalloonEnginePlugin>>checkCompressedFillIndexList:max:segments: (in category 'shapes-compressed') -----
  checkCompressedFillIndexList: fillList max: maxIndex segments: nSegs
  	"Check the fill indexes in the run-length encoded fillList"
  	| length runLength runValue nFills fillPtr |
  	<inline: false>
+ 	<var: 'fillPtr' type: #'int *'>
- 	<var: #fillPtr type:'int *'>
  	length := interpreterProxy slotSizeOf: fillList.
  	fillPtr := interpreterProxy firstIndexableField: fillList.
  	nFills := 0.
  	0 to: length-1 do:[:i |
  		runLength := self shortRunLengthAt: i from: fillPtr.
  		runValue := self shortRunValueAt: i from: fillPtr.
  		(runValue >= 0 and:[runValue <= maxIndex]) ifFalse:[^false].
  		nFills := nFills + runLength.
  	].
  	^nFills = nSegs!

Item was changed:
  ----- Method: BalloonEnginePlugin>>checkCompressedFills: (in category 'shapes-compressed') -----
  checkCompressedFills: indexList
  	"Check if the indexList (containing fill handles) is okay."
  	| fillPtr length fillIndex |
  	<inline: false>
+ 	<var: 'fillPtr' type: #'int *'>
- 	<var: #fillPtr type:'int *'>
  	"First check if the oops have the right format"
  	(interpreterProxy isWords: indexList) ifFalse:[^false].
  
  	"Then check the fill entries"
  	length := interpreterProxy slotSizeOf: indexList.
  	fillPtr := interpreterProxy firstIndexableField: indexList.
  	0 to: length-1 do:[:i |
  		fillIndex := fillPtr at: i.
  		"Make sure the fill is okay"
  		(self isFillOkay: fillIndex) ifFalse:[^false]].
  
  	^ true!

Item was changed:
  ----- Method: BalloonEnginePlugin>>checkCompressedLineWidths:segments: (in category 'shapes-compressed') -----
  checkCompressedLineWidths: lineWidthList segments: nSegments
  	"Check the run-length encoded lineWidthList matches nSegments"
  	| length runLength nItems ptr |
  	<inline: false>
+ 	<var: 'ptr' type: #'int *'>
- 	<var: #ptr type:'int *'>
  	length := interpreterProxy slotSizeOf: lineWidthList.
  	ptr := interpreterProxy firstIndexableField: lineWidthList.
  	nItems := 0.
  	0 to: length-1 do:[:i|
  		runLength := self shortRunLengthAt: i from: ptr.
  		nItems := nItems + runLength.
  	].
  	^nItems = nSegments!

Item was changed:
  ----- Method: BalloonEnginePlugin>>computeBezier:splitAt: (in category 'bezier-loading') -----
  computeBezier: index splitAt: param
  	"Split the bezier curve at the given parametric value.
  	Note: Since this method is only invoked to make non-monoton
  		beziers monoton we must check for the resulting y values
  		to be *really* between the start and end value."
  	| startX startY viaX viaY endX endY newIndex 
  	leftViaX  leftViaY rightViaX rightViaY sharedX sharedY |
  	<inline: false>
+ 	<var: 'param' type: #double>
- 	<var: #param type:'double '>
  	leftViaX := startX := self bzStartX: index.
  	leftViaY := startY := self bzStartY: index.
  	rightViaX := viaX := self bzViaX: index.
  	rightViaY := viaY := self bzViaY: index.
  	endX := self bzEndX: index.
  	endY := self bzEndY: index.
  
  	"Compute intermediate points"
  	sharedX := leftViaX := leftViaX + ((viaX - startX) asFloat * param) asInteger.
  	sharedY := leftViaY := leftViaY + ((viaY - startY) asFloat * param) asInteger.
  	rightViaX := rightViaX + ((endX - viaX) asFloat * param) asInteger.
  	rightViaY := rightViaY + ((endY - viaY) asFloat * param) asInteger.
  	"Compute new shared point"
  	sharedX := sharedX + ((rightViaX - leftViaX) asFloat * param) asInteger.
  	sharedY := sharedY + ((rightViaY - leftViaY) asFloat * param) asInteger.
  
  	"Check the new via points"
  	leftViaY := self assureValue: leftViaY between: startY and: sharedY.
  	rightViaY := self assureValue: rightViaY between: sharedY and: endY.
  
  	newIndex := self allocateBezierStackEntry.
  	engineStopped ifTrue:[^0]. "Something went wrong"
  
  	"Store the first part back"
  	self bzViaX: index put: leftViaX.
  	self bzViaY: index put: leftViaY.
  	self bzEndX: index put: sharedX.
  	self bzEndY: index put: sharedY.
  	"Store the second point back"
  	self bzStartX: newIndex put: sharedX.
  	self bzStartY: newIndex put: sharedY.
  	self bzViaX: newIndex put: rightViaX.
  	self bzViaY: newIndex put: rightViaY.
  	self bzEndX: newIndex put: endX.
  	self bzEndY: newIndex put: endY.
  
  	^newIndex!

Item was changed:
  ----- Method: BalloonEnginePlugin>>fillBitmapSpan:from:to:at: (in category 'fills-bitmaps') -----
  fillBitmapSpan: bmFill from: leftX to: rightX at: yValue
  	| x x1 dsX ds dtX dt deltaX deltaY bits xp yp bmWidth bmHeight fillValue tileFlag |
  	<inline: false>
+ 	<var: 'bits' type: #'int *'>
- 	<var: #bits type:'int *'>
  	self aaLevelGet = 1
  		ifFalse:[^self fillBitmapSpanAA: bmFill from: leftX to: rightX at: yValue].
  
  	bits := self loadBitsFrom: bmFill.
  	bits == nil ifTrue:[^nil].
  	bmWidth := self bitmapWidthOf: bmFill.
  	bmHeight := self bitmapHeightOf: bmFill.
  	tileFlag := (self bitmapTileFlagOf: bmFill) = 1.
  	deltaX := leftX - (self fillOriginXOf: bmFill).
  	deltaY := yValue - (self fillOriginYOf: bmFill).
  	dsX := self fillDirectionXOf: bmFill.
  	dtX := self fillNormalXOf: bmFill.
  
  	ds := (deltaX * dsX) + (deltaY * (self fillDirectionYOf: bmFill)).
  	dt := (deltaX * dtX) + (deltaY * (self fillNormalYOf: bmFill)).
  
  	x := leftX.
  	x1 := rightX.
  	[x < x1] whileTrue:[
  		tileFlag ifTrue:[
  			ds := self repeatValue: ds max: bmWidth << 16.
  			dt := self repeatValue: dt max: bmHeight << 16].
  		xp := ds // 16r10000.
  		yp := dt // 16r10000.
  		tileFlag ifFalse:[
  			xp := self clampValue: xp max: bmWidth.
  			yp := self clampValue: yp max: bmHeight].
  		(xp >= 0 and:[yp >= 0 and:[xp < bmWidth and:[yp < bmHeight]]]) ifTrue:[
  			fillValue := self bitmapValue: bmFill bits: bits atX: xp y: yp.
  			spanBuffer at: x put: fillValue.
  		].
  		ds := ds + dsX.
  		dt := dt + dtX.
  		x := x + 1.
  	].!

Item was changed:
  ----- Method: BalloonEnginePlugin>>fillBitmapSpanAA:from:to:at: (in category 'fills-bitmaps') -----
  fillBitmapSpanAA: bmFill from: leftX to: rightX at: yValue
  	| x dsX ds dtX dt deltaX deltaY bits xp yp bmWidth bmHeight fillValue baseShift cMask cShift idx aaLevel firstPixel lastPixel tileFlag |
  	<inline: false>
+ 	<var: 'bits' type: #'int *'>
- 	<var: #bits type:'int *'>
  	bits := self loadBitsFrom: bmFill.
  	bits == nil ifTrue:[^nil].
  	bmWidth := self bitmapWidthOf: bmFill.
  	bmHeight := self bitmapHeightOf: bmFill.
  	tileFlag := (self bitmapTileFlagOf: bmFill) = 1.
  	deltaX := leftX - (self fillOriginXOf: bmFill).
  	deltaY := yValue - (self fillOriginYOf: bmFill).
  	dsX := self fillDirectionXOf: bmFill.
  	dtX := self fillNormalXOf: bmFill.
  
  	ds := (deltaX * dsX) + (deltaY * (self fillDirectionYOf: bmFill)).
  	dt := (deltaX * dtX) + (deltaY * (self fillNormalYOf: bmFill)).
  
  	aaLevel := self aaLevelGet.
  	firstPixel := self aaFirstPixelFrom: leftX to: rightX.
  	lastPixel := self aaLastPixelFrom: leftX to: rightX.
  	baseShift := self aaShiftGet.
  	cMask := self aaColorMaskGet.
  	cShift := self aaColorShiftGet.
  	x := leftX.
  	[x < firstPixel] whileTrue:[
  		tileFlag ifTrue:[
  			ds := self repeatValue: ds max: bmWidth << 16.
  			dt := self repeatValue: dt max: bmHeight << 16].
  		xp := ds // 16r10000.
  		yp := dt // 16r10000.
  		tileFlag ifFalse:[
  			xp := self clampValue: xp max: bmWidth.
  			yp := self clampValue: yp max: bmHeight].
  		(xp >= 0 and:[yp >= 0 and:[xp < bmWidth and:[yp < bmHeight]]]) ifTrue:[
  			fillValue := self bitmapValue: bmFill bits: bits atX: xp y: yp.
  			fillValue := (fillValue bitAnd: cMask) >> cShift.
  			idx := x >> baseShift.
  			spanBuffer at: idx put: (spanBuffer at: idx) + fillValue.
  		].
  		ds := ds + dsX.
  		dt := dt + dtX.
  		x := x + 1.
  	].
  
  	cMask := (self aaColorMaskGet >> self aaShiftGet) bitOr: 16rF0F0F0F0.
  	cShift := self aaShiftGet.
  	[x < lastPixel] whileTrue:[
  		tileFlag ifTrue:[
  			ds := self repeatValue: ds max: bmWidth << 16.
  			dt := self repeatValue: dt max: bmHeight << 16].
  		xp := ds // 16r10000.
  		yp := dt // 16r10000.
  		tileFlag ifFalse:[
  			xp := self clampValue: xp max: bmWidth.
  			yp := self clampValue: yp max: bmHeight].
  		(xp >= 0 and:[yp >= 0 and:[xp < bmWidth and:[yp < bmHeight]]]) ifTrue:[
  			fillValue := self bitmapValue: bmFill bits: bits atX: xp y: yp.
  			fillValue := (fillValue bitAnd: cMask) >> cShift.
  			idx := x >> baseShift.
  			spanBuffer at: idx put: (spanBuffer at: idx) + fillValue.
  		].
  		ds := ds + (dsX << cShift).
  		dt := dt + (dtX << cShift).
  		x := x + aaLevel.
  	].
  
  	cMask := self aaColorMaskGet.
  	cShift := self aaColorShiftGet.
  	[x < rightX] whileTrue:[
  		tileFlag ifTrue:[
  			ds := self repeatValue: ds max: bmWidth << 16.
  			dt := self repeatValue: dt max: bmHeight << 16].
  		xp := ds // 16r10000.
  		yp := dt // 16r10000.
  		tileFlag ifFalse:[
  			xp := self clampValue: xp max: bmWidth.
  			yp := self clampValue: yp max: bmHeight].
  		(xp >= 0 and:[yp >= 0 and:[xp < bmWidth and:[yp < bmHeight]]]) ifTrue:[
  			fillValue := self bitmapValue: bmFill bits: bits atX: xp y: yp.
  			fillValue := (fillValue bitAnd: cMask) >> cShift.
  			idx := x >> baseShift.
  			spanBuffer at: idx put: (spanBuffer at: idx) + fillValue.
  		].
  		ds := ds + dsX.
  		dt := dt + dtX.
  		x := x + 1.
  	].
  !

Item was changed:
  ----- Method: BalloonEnginePlugin>>fillLinearGradient:from:to:at: (in category 'fills-gradient') -----
  fillLinearGradient: fill from: leftX to: rightX at: yValue
  	"Draw a linear gradient fill."
  	| x0 x1 ramp rampSize dsX ds x rampIndex |
  	<inline: false>
+ 	<var: 'ramp' type: #'int *'>
- 	<var: #ramp type:'int *'>
  	ramp := self gradientRampOf: fill.
  	rampSize := self gradientRampLengthOf: fill.
  
  	dsX := self fillDirectionXOf: fill.
  	ds := ((leftX - (self fillOriginXOf: fill)) * dsX) + 
  			((yValue - (self fillOriginYOf: fill)) * (self fillDirectionYOf: fill)).
  
  	x := x0 := leftX.
  	x1 := rightX.
  
  	"Note: The inner loop has been divided into three parts for speed"
  	"Part one: Fill everything outside the left boundary"
  	[((rampIndex := ds // 16r10000) < 0 or:[rampIndex >= rampSize]) and:[x < x1]] 
  		whileTrue:[	x := x + 1.
  					ds := ds + dsX].
  	x > x0 ifTrue:[
  		rampIndex < 0 ifTrue:[rampIndex := 0].
  		rampIndex >= rampSize ifTrue:[rampIndex := rampSize - 1].
  		self fillColorSpan: (self makeUnsignedFrom: (ramp at: rampIndex)) from: x0 to: x].
  
  	"Part two: Fill everything inside the boundaries"
  	self aaLevelGet = 1 ifTrue:[
  		"Fast version w/o anti-aliasing"
  		[((rampIndex := ds // 16r10000) < rampSize and:[rampIndex >= 0]) and:[x < x1]] whileTrue:[
  			spanBuffer at: x put: (self makeUnsignedFrom: (ramp at: rampIndex)).
  			x := x + 1.
  			ds := ds + dsX.
  		].
  	] ifFalse:[x := self fillLinearGradientAA: fill ramp: ramp ds: ds dsX: dsX from: x to: rightX].
  	"Part three fill everything outside right boundary"
  	x < x1 ifTrue:[
  		rampIndex < 0 ifTrue:[rampIndex := 0].
  		rampIndex >= rampSize ifTrue:[rampIndex := rampSize-1].
  		self fillColorSpan: (self makeUnsignedFrom: (ramp at: rampIndex)) from: x to: x1].
  !

Item was changed:
  ----- Method: BalloonEnginePlugin>>fillLinearGradientAA:ramp:ds:dsX:from:to: (in category 'fills-gradient') -----
  fillLinearGradientAA: fill ramp: ramp ds: deltaS dsX: dsX from: leftX to: rightX
  	"This is the AA version of linear gradient filling."
  	| colorMask colorShift baseShift rampIndex ds rampSize x idx rampValue 
  	 aaLevel firstPixel lastPixel |
  	<inline: false>
+ 	<var: 'ramp' type: #'int *'>
- 	<var: #ramp type:'int *'>
  
  	aaLevel := self aaLevelGet.
  	baseShift := self aaShiftGet.
  	rampSize := self gradientRampLengthOf: fill.
  	ds := deltaS.
  	x := leftX.
  	rampIndex := ds // 16r10000.
  
  	firstPixel := self aaFirstPixelFrom: leftX to: rightX.
  	lastPixel := self aaLastPixelFrom: leftX to: rightX.
  
  	"Deal with the first n sub-pixels"
  	colorMask := self aaColorMaskGet.
  	colorShift := self aaColorShiftGet.
  	[x < firstPixel and:[rampIndex < rampSize and:[rampIndex >= 0]]] whileTrue:[
+ 		rampValue := self makeUnsignedFrom: ((self cCoerce: ramp to: #'int *') at: rampIndex).
- 		rampValue := self makeUnsignedFrom: ((self cCoerce: ramp to:'int *') at: rampIndex).
  		rampValue := (rampValue bitAnd: colorMask) >> colorShift.
  		"Copy as many pixels as possible"
  		[x < firstPixel and:[(ds//16r10000) = rampIndex]] whileTrue:[
  			idx := x >> baseShift.
  			spanBuffer at: idx put: (spanBuffer at: idx) + rampValue.
  			x := x + 1.
  			ds := ds + dsX].
  		rampIndex := ds // 16r10000.
  	].
  
  	"Deal with the full pixels"
  	colorMask := (self aaColorMaskGet >> self aaShiftGet) bitOr: 16rF0F0F0F0.
  	colorShift := self aaShiftGet.
  	[x < lastPixel and:[rampIndex < rampSize and:[rampIndex >= 0]]] whileTrue:[
+ 		rampValue := self makeUnsignedFrom: ((self cCoerce: ramp to: #'int *') at: rampIndex).
- 		rampValue := self makeUnsignedFrom: ((self cCoerce: ramp to:'int *') at: rampIndex).
  		rampValue := (rampValue bitAnd: colorMask) >> colorShift.
  		"Copy as many pixels as possible"
  		[x < lastPixel and:[(ds//16r10000) = rampIndex]] whileTrue:[
  			idx := x >> baseShift.
  			spanBuffer at: idx put: (spanBuffer at: idx) + rampValue.
  			x := x + aaLevel.
  			ds := ds + (dsX << colorShift)].
  		rampIndex := ds // 16r10000.
  	].
  
  	"Deal with the last n sub-pixels"
  	colorMask := self aaColorMaskGet.
  	colorShift := self aaColorShiftGet.
  	[x < rightX and:[rampIndex < rampSize and:[rampIndex>=0]]] whileTrue:[
+ 		rampValue := self makeUnsignedFrom: ((self cCoerce: ramp to: #'int *') at: rampIndex).
- 		rampValue := self makeUnsignedFrom: ((self cCoerce: ramp to:'int *') at: rampIndex).
  		rampValue := (rampValue bitAnd: colorMask) >> colorShift.
  		"Copy as many pixels as possible"
  		[x < rightX and:[(ds//16r10000) = rampIndex]] whileTrue:[
  			idx := x >> baseShift.
  			spanBuffer at: idx put: (spanBuffer at: idx) + rampValue.
  			x := x + 1.
  			ds := ds + dsX].
  		rampIndex := ds // 16r10000.
  	].
  	^x!

Item was changed:
  ----- Method: BalloonEnginePlugin>>fillRadialDecreasing:ramp:deltaST:dsX:dtX:from:to: (in category 'fills-gradient') -----
  fillRadialDecreasing: fill ramp: ramp deltaST: deltaST dsX: dsX dtX: dtX from: leftX to: rightX
  	"Part 2a) Compute the decreasing part of the ramp"
  	| ds dt rampIndex rampValue length2 x x1 nextLength |
  	<inline: true>
+ 	ds := (self cCoerce: deltaST to: #'int *') at: 0.
+ 	dt := (self cCoerce: deltaST to: #'int *') at: 1.
- 	ds := (self cCoerce: deltaST to:'int*') at: 0.
- 	dt := (self cCoerce: deltaST to:'int*') at: 1.
  	rampIndex := self accurateLengthOf: ds // 16r10000 with: dt // 16r10000.
+ 	rampValue := self makeUnsignedFrom: ((self cCoerce: ramp to: #'int *') at: rampIndex).
- 	rampValue := self makeUnsignedFrom: ((self cCoerce: ramp to:'int *') at: rampIndex).
  	length2 := (rampIndex-1) * (rampIndex-1).
  
  	x := leftX.
  	x1 := rightX.
  	x1 > (self fillOriginXOf: fill) ifTrue:[x1 := self fillOriginXOf: fill].
  	[x < x1] whileTrue:[
  		"Try to copy the current value more than just once"
  		[x < x1 and:[(self squaredLengthOf: ds //  16r10000 with: dt // 16r10000) >= length2]]
  			whileTrue:[	spanBuffer at: x put: rampValue.
  						x := x + 1.
  						ds := ds + dsX.
  						dt := dt + dtX].
  		"Step to next ramp value"
  		nextLength := self squaredLengthOf: ds //  16r10000 with: dt // 16r10000.
  		[nextLength < length2] whileTrue:[
  			rampIndex := rampIndex - 1.
+ 			rampValue := self makeUnsignedFrom: ((self cCoerce: ramp to: #'int *') at: rampIndex).
- 			rampValue := self makeUnsignedFrom: ((self cCoerce: ramp to:'int *') at: rampIndex).
  			length2 := (rampIndex-1) * (rampIndex-1).
  		].
  	].
  
+ 	(self cCoerce: deltaST to: #'int *') at: 0 put: ds.
+ 	(self cCoerce: deltaST to: #'int *') at: 1 put: dt.
- 	(self cCoerce: deltaST to: 'int *') at: 0 put: ds.
- 	(self cCoerce: deltaST to: 'int *') at: 1 put: dt.
  	^x!

Item was changed:
  ----- Method: BalloonEnginePlugin>>fillRadialDecreasingAA:ramp:deltaST:dsX:dtX:from:to: (in category 'fills-gradient') -----
  fillRadialDecreasingAA: fill ramp: ramp deltaST: deltaST dsX: dsX dtX: dtX from: leftX to: rightX
  	"Part 2a) Compute the decreasing part of the ramp"
  	| ds dt rampIndex rampValue length2 x nextLength x1
  	aaLevel colorMask colorShift baseShift index firstPixel lastPixel |
  	<inline: false>
+ 	<var: 'ramp' type: #'int *'>
+ 	<var: 'deltaST' type: #'int *'>
- 	<var: #ramp type:'int *'>
- 	<var: #deltaST type:' int *'>
  
+ 	ds := (self cCoerce: deltaST to: #'int *') at: 0.
+ 	dt := (self cCoerce: deltaST to: #'int *') at: 1.
- 	ds := (self cCoerce: deltaST to:'int*') at: 0.
- 	dt := (self cCoerce: deltaST to:'int*') at: 1.
  	aaLevel := self aaLevelGet.
  	baseShift := self aaShiftGet.
  	rampIndex := self accurateLengthOf: ds // 16r10000 with: dt // 16r10000.
  	length2 := (rampIndex-1) * (rampIndex-1).
  
  	x := leftX.
  	x1 := self fillOriginXOf: fill.
  	x1 > rightX ifTrue:[x1 := rightX].
  	firstPixel := self aaFirstPixelFrom: leftX to: x1.
  	lastPixel := self aaLastPixelFrom: leftX to: x1.
  
  	"Deal with the first n sub-pixels"
  	(x < firstPixel) ifTrue:[
  		colorMask := self aaColorMaskGet.
  		colorShift := self aaColorShiftGet.
+ 		rampValue := self makeUnsignedFrom: ((self cCoerce: ramp to: #'int *') at: rampIndex).
- 		rampValue := self makeUnsignedFrom: ((self cCoerce: ramp to:'int *') at: rampIndex).
  		rampValue := (rampValue bitAnd: colorMask) >> colorShift.
  		[x < firstPixel] whileTrue:[
  			"Try to copy the current value more than just once"
  			[x < firstPixel and:[(self squaredLengthOf: ds //  16r10000 with: dt // 16r10000) >= length2]]
  				whileTrue:[	index := x >> baseShift.
  							spanBuffer at: index put: (spanBuffer at: index) + rampValue.
  							x := x + 1.
  							ds := ds + dsX.
  							dt := dt + dtX].
  			"Step to next ramp value"
  			nextLength := self squaredLengthOf: ds //  16r10000 with: dt // 16r10000.
  			[nextLength < length2] whileTrue:[
  				rampIndex := rampIndex - 1.
+ 				rampValue := self makeUnsignedFrom: ((self cCoerce: ramp to: #'int *') at: rampIndex).
- 				rampValue := self makeUnsignedFrom: ((self cCoerce: ramp to:'int *') at: rampIndex).
  				rampValue := (rampValue bitAnd: colorMask) >> colorShift.
  				length2 := (rampIndex-1) * (rampIndex-1).
  			].
  		].
  	].
  
  	"Deal with the full pixels"
  	(x < lastPixel) ifTrue:[
  		colorMask := (self aaColorMaskGet >> self aaShiftGet) bitOr: 16rF0F0F0F0.
  		colorShift := self aaShiftGet.
+ 		rampValue := self makeUnsignedFrom: ((self cCoerce: ramp to: #'int *') at: rampIndex).
- 		rampValue := self makeUnsignedFrom: ((self cCoerce: ramp to:'int *') at: rampIndex).
  		rampValue := (rampValue bitAnd: colorMask) >> colorShift.
  		[x < lastPixel] whileTrue:[
  			"Try to copy the current value more than just once"
  			[x < lastPixel and:[(self squaredLengthOf: ds //  16r10000 with: dt // 16r10000) >= length2]]
  				whileTrue:[	index := x >> baseShift.
  							spanBuffer at: index put: (spanBuffer at: index) + rampValue.
  							x := x + aaLevel.
  							ds := ds + (dsX << colorShift).
  							dt := dt + (dtX << colorShift)].
  			"Step to next ramp value"
  			nextLength := self squaredLengthOf: ds //  16r10000 with: dt // 16r10000.
  			[nextLength < length2] whileTrue:[
  				rampIndex := rampIndex - 1.
+ 				rampValue := self makeUnsignedFrom: ((self cCoerce: ramp to: #'int *') at: rampIndex).
- 				rampValue := self makeUnsignedFrom: ((self cCoerce: ramp to:'int *') at: rampIndex).
  				rampValue := (rampValue bitAnd: colorMask) >> colorShift.
  				length2 := (rampIndex-1) * (rampIndex-1).
  			].
  		].
  	].
  
  	"Deal with the last n sub-pixels"
  	(x < x1) ifTrue:[
  		colorMask := self aaColorMaskGet.
  		colorShift := self aaColorShiftGet.
+ 		rampValue := self makeUnsignedFrom: ((self cCoerce: ramp to: #'int *') at: rampIndex).
- 		rampValue := self makeUnsignedFrom: ((self cCoerce: ramp to:'int *') at: rampIndex).
  		rampValue := (rampValue bitAnd: colorMask) >> colorShift.
  		[x < x1] whileTrue:[
  			"Try to copy the current value more than just once"
  			[x < x1 and:[(self squaredLengthOf: ds //  16r10000 with: dt // 16r10000) >= length2]]
  				whileTrue:[	index := x >> baseShift.
  							spanBuffer at: index put: (spanBuffer at: index) + rampValue.
  							x := x + 1.
  							ds := ds + dsX.
  							dt := dt + dtX].
  			"Step to next ramp value"
  			nextLength := self squaredLengthOf: ds //  16r10000 with: dt // 16r10000.
  			[nextLength < length2] whileTrue:[
  				rampIndex := rampIndex - 1.
+ 				rampValue := self makeUnsignedFrom: ((self cCoerce: ramp to: #'int *') at: rampIndex).
- 				rampValue := self makeUnsignedFrom: ((self cCoerce: ramp to:'int *') at: rampIndex).
  				rampValue := (rampValue bitAnd: colorMask) >> colorShift.
  				length2 := (rampIndex-1) * (rampIndex-1).
  			].
  		].
  	].
  	"Done -- store stuff back"
+ 	(self cCoerce: deltaST to: #'int *') at: 0 put: ds.
+ 	(self cCoerce: deltaST to: #'int *') at: 1 put: dt.
- 	(self cCoerce: deltaST to: 'int *') at: 0 put: ds.
- 	(self cCoerce: deltaST to: 'int *') at: 1 put: dt.
  	^x!

Item was changed:
  ----- Method: BalloonEnginePlugin>>fillRadialGradient:from:to:at: (in category 'fills-gradient') -----
  fillRadialGradient: fill from: leftX to: rightX at: yValue
  	"Draw a radial gradient fill."
  	| x x1 ramp rampSize dsX ds dtX dt length2 deltaX deltaY deltaST |
  	<inline: false>
+ 	<var: 'ramp' type: #'int *'>
+ 	<var: 'deltaST' type: #'int *'>
- 	<var: #ramp type:'int *'>
- 	<var: #deltaST type:'int *'>
  
  	ramp := self gradientRampOf: fill.
  	rampSize := self gradientRampLengthOf: fill.
  
  	deltaX := leftX - (self fillOriginXOf: fill).
  	deltaY := yValue - (self fillOriginYOf: fill).
  
  	dsX := self fillDirectionXOf: fill.
  	dtX := self fillNormalXOf: fill.
  
  	ds := (deltaX * dsX) + (deltaY * (self fillDirectionYOf: fill)).
  	dt := (deltaX * dtX) + (deltaY * (self fillNormalYOf: fill)).
  
  	x := leftX.
  	x1 := rightX.
  
  	"Note: The inner loop has been divided into three parts for speed"
  	"Part one: Fill everything outside the left boundary"
  	length2 := (rampSize-1) * (rampSize-1). "This is the upper bound"
  	[(self squaredLengthOf: ds // 16r10000 with: dt // 16r10000) >= length2 and:[x < x1]]
  		whileTrue:[	x := x + 1.	ds := ds + dsX.	dt := dt + dtX].
  	x > leftX ifTrue:[self fillColorSpan: (self makeUnsignedFrom: (ramp at: rampSize-1)) from: leftX to: x].
  
  	"Part two: Fill everything inside the boundaries"
  	deltaST := self point1Get.
  	deltaST at: 0 put: ds.
  	deltaST at: 1 put: dt.
  	(x < (self fillOriginXOf: fill)) ifTrue:[
  		"Draw the decreasing part"
  		self aaLevelGet = 1 
  			ifTrue:[x := self fillRadialDecreasing: fill ramp: ramp deltaST: deltaST 
  							dsX: dsX dtX: dtX from: x to: x1]
  			ifFalse:[x := self fillRadialDecreasingAA: fill ramp: ramp deltaST: deltaST 
  							dsX: dsX dtX: dtX from: x to: x1].
  	].
  	x < x1 ifTrue:[
  		"Draw the increasing part"
  		self aaLevelGet = 1
  			ifTrue:[x := self fillRadialIncreasing: fill ramp: ramp deltaST: deltaST
  							dsX: dsX dtX: dtX from: x to: x1]
  			ifFalse:[x := self fillRadialIncreasingAA: fill ramp: ramp deltaST: deltaST
  							dsX: dsX dtX: dtX from: x to: x1].
  	].
  
  	"Part three fill everything outside right boundary"
  	x < rightX ifTrue:[self fillColorSpan: (self makeUnsignedFrom: (ramp at: rampSize-1)) from: x to: rightX].
  !

Item was changed:
  ----- Method: BalloonEnginePlugin>>fillRadialIncreasing:ramp:deltaST:dsX:dtX:from:to: (in category 'fills-gradient') -----
  fillRadialIncreasing: fill ramp: ramp deltaST: deltaST dsX: dsX dtX: dtX from: leftX to: rightX
  	"Part 2b) Compute the increasing part of the ramp"
  	| ds dt rampIndex rampValue length2 x x1 nextLength rampSize lastLength |
  	<inline: true>
+ 	ds := (self cCoerce: deltaST to: #'int *') at: 0.
+ 	dt := (self cCoerce: deltaST to: #'int *') at: 1.
- 	ds := (self cCoerce: deltaST to:'int*') at: 0.
- 	dt := (self cCoerce: deltaST to:'int*') at: 1.
  	rampIndex := self accurateLengthOf: ds // 16r10000 with: dt // 16r10000.
+ 	rampValue := self makeUnsignedFrom: ((self cCoerce: ramp to: #'int *') at: rampIndex).
- 	rampValue := self makeUnsignedFrom: ((self cCoerce: ramp to:'int *') at: rampIndex).
  	rampSize := self gradientRampLengthOf: fill.
  	length2 := (rampSize-1) * (rampSize-1). "This is the upper bound"
  	nextLength := (rampIndex+1) * (rampIndex+1).
  	lastLength := self squaredLengthOf: ds //  16r10000 with: dt // 16r10000.
  
  	x := leftX.
  	x1 := rightX.
  
  	[x < x1 and:[lastLength < length2]] whileTrue:[
  		"Try to copy the current value more than once"
  		[x < x1 and:[(self squaredLengthOf: ds //  16r10000 with: dt // 16r10000) <= nextLength]]
  			whileTrue:[	spanBuffer at: x put: rampValue.
  						x := x + 1.
  						ds := ds + dsX.
  						dt := dt + dtX].
  		lastLength := self squaredLengthOf: ds //  16r10000 with: dt // 16r10000.
  		[lastLength > nextLength] whileTrue:[
  			rampIndex := rampIndex + 1.
+ 			rampValue := self makeUnsignedFrom: ((self cCoerce: ramp to: #'int *') at: rampIndex).
- 			rampValue := self makeUnsignedFrom: ((self cCoerce: ramp to:'int *') at: rampIndex).
  			nextLength := (rampIndex+1) * (rampIndex+1).
  		].
  	].
  
+ 	(self cCoerce: deltaST to: #'int *') at: 0 put: ds.
+ 	(self cCoerce: deltaST to: #'int *') at: 1 put: dt.
- 	(self cCoerce: deltaST to: 'int *') at: 0 put: ds.
- 	(self cCoerce: deltaST to: 'int *') at: 1 put: dt.
  	^x!

Item was changed:
  ----- Method: BalloonEnginePlugin>>fillRadialIncreasingAA:ramp:deltaST:dsX:dtX:from:to: (in category 'fills-gradient') -----
  fillRadialIncreasingAA: fill ramp: ramp deltaST: deltaST dsX: dsX dtX: dtX from: leftX to: rightX
  	"Part 2b) Compute the increasing part of the ramp"
  	| ds dt rampIndex rampValue length2 x nextLength rampSize lastLength 
  	aaLevel colorMask colorShift baseShift index firstPixel lastPixel |
  	<inline: false>
+ 	<var: 'ramp' type: #'int *'>
+ 	<var: 'deltaST' type: #'int *'>
- 	<var: #ramp type:'int *'>
- 	<var: #deltaST type:' int *'>
  
+ 	ds := (self cCoerce: deltaST to: #'int *') at: 0.
+ 	dt := (self cCoerce: deltaST to: #'int *') at: 1.
- 	ds := (self cCoerce: deltaST to:'int*') at: 0.
- 	dt := (self cCoerce: deltaST to:'int*') at: 1.
  	aaLevel := self aaLevelGet.
  	baseShift := self aaShiftGet.
  	rampIndex := self accurateLengthOf: ds // 16r10000 with: dt // 16r10000.
  	rampSize := self gradientRampLengthOf: fill.
  	length2 := (rampSize-1) * (rampSize-1). "This is the upper bound"
  	nextLength := (rampIndex+1) * (rampIndex+1).
  	lastLength := self squaredLengthOf: ds //  16r10000 with: dt // 16r10000.
  
  	x := leftX.
  
  	firstPixel := self aaFirstPixelFrom: leftX to: rightX.
  	lastPixel := self aaLastPixelFrom: leftX to: rightX.
  
  	"Deal with the first n subPixels"
  	(x < firstPixel and:[lastLength < length2]) ifTrue:[
  		colorMask := self aaColorMaskGet.
  		colorShift := self aaColorShiftGet.
+ 		rampValue := self makeUnsignedFrom: ((self cCoerce: ramp to: #'int *') at: rampIndex).
- 		rampValue := self makeUnsignedFrom: ((self cCoerce: ramp to:'int *') at: rampIndex).
  		rampValue := (rampValue bitAnd: colorMask) >> colorShift.
  		[x < firstPixel and:[lastLength < length2]] whileTrue:[
  			"Try to copy the current value more than once"
  			[x < firstPixel and:[(self squaredLengthOf: ds //  16r10000 with: dt // 16r10000) <= nextLength]]
  				whileTrue:[	index := x >> baseShift.
  							spanBuffer at: index put: (spanBuffer at: index) + rampValue.
  							x := x + 1.
  							ds := ds + dsX.
  							dt := dt + dtX].
  			lastLength := self squaredLengthOf: ds //  16r10000 with: dt // 16r10000.
  			[lastLength > nextLength] whileTrue:[
  				rampIndex := rampIndex + 1.
+ 				rampValue := self makeUnsignedFrom: ((self cCoerce: ramp to: #'int *') at: rampIndex).
- 				rampValue := self makeUnsignedFrom: ((self cCoerce: ramp to:'int *') at: rampIndex).
  				rampValue := (rampValue bitAnd: colorMask) >> colorShift.
  				nextLength := (rampIndex+1) * (rampIndex+1).
  			].
  		].
  	].
  
  	"Deal with the full pixels"
  	(x < lastPixel and:[lastLength < length2]) ifTrue:[
  		colorMask := (self aaColorMaskGet >> self aaShiftGet) bitOr: 16rF0F0F0F0.
  		colorShift := self aaShiftGet.
+ 		rampValue := self makeUnsignedFrom: ((self cCoerce: ramp to: #'int *') at: rampIndex).
- 		rampValue := self makeUnsignedFrom: ((self cCoerce: ramp to:'int *') at: rampIndex).
  		rampValue := (rampValue bitAnd: colorMask) >> colorShift.
  		[x < lastPixel and:[lastLength < length2]] whileTrue:[
  			"Try to copy the current value more than once"
  			[x < lastPixel and:[(self squaredLengthOf: ds //  16r10000 with: dt // 16r10000) <= nextLength]]
  				whileTrue:[	index := x >> baseShift.
  							spanBuffer at: index put: (spanBuffer at: index) + rampValue.
  							x := x + aaLevel.
  							ds := ds + (dsX << colorShift).
  							dt := dt + (dtX << colorShift)].
  			lastLength := self squaredLengthOf: ds //  16r10000 with: dt // 16r10000.
  			[lastLength > nextLength] whileTrue:[
  				rampIndex := rampIndex + 1.
+ 				rampValue := self makeUnsignedFrom: ((self cCoerce: ramp to: #'int *') at: rampIndex).
- 				rampValue := self makeUnsignedFrom: ((self cCoerce: ramp to:'int *') at: rampIndex).
  				rampValue := (rampValue bitAnd: colorMask) >> colorShift.
  				nextLength := (rampIndex+1) * (rampIndex+1).
  			].
  		].
  	].
  
  	"Deal with last n sub-pixels"
  	(x < rightX and:[lastLength < length2]) ifTrue:[
  		colorMask := self aaColorMaskGet.
  		colorShift := self aaColorShiftGet.
+ 		rampValue := self makeUnsignedFrom: ((self cCoerce: ramp to: #'int *') at: rampIndex).
- 		rampValue := self makeUnsignedFrom: ((self cCoerce: ramp to:'int *') at: rampIndex).
  		rampValue := (rampValue bitAnd: colorMask) >> colorShift.
  		[x < rightX and:[lastLength < length2]] whileTrue:[
  			"Try to copy the current value more than once"
  			[x < rightX and:[(self squaredLengthOf: ds //  16r10000 with: dt // 16r10000) <= nextLength]]
  				whileTrue:[	index := x >> baseShift.
  							spanBuffer at: index put: (spanBuffer at: index) + rampValue.
  							x := x + 1.
  							ds := ds + dsX.
  							dt := dt + dtX].
  			lastLength := self squaredLengthOf: ds //  16r10000 with: dt // 16r10000.
  			[lastLength > nextLength] whileTrue:[
  				rampIndex := rampIndex + 1.
+ 				rampValue := self makeUnsignedFrom: ((self cCoerce: ramp to: #'int *') at: rampIndex).
- 				rampValue := self makeUnsignedFrom: ((self cCoerce: ramp to:'int *') at: rampIndex).
  				rampValue := (rampValue bitAnd: colorMask) >> colorShift.
  				nextLength := (rampIndex+1) * (rampIndex+1).
  			].
  		].
  	].
  	"Done -- store stuff back"
+ 	(self cCoerce: deltaST to: #'int *') at: 0 put: ds.
+ 	(self cCoerce: deltaST to: #'int *') at: 1 put: dt.
- 	(self cCoerce: deltaST to: 'int *') at: 0 put: ds.
- 	(self cCoerce: deltaST to: 'int *') at: 1 put: dt.
  	^x!

Item was changed:
  ----- Method: BalloonEnginePlugin>>loadAndSubdivideBezierFrom:via:to:isWide: (in category 'bezier-loading') -----
  loadAndSubdivideBezierFrom: point1 via: point2 to: point3 isWide: wideFlag
  	"Load and subdivide the bezier curve from point1/point2/point3.
  	If wideFlag is set then make sure the curve is monoton in X."
  	| bz1 bz2 index2 index1 |
  	<inline: false>
+ 	<var: 'point1' type: #'int *'>
+ 	<var: 'point2' type: #'int *'>
+ 	<var: 'point3' type: #'int *'>
- 	<var: #point1 type:'int *'>
- 	<var: #point2 type:'int *'>
- 	<var: #point3 type:'int *'>
  	bz1 := self allocateBezierStackEntry.	
  	engineStopped ifTrue:[^0].
  	"Load point1/point2/point3 on the top of the stack"
  	self bzStartX: bz1 put: (point1 at: 0).
  	self bzStartY: bz1 put: (point1 at: 1).
  	self bzViaX: bz1 put: (point2 at: 0).
  	self bzViaY: bz1 put: (point2 at: 1).
  	self bzEndX: bz1 put: (point3 at: 0).
  	self bzEndY: bz1 put: (point3 at: 1).
  
  	"Now check if the bezier curve is monoton. If not, subdivide it."
  	index2 := bz2 := self subdivideToBeMonoton: bz1 inX: wideFlag.
  	bz1 to: bz2 by: 6 do:[:index|
  		index1 := self subdivideBezierFrom: index.
  		index1 > index2 ifTrue:[index2 := index1].
  		engineStopped ifTrue:[^0]. "Something went wrong"
  	].
  	"Return the number of segments"
  	^index2 // 6!

Item was changed:
  ----- Method: BalloonEnginePlugin>>loadBitmapFill:colormap:tile:from:along:normal:xIndex: (in category 'fills-bitmaps') -----
  loadBitmapFill: formOop colormap: cmOop tile: tileFlag from: point1 along: point2 normal: point3 xIndex: xIndex
  	"Load the bitmap fill."
  	| bmFill cmSize cmBits bmBits bmBitsSize bmWidth bmHeight bmDepth ppw bmRaster |
+ 	<var: 'cmBits' type: #'int *'>
+ 	<var: 'point1' type: #'int *'>
+ 	<var: 'point2' type: #'int *'>
+ 	<var: 'point3' type: #'int *'>
- 	<var: #cmBits type: #'int *'>
- 	<var: #point1 type: #'int *'>
- 	<var: #point2 type: #'int *'>
- 	<var: #point3 type: #'int *'>
  
  	cmOop == interpreterProxy nilObject ifTrue:[
  		cmSize := 0.
  		cmBits := nil.
  	] ifFalse:[
  		(interpreterProxy fetchClassOf: cmOop) = interpreterProxy classBitmap
  			ifFalse:[^interpreterProxy primitiveFail].
  		cmSize := interpreterProxy slotSizeOf: cmOop.
  		cmBits := interpreterProxy firstIndexableField: cmOop.
  	].
  	(interpreterProxy isPointers: formOop) 
  		ifFalse:[^interpreterProxy primitiveFail].
  	(interpreterProxy slotSizeOf: formOop) < 5 
  		ifTrue:[^interpreterProxy primitiveFail].
  	bmBits := interpreterProxy fetchPointer: 0 ofObject: formOop.
  	(interpreterProxy fetchClassOf: bmBits) = interpreterProxy classBitmap
  		ifFalse:[^interpreterProxy primitiveFail].
  	bmBitsSize := interpreterProxy slotSizeOf: bmBits.
  	bmWidth := interpreterProxy fetchInteger: 1 ofObject: formOop.
  	bmHeight := interpreterProxy fetchInteger: 2 ofObject: formOop.
  	bmDepth := interpreterProxy fetchInteger: 3 ofObject: formOop.
  	interpreterProxy failed ifTrue:[^nil].
  	(bmWidth >= 0 and:[bmHeight >= 0]) ifFalse:[^interpreterProxy primitiveFail].
  	(bmDepth = 32) | (bmDepth = 8) | (bmDepth = 16) | 
  		(bmDepth = 1) | (bmDepth = 2) | (bmDepth = 4)
  			ifFalse:[^interpreterProxy primitiveFail].
  	(cmSize = 0 or:[cmSize = (1 << bmDepth)])
  		ifFalse:[^interpreterProxy primitiveFail].
  	ppw := 32 // bmDepth.
  	bmRaster := bmWidth + (ppw-1) // ppw.
  	bmBitsSize = (bmRaster * bmHeight)
  		ifFalse:[^interpreterProxy primitiveFail].
  	bmFill := self allocateBitmapFill: cmSize colormap: cmBits.
  	engineStopped ifTrue:[^nil].
  	self bitmapWidthOf: bmFill put: bmWidth.
  	self bitmapHeightOf: bmFill put: bmHeight.
  	self bitmapDepthOf: bmFill put: bmDepth.
  	self bitmapRasterOf: bmFill put: bmRaster.
  	self bitmapSizeOf: bmFill put: bmBitsSize.
  	self bitmapTileFlagOf: bmFill put: tileFlag.
  	self objectIndexOf: bmFill put: xIndex.
  	self loadFillOrientation: bmFill
  		from: point1 along: point2 normal: point3
  		width: bmWidth height: bmHeight.
  	^bmFill!

Item was changed:
  ----- Method: BalloonEnginePlugin>>loadCompressedShape:segments:leftFills:rightFills:lineWidths:lineFills:fillIndexList:pointShort: (in category 'shapes-compressed') -----
  loadCompressedShape: points segments: nSegments leftFills: leftFills rightFills: rightFills lineWidths: lineWidths lineFills: lineFills fillIndexList: fillIndexList pointShort: pointsShort
  	"Load a compressed shape into the engine.
  		WARNING: THIS METHOD NEEDS THE FULL FRAME SIZE!!!!!!!!
  	"
  	| leftRun rightRun widthRun lineFillRun
  	leftLength rightLength widthLength lineFillLength
  	leftValue rightValue widthValue lineFillValue |
  
  	<inline: false>
+ 	<var: 'points' type: #'int *'>
+ 	<var: 'leftFills' type: #'int *'>
+ 	<var: 'rightFills' type: #'int *'>
+ 	<var: 'lineWidths' type: #'int *'>
+ 	<var: 'lineFills' type: #'int *'>
+ 	<var: 'fillIndexList' type: #'int *'>
- 	<var: #points type:'int *'>
- 	<var: #leftFills type:'int *'>
- 	<var: #rightFills type:'int *'>
- 	<var: #lineWidths type:'int *'>
- 	<var: #lineFills type:'int *'>
- 	<var: #fillIndexList type:'int *'>
  
  	nSegments = 0 ifTrue:[^0].
  
  	"Initialize run length encodings"
  	leftRun :=  rightRun := widthRun := lineFillRun := -1.
  	leftLength := rightLength := widthLength := lineFillLength := 1.
  	leftValue := rightValue := widthValue := lineFillValue := 0.
  
  	1 to: nSegments do:[:i|
  		"Decrement current run length and load new stuff"
  		(leftLength := leftLength - 1) <= 0 ifTrue:[
  			leftRun := leftRun + 1.
  			leftLength := self shortRunLengthAt: leftRun from: leftFills.
  			leftValue := self shortRunValueAt: leftRun from: leftFills.
  			leftValue = 0 ifFalse:[
  				leftValue := fillIndexList at: leftValue-1.
  				leftValue := self transformColor: leftValue.
  				engineStopped ifTrue:[^nil]]].
  		(rightLength := rightLength - 1) <= 0 ifTrue:[
  			rightRun := rightRun + 1.
  			rightLength := self shortRunLengthAt: rightRun from: rightFills.
  			rightValue := self shortRunValueAt: rightRun from: rightFills.
  			rightValue = 0 ifFalse:[
  				rightValue := fillIndexList at: rightValue-1.
  				rightValue := self transformColor: rightValue]].
  		(widthLength := widthLength - 1) <= 0 ifTrue:[
  			widthRun := widthRun + 1.
  			widthLength := self shortRunLengthAt: widthRun from: lineWidths.
  			widthValue := self shortRunValueAt: widthRun from: lineWidths.
  			widthValue = 0 ifFalse:[widthValue := self transformWidth: widthValue]].
  		(lineFillLength := lineFillLength - 1) <= 0 ifTrue:[
  			lineFillRun := lineFillRun + 1.
  			lineFillLength := self shortRunLengthAt: lineFillRun from: lineFills.
  			lineFillValue := self shortRunValueAt: lineFillRun from: lineFills.
  			lineFillValue = 0 ifFalse:[lineFillValue := fillIndexList at: lineFillValue-1]].
  		self loadCompressedSegment: i - 1
  			from: points 
  			short: pointsShort 
  			leftFill: leftValue 
  			rightFill: rightValue 
  			lineWidth: widthValue 
  			lineColor: lineFillValue.
  		engineStopped ifTrue:[^nil].
  	].!

Item was changed:
  ----- Method: BalloonEnginePlugin>>loadFillOrientation:from:along:normal:width:height: (in category 'fills-gradient') -----
  loadFillOrientation: fill from: point1 along: point2 normal: point3 width: fillWidth height: fillHeight
  	"Transform the points"
  	| dirX dirY nrmX nrmY dsLength2 dsX dsY dtLength2 dtX dtY |
+ 	<var: 'point1' type: #'int *'>
+ 	<var: 'point2' type: #'int *'>
+ 	<var: 'point3' type: #'int *'>
- 	<var: #point1 type:'int *'>
- 	<var: #point2 type:'int *'>
- 	<var: #point3 type:'int *'>
  
  	point2 at: 0 put: (point2 at: 0) + (point1 at: 0).
  	point2 at: 1 put: (point2 at: 1) + (point1 at: 1).
  	point3 at: 0 put: (point3 at: 0) + (point1 at: 0).
  	point3 at: 1 put: (point3 at: 1) + (point1 at: 1).
  	self transformPoint: point1.
  	self transformPoint: point2.
  	self transformPoint: point3.
  	dirX := (point2 at: 0) - (point1 at: 0).
  	dirY := (point2 at: 1) - (point1 at: 1).
  	nrmX := (point3 at: 0) - (point1 at: 0).
  	nrmY := (point3 at: 1) - (point1 at: 1).
  
  	"Compute the scale from direction/normal into ramp size"
  	dsLength2 := (dirX * dirX) + (dirY * dirY).
  	dsLength2 > 0 ifTrue:[
  		dsX := (dirX asFloat * fillWidth asFloat * 65536.0 / dsLength2 asFloat) asInteger.
  		dsY := (dirY asFloat * fillWidth asFloat * 65536.0 / dsLength2 asFloat) asInteger.
  	] ifFalse:[ dsX := 0. dsY := 0].
  	dtLength2 := (nrmX * nrmX) + (nrmY * nrmY).
  	dtLength2 > 0 ifTrue:[
  		dtX := (nrmX asFloat * fillHeight asFloat * 65536.0 / dtLength2 asFloat) asInteger.
  		dtY := (nrmY asFloat * fillHeight asFloat * 65536.0 / dtLength2 asFloat) asInteger.
  	] ifFalse:[dtX := 0. dtY := 0].
  	self fillOriginXOf: fill put: (point1 at: 0).
  	self fillOriginYOf: fill put: (point1 at: 1).
  	self fillDirectionXOf: fill put: dsX.
  	self fillDirectionYOf: fill put: dsY.
  	self fillNormalXOf: fill put: dtX.
  	self fillNormalYOf: fill put: dtY.
  !

Item was changed:
  ----- Method: BalloonEnginePlugin>>loadGradientFill:from:along:normal:isRadial: (in category 'fills-gradient') -----
  loadGradientFill: rampOop from: point1 along: point2 normal: point3 isRadial: isRadial
  	"Load the gradient fill as defined by the color ramp."
  	| rampWidth fill |
  	<inline: false>
+ 	<var: 'point1' type: #'int *'>
+ 	<var: 'point2' type: #'int *'>
+ 	<var: 'point3' type: #'int *'>
- 	<var: #point1 type:'int *'>
- 	<var: #point2 type:'int *'>
- 	<var: #point3 type:'int *'>
  	(interpreterProxy fetchClassOf: rampOop) = interpreterProxy classBitmap
  		ifFalse:[^interpreterProxy primitiveFail].
  	rampWidth := interpreterProxy slotSizeOf: rampOop.
  	fill := self allocateGradientFill: (interpreterProxy firstIndexableField: rampOop)
  				rampWidth: rampWidth isRadial: isRadial.
  	engineStopped ifTrue:[^nil].
  	self loadFillOrientation: fill 
  		from: point1 along: point2 normal: point3 
  		width: rampWidth height: rampWidth.
  	^fill!

Item was changed:
  ----- Method: BalloonEnginePlugin>>loadLine:from:to:offset:leftFill:rightFill: (in category 'lines-loading') -----
  loadLine: line from: point1 to: point2 offset: yOffset leftFill: leftFill rightFill: rightFill
  	"Load the line defined by point1 and point2."
  	| p1 p2 yDir |
+ 	<var: 'point1' type: #'int *'>
+ 	<var: 'point2' type: #'int *'>
+ 	<var: 'p1' type: #'int *'>
+ 	<var: 'p2' type: #'int *'>
- 	<var: #point1 type:'int *'>
- 	<var: #point2 type:'int *'>
- 	<var: #p1 type:'int *'>
- 	<var: #p2 type:'int *'>
  
  	(point1 at: 1) <= (point2 at: 1) 
  		ifTrue:[	p1 := point1.
  				p2 := point2.
  				yDir := 1]
  		ifFalse:[	p1 := point2.
  				p2 := point1.
  				yDir := -1].
  	self edgeXValueOf: line put: (p1 at: 0).
  	self edgeYValueOf: line put: (p1 at: 1) - yOffset.
  	self edgeZValueOf: line put: self currentZGet.
  	self edgeLeftFillOf: line put: leftFill.
  	self edgeRightFillOf: line put: rightFill.
  	self lineEndXOf: line put: (p2 at: 0).
  	self lineEndYOf: line put: (p2 at: 1) - yOffset.
  	self lineYDirectionOf: line put: yDir.!

Item was changed:
  ----- Method: BalloonEnginePlugin>>loadPointIntAt:from: (in category 'private') -----
  loadPointIntAt: index from: intArray
  	"Load the int value from the given index in intArray"
+ 	^(self cCoerce: intArray to: #'int *') at: index!
- 	^(self cCoerce: intArray to: 'int *') at: index!

Item was changed:
  ----- Method: BalloonEnginePlugin>>loadPointShortAt:from: (in category 'private') -----
  loadPointShortAt: index from: shortArray
  	"Load the short value from the given index in shortArray"
  	<returnTypeC:'short'>
+ 	^(self cCoerce: shortArray to: #'short *') at: index!
- 	^(self cCoerce: shortArray to: 'short *') at: index!

Item was changed:
  ----- Method: BalloonEnginePlugin>>loadPolygon:nPoints:fill:lineWidth:lineFill:pointsShort: (in category 'shapes-polygons') -----
  loadPolygon: points nPoints: nPoints fill: fillIndex lineWidth: lineWidth lineFill: lineFill pointsShort: isShort
  	| x0 y0 x1 y1 |
+ 	<var:#points type: #'int *'>
- 	<var:#points type:'int *'>
  	isShort ifTrue:[
  		x0 := self loadPointShortAt: 0 from: points.
  		y0 := self loadPointShortAt: 1 from: points.
  	] ifFalse:[
  		x0 := self loadPointIntAt: 0 from: points.
  		y0 := self loadPointIntAt: 1 from: points.
  	].
  	1 to: nPoints-1 do:[:i|
  		isShort ifTrue:[
  			x1 := self loadPointShortAt: i*2 from: points.
  			y1 := self loadPointShortAt: i*2+1 from: points.
  		] ifFalse:[
  			x1 := self loadPointIntAt: i*2 from: points.
  			y1 := self loadPointIntAt: i*2+1 from: points.
  		].
  		self point1Get at: 0 put: x0.
  		self point1Get at: 1 put: y0.
  		self point2Get at: 0 put: x1.
  		self point2Get at: 1 put: y1.
  		self transformPoints: 2.
  		self loadWideLine: lineWidth 
  			from: self point1Get
  			to: self point2Get
  			lineFill: lineFill 
  			leftFill: fillIndex
  			rightFill: 0.
  		engineStopped ifTrue:[^nil].
  		x0 := x1.
  		y0 := y1.
  	].!

Item was changed:
  ----- Method: BalloonEnginePlugin>>loadShape:nSegments:fill:lineWidth:lineFill:pointsShort: (in category 'shapes-polygons') -----
  loadShape: points nSegments: nSegments fill: fillIndex lineWidth: lineWidth lineFill: lineFill  pointsShort: pointsShort
  	<inline: false>
+ 	<var:#points type: #'int *'>
- 	<var:#points type:'int *'>
  	1 to: nSegments do:[:i|
  		self loadCompressedSegment: i-1
  			from: points
  			short: pointsShort
  			leftFill: fillIndex
  			rightFill: 0
  			lineWidth: lineWidth
  			lineColor: lineFill.
  		engineStopped ifTrue:[^nil].
  	].!

Item was changed:
  ----- Method: BalloonEnginePlugin>>loadWideLine:from:to:lineFill:leftFill:rightFill: (in category 'lines-loading') -----
  loadWideLine: lineWidth from: p1 to: p2 lineFill: lineFill leftFill: leftFill rightFill: rightFill
  	"Load a (possibly wide) line defined by the points p1 and p2"
  	| line offset |
+ 	<var: 'p1' type: #'int *'>
+ 	<var: 'p2' type: #'int *'>
- 	<var: #p1 type:'int *'>
- 	<var: #p2 type:'int *'>
  	(lineWidth = 0 or:[lineFill = 0])
  		ifTrue:[	line := self allocateLine.
  				offset := 0]
  		ifFalse:[	line := self allocateWideLine.
  				offset := self offsetFromWidth: lineWidth].
  	engineStopped ifTrue:[^0].
  	self loadLine: line 
  		from: p1
  		to: p2
  		offset: offset 
  		leftFill: leftFill
  		rightFill: rightFill.
  	(self isWide: line) ifTrue:[
  		self wideLineFillOf: line put: lineFill.
  		self wideLineWidthOf: line put: lineWidth.
  		self wideLineExtentOf: line put: lineWidth].!

Item was changed:
  ----- Method: BalloonEnginePlugin>>primitiveGetBezierStats (in category 'primitives') -----
  primitiveGetBezierStats
  	| failureCode statOop stats |
  	<export: true>
  	<inline: false>
+ 	<var: 'stats' type: #'int *'>
- 	<var: #stats type:'int *'>
  
  	interpreterProxy methodArgumentCount = 1
  		ifFalse:[^interpreterProxy primitiveFailFor: PrimErrBadNumArgs].
  
  	(failureCode := self quickLoadEngineFrom: (interpreterProxy stackValue: 1)) = 0
  		ifFalse:[^interpreterProxy primitiveFailFor: failureCode].
  
  	statOop := interpreterProxy stackObjectValue: 0.
  	(interpreterProxy failed not
  	and: [(interpreterProxy isWords: statOop)
  	and: [(interpreterProxy slotSizeOf: statOop) >= 4]])
  		ifFalse:[^interpreterProxy primitiveFailFor: PrimErrBadArgument].
  	stats := interpreterProxy firstIndexableField: statOop.
  	stats at: 0 put: (stats at: 0) + (workBuffer at: GWBezierMonotonSubdivisions).
  	stats at: 1 put: (stats at: 1) + (workBuffer at: GWBezierHeightSubdivisions).
  	stats at: 2 put: (stats at: 2) + (workBuffer at: GWBezierOverflowSubdivisions).
  	stats at: 3 put: (stats at: 3) + (workBuffer at: GWBezierLineConversions).
  
  	interpreterProxy pop: 1. "Leave rcvr on stack"!

Item was changed:
  ----- Method: BalloonEnginePlugin>>shortRunLengthAt:from: (in category 'private') -----
  shortRunLengthAt: i from: runArray
  	"Return the run-length value from the given ShortRunArray."
+ 	^((self cCoerce: runArray to: #'int *') at: i) bitShift: -16!
- 	^((self cCoerce: runArray to:'int *') at: i) bitShift: -16!

Item was changed:
  ----- Method: BalloonEnginePlugin>>shortRunValueAt:from: (in category 'private') -----
  shortRunValueAt: i from: runArray
  	"Return the run-length value from the given ShortRunArray.
  	Note: We don't need any coercion to short/int here, since
  	we deal basically only with unsigned values."
+ 	^(((self cCoerce: runArray to: #'int *') at: i) bitAnd: 16rFFFF)!
- 	^(((self cCoerce: runArray to:'int *') at: i) bitAnd: 16rFFFF)!

Item was changed:
  ----- Method: BalloonEnginePlugin>>stepToFirstBezierIn:at: (in category 'beziers-simple') -----
  stepToFirstBezierIn: bezier at: yValue
  	"Initialize the bezier at yValue.
  	TODO: Check if reducing maxSteps from 2*deltaY to deltaY 
  		brings a *significant* performance improvement.
  		In theory this should make for double step performance
  		but will cost in quality. Might be that the AA stuff will
  		compensate for this - but I'm not really sure."
  	| updateData deltaY maxSteps scaledStepSize squaredStepSize 
  	startX startY viaX viaY endX endY 
  	fwX1 fwX2 fwY1 fwY2 
  	fwDx fwDDx fwDy fwDDy |
  	<inline: false>
+ 	<var: 'updateData' type: #'int *'>
- 	<var: #updateData type:'int *'>
  
  
  	"Do a quick check if there is anything at all to do"
  	((self isWide: bezier) not and:[yValue >= (self bezierEndYOf: bezier)])
  		ifTrue:[^self edgeNumLinesOf: bezier put: 0].
  
  	"Now really initialize bezier"
  	startX := self edgeXValueOf: bezier.
  	startY := self edgeYValueOf: bezier.
  	viaX := self bezierViaXOf: bezier.
  	viaY := self bezierViaYOf: bezier.
  	endX := self bezierEndXOf: bezier.
  	endY := self bezierEndYOf: bezier.
  	deltaY := endY - startY.
  
  	"Initialize integer forward differencing"
  	fwX1 := (viaX - startX) * 2.
  	fwX2 := startX + endX - (viaX * 2).
  	fwY1 := (viaY - startY) * 2.
  	fwY2 := startY + endY - (viaY * 2).
  	maxSteps := deltaY * 2.
  	maxSteps < 2 ifTrue:[maxSteps := 2].
  	scaledStepSize := 16r1000000 // maxSteps.
  	squaredStepSize := self absoluteSquared8Dot24: scaledStepSize.
  	fwDx := fwX1 * scaledStepSize.
  	fwDDx := fwX2 * squaredStepSize * 2.
  	fwDx := fwDx + (fwDDx // 2).
  	fwDy := fwY1 * scaledStepSize.
  	fwDDy := fwY2 * squaredStepSize * 2.
  	fwDy := fwDy + (fwDDy // 2).
  
  	"Store the values"
  	self edgeNumLinesOf: bezier put: deltaY.
  
  	updateData := self bezierUpdateDataOf: bezier.
  	updateData at: GBUpdateX put: (startX * 256).
  	updateData at: GBUpdateY put: (startY * 256).
  	updateData at: GBUpdateDX put: fwDx.
  	updateData at: GBUpdateDY put: fwDy.
  	updateData at: GBUpdateDDX put: fwDDx.
  	updateData at: GBUpdateDDY put: fwDDy.
  
  	"And step to the first scan line"
  	(startY := self edgeYValueOf: bezier) = yValue ifFalse:[
  		self stepToNextBezierIn: bezier at: yValue.
  		"Adjust number of lines remaining"
  		self edgeNumLinesOf: bezier put: deltaY - (yValue - startY).
  	].!

Item was changed:
  ----- Method: BalloonEnginePlugin>>stepToNextBezierForward:at: (in category 'beziers-simple') -----
  stepToNextBezierForward: updateData at: yValue
  	"Incrementally step to the next scan line in the given bezier update data.
  	Note: This method has been written so that inlining works, e.g.,
+ 		not declaring updateData as 'int *' but casting it on every use."
+ 	<var: 'updateData' type: #'int *'>
- 		not declaring updateData as 'int*' but casting it on every use."
- 	<var: #updateData type:'int *'>
  	| minY lastX lastY fwDx fwDy |
  	<inline: true>
  	lastX := updateData at: GBUpdateX.
  	lastY := updateData at: GBUpdateY.
  	fwDx := updateData at: GBUpdateDX.
  	fwDy := updateData at: GBUpdateDY.
  	minY := yValue * 256.
  	"Step as long as we haven't yet reached minY and also
  	as long as fwDy is greater than zero thus stepping down.
  	Note: The test for fwDy should not be necessary in theory
  		but is a good insurance in practice."
  	[minY > lastY and:[fwDy >= 0]] whileTrue:[
  		lastX := lastX + ((fwDx + 16r8000) signedBitShift: -16).
  		lastY := lastY + ((fwDy + 16r8000) signedBitShift: -16).
  		fwDx := fwDx + (updateData at: GBUpdateDDX).
  		fwDy := fwDy + (updateData at: GBUpdateDDY).
  	].
  	updateData at: GBUpdateX put: lastX.
  	updateData at: GBUpdateY put: lastY.
  	updateData at: GBUpdateDX put: fwDx.
  	updateData at: GBUpdateDY put: fwDy.
  	^lastX signedBitShift: -8
  !

Item was changed:
  ----- Method: BitBltSimulation>>addWord:with: (in category 'combination rules') -----
  addWord: sourceWord with: destinationWord
  	<returnTypeC: 'unsigned int'>
+ 	<var: 'sourceWord' type: #'unsigned int'>
+ 	<var: 'destinationWord' type: #'unsigned int'>
- 	<var: #sourceWord type: 'unsigned int'>
- 	<var: #destinationWord type: 'unsigned int'>
  	^sourceWord + destinationWord!

Item was changed:
  ----- Method: BitBltSimulation>>alphaBlend:with: (in category 'combination rules') -----
  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 result blendRB blendAG |
  	<inline: false>
  	<returnTypeC: 'unsigned int'>
+ 	<var: 'sourceWord' type: #'unsigned int'>
+ 	<var: 'destinationWord' type: #'unsigned int'>
+ 	<var: 'blendRB' type: #'unsigned int'>
+ 	<var: 'blendAG' type: #'unsigned int'>
+ 	<var: 'result' type: #'unsigned int'>
+ 	<var: 'alpha' type: #'unsigned int'>
+ 	<var: 'unAlpha' type: #'unsigned int'>
- 	<var: #sourceWord type: 'unsigned int'>
- 	<var: #destinationWord type: 'unsigned int'>
- 	<var: #blendRB type: 'unsigned int'>
- 	<var: #blendAG type: 'unsigned int'>
- 	<var: #result type: 'unsigned int'>
- 	<var: #alpha type: 'unsigned int'>
- 	<var: #unAlpha type: 'unsigned int'>
  	alpha := sourceWord >> 24.  "High 8 bits of source pixel"
  	alpha = 0 ifTrue: [ ^ destinationWord ].
  	alpha = 255 ifTrue: [ ^ sourceWord ].
  	unAlpha := 255 - alpha.
  
  	blendRB := ((sourceWord bitAnd: 16rFF00FF) * alpha) +
  				((destinationWord bitAnd: 16rFF00FF) * unAlpha)
  				+ 16rFF00FF.	"blend red and blue"
  
  	blendAG := (((sourceWord>> 8 bitOr: 16rFF0000) bitAnd: 16rFF00FF) * alpha) +
  				((destinationWord>>8 bitAnd: 16rFF00FF) * unAlpha)
  				+ 16rFF00FF.	"blend alpha and green"
  
  	blendRB := blendRB + (blendRB - 16r10001 >> 8 bitAnd: 16rFF00FF) >> 8 bitAnd: 16rFF00FF.	"divide by 255"
  	blendAG := blendAG + (blendAG - 16r10001 >> 8 bitAnd: 16rFF00FF) >> 8 bitAnd: 16rFF00FF.
  	result := blendRB bitOr: blendAG<<8.
  	^ result
  !

Item was changed:
  ----- Method: BitBltSimulation>>alphaBlendConst:with: (in category 'combination rules') -----
  alphaBlendConst: sourceWord with: destinationWord
  	<returnTypeC: 'unsigned int'>
+ 	<var: 'sourceWord' type: #'unsigned int'>
+ 	<var: 'destinationWord' type: #'unsigned int'>
- 	<var: #sourceWord type: 'unsigned int'>
- 	<var: #destinationWord type: 'unsigned int'>
  
  	^ self alphaBlendConst: sourceWord with: destinationWord paintMode: false!

Item was changed:
  ----- Method: BitBltSimulation>>alphaBlendConst:with:paintMode: (in category 'combination rules') -----
  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 blendAG blendRB |
  	<inline: false>
  	<returnTypeC: 'unsigned int'>
+ 	<var: 'sourceWord' type: #'unsigned int'>
+ 	<var: 'destinationWord' type: #'unsigned int'>
+ 	<var: 'blendRB' type: #'unsigned int'>
+ 	<var: 'blendAG' type: #'unsigned int'>
+ 	<var: 'result' type: #'unsigned int'>
+ 	<var: 'sourceAlpha' type: #'unsigned int'>
+ 	<var: 'unAlpha' type: #'unsigned int'>
+ 	<var: 'sourceShifted' type: #'unsigned int'>
+ 	<var: 'destShifted' type: #'unsigned int'>
+ 	<var: 'maskShifted' type: #'unsigned int'>
+ 	<var: 'pixMask' type: #'unsigned int'>
+ 	<var: 'rgbMask' type: #'unsigned int'>
+ 	<var: 'pixBlend' type: #'unsigned int'>
+ 	<var: 'blend' type: #'unsigned int'>
- 	<var: #sourceWord type: 'unsigned int'>
- 	<var: #destinationWord type: 'unsigned int'>
- 	<var: #blendRB type: 'unsigned int'>
- 	<var: #blendAG type: 'unsigned int'>
- 	<var: #result type: 'unsigned int'>
- 	<var: #sourceAlpha type: 'unsigned int'>
- 	<var: #unAlpha type: 'unsigned int'>
- 	<var: #sourceShifted type: 'unsigned int'>
- 	<var: #destShifted type: 'unsigned int'>
- 	<var: #maskShifted type: 'unsigned int'>
- 	<var: #pixMask type: 'unsigned int'>
- 	<var: #rgbMask type: 'unsigned int'>
- 	<var: #pixBlend type: 'unsigned int'>
- 	<var: #blend type: 'unsigned int'>
  	destDepth < 16 ifTrue: [^ destinationWord "no-op"].
  	unAlpha := 255 - sourceAlpha.
  	result := destinationWord.
  	destPPW = 1 ifTrue:["32bpp blends include alpha"
  		paintMode & (sourceWord = 0)  "painting a transparent pixel" ifFalse:[
  
  				blendRB := ((sourceWord bitAnd: 16rFF00FF) * sourceAlpha) +
  						((destinationWord bitAnd: 16rFF00FF) * unAlpha) + 16rFF00FF.	"blendRB red and blue"
  
  				blendAG := ((sourceWord>> 8 bitAnd: 16rFF00FF) * sourceAlpha) +
  						((destinationWord>>8 bitAnd: 16rFF00FF) * unAlpha) + 16rFF00FF.	"blendRB alpha and green"
  
  				blendRB := blendRB + (blendRB - 16r10001 >> 8 bitAnd: 16rFF00FF) >> 8 bitAnd: 16rFF00FF.	"divide by 255"
  				blendAG := blendAG + (blendAG - 16r10001 >> 8 bitAnd: 16rFF00FF) >> 8 bitAnd: 16rFF00FF.
  				result := blendRB bitOr: blendAG<<8.
  		].
  	] ifFalse:[
  		pixMask := maskTable at: destDepth.
  		bitsPerColor := 5.
  		rgbMask := 16r1F.
  		maskShifted := destMask.
  		destShifted := destinationWord.
  		sourceShifted := sourceWord.
  		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].
  				result := (result bitAnd: (pixMask << (j-1*16)) bitInvert32)
  								bitOr: pixBlend << (j-1*16)].
  			maskShifted := maskShifted >> destDepth.
  			sourceShifted := sourceShifted >> destDepth.
  			destShifted := destShifted >> destDepth].
  	].
  	^ result
  !

Item was changed:
  ----- Method: BitBltSimulation>>alphaBlendScaled:with: (in category 'combination rules') -----
  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."
+ 	<returnTypeC: #'unsigned int'>
- 	| unAlpha rb ag |
  	<inline: false>	"Do NOT inline this into optimized loops"
+ 	| unAlpha rb ag |
+ 	<var: 'sourceWord' type: #'unsigned int'>
+ 	<var: 'destinationWord' type: #'unsigned int'>
+ 	<var: 'rb' type: #'unsigned int'>
+ 	<var: 'ag' type: #'unsigned int'>
+ 	<var: 'unAlpha' type: #'unsigned int'>
- 	<returnTypeC: 'unsigned int'>
- 	<var: #sourceWord type: 'unsigned int'>
- 	<var: #destinationWord type: 'unsigned int'>
- 	<var: #rb type: 'unsigned int'>
- 	<var: #ag type: 'unsigned int'>
- 	<var: #unAlpha type: 'unsigned int'>
  	unAlpha := 255 - (sourceWord >> 24).  "High 8 bits of source pixel is source opacity (ARGB format)"
  	rb := ((destinationWord bitAnd: 16rFF00FF) * unAlpha >> 8 bitAnd: 16rFF00FF) + (sourceWord bitAnd: 16rFF00FF). "blend red and blue components"
+ 	ag := ((destinationWord >> 8 bitAnd: 16rFF00FF) * unAlpha >> 8 bitAnd: 16rFF00FF) + (sourceWord >> 8 bitAnd: 16rFF00FF). "blend alpha and green components"
+ 	rb := (rb bitAnd: 16rFF00FF) bitOr: (rb bitAnd: 16r01000100) * 16rFF >> 8. "saturate red and blue components if there is a carry"
+ 	ag := (ag bitAnd: 16rFF00FF) << 8 bitOr: (ag bitAnd: 16r01000100) * 16rFF. "saturate alpha and green components if there is a carry"
- 	ag := ((destinationWord>>8 bitAnd: 16rFF00FF) * unAlpha >> 8 bitAnd: 16rFF00FF) + (sourceWord>>8 bitAnd: 16rFF00FF). "blend alpha and green components"
- 	rb := (rb bitAnd: 16rFF00FF) bitOr: (rb bitAnd: 16r1000100) * 16rFF >> 8. "saturate red and blue components if there is a carry"
- 	ag := (ag bitAnd: 16rFF00FF) << 8 bitOr: (ag bitAnd: 16r1000100) * 16rFF. "saturate alpha and green components if there is a carry"
  	^ag bitOr: rb "recompose"!

Item was changed:
  ----- Method: BitBltSimulation>>alphaBlendUnscaled:with: (in category 'combination rules') -----
  alphaBlendUnscaled: sourceWord with: destinationWord
  	"Blend sourceWord with destinationWord using the alpha value from both sourceWord and destinationWord.
  	Alpha is encoded as 0 meaning 0.0, and 255 meaning 1.0.
  	The alpha channel and color produced are
  
  		srcAlpha + (destAlpha*(1-srcAlpha))
  		(srcAlpha*srcColor + (destAlpha*(1-srcAlpha)*dstColor)) / (srcAlpha + (destAlpha*(1-srcAlpha)))
  
  	In contrast to alphaBlend:with: the method does not assume that destination form is opaque.
  	In contrast to alphaBlendScaled:with: the method does not assume that colors have been pre-scaled (muliplied) by alpha channel."
  	| alpha blendA result blendRB blendG |
  	<inline: false>
  	<returnTypeC: 'unsigned int'>
+ 	<var: 'sourceWord' type: #'unsigned int'>
+ 	<var: 'destinationWord' type: #'unsigned int'>
+ 	<var: 'blendRB' type: #'unsigned int'>
+ 	<var: 'blendG' type: #'unsigned int'>
+ 	<var: 'result' type: #'unsigned int'>
+ 	<var: 'alpha' type: #'unsigned int'>
+ 	<var: 'blendA' type: #'unsigned int'>
- 	<var: #sourceWord type: 'unsigned int'>
- 	<var: #destinationWord type: 'unsigned int'>
- 	<var: #blendRB type: 'unsigned int'>
- 	<var: #blendG type: 'unsigned int'>
- 	<var: #result type: 'unsigned int'>
- 	<var: #alpha type: 'unsigned int'>
- 	<var: #blendA type: 'unsigned int'>
  	alpha := sourceWord >> 24.  "High 8 bits of source pixel, assuming ARGB encoding"
  	alpha = 0 ifTrue: [ ^ destinationWord ].
  	alpha = 255 ifTrue: [ ^ sourceWord ].
  	
  	blendA := 16rFF * alpha + (16rFF - alpha * (destinationWord >> 24)) + 16rFF. "blend alpha channels"
  	blendA := blendA + (blendA - 1 >> 8 bitAnd: 16rFF) >> 8 bitAnd: 16rFF. "divide by 255"
  
  	blendRB := ((sourceWord bitAnd: 16rFF00FF) * alpha) +
  				((destinationWord bitAnd: 16rFF00FF) * (blendA-alpha))
  				/ blendA.	"blend red and blue"
  
  	blendG := ((sourceWord bitAnd: 16r00FF00) * alpha) +
  				((destinationWord bitAnd: 16r00FF00) * (blendA-alpha))
  				/ blendA.	"blend green"
  	result := (blendRB bitOr: blendG) bitOr: blendA << 24.
  	^ result
  !

Item was changed:
  ----- Method: BitBltSimulation>>alphaPaintConst:with: (in category 'combination rules') -----
  alphaPaintConst: sourceWord with: destinationWord
  	<returnTypeC: 'unsigned int'>
+ 	<var: 'sourceWord' type: #'unsigned int'>
+ 	<var: 'destinationWord' type: #'unsigned int'>
- 	<var: #sourceWord type: 'unsigned int'>
- 	<var: #destinationWord type: 'unsigned int'>
  
  	sourceWord = 0 ifTrue: [^ destinationWord  "opt for all-transparent source"].
  	^ self alphaBlendConst: sourceWord with: destinationWord paintMode: true!

Item was changed:
  ----- Method: BitBltSimulation>>alphaScale:with: (in category 'combination rules') -----
  alphaScale: sourceWord with: destinationWord
  	"Scale (premultiply) the destination with its alpha channel.
  	Note that sourceWord is ignored."
  	| alpha rb g |
  	<inline: false>	"Do NOT inline this into optimized loops"
  	<returnTypeC: 'unsigned int'>
+ 	<var: 'sourceWord' type: #'unsigned int'>
+ 	<var: 'destinationWord' type: #'unsigned int'>
+ 	<var: 'rb' type: #'unsigned int'>
+ 	<var: 'g' type: #'unsigned int'>
+ 	<var: 'alpha' type: #'unsigned int'>
- 	<var: #sourceWord type: 'unsigned int'>
- 	<var: #destinationWord type: 'unsigned int'>
- 	<var: #rb type: 'unsigned int'>
- 	<var: #g type: 'unsigned int'>
- 	<var: #alpha type: 'unsigned int'>
  	alpha := destinationWord >> 24.  "High 8 bits is opacity (ARGB format)"
  	rb := ((destinationWord bitAnd: 16rFF00FF) * alpha >> 8 bitAnd: 16rFF00FF). "scale red and blue components"
  	g := ((destinationWord bitAnd: 16r00FF00) * alpha >> 8 bitAnd: 16r00FF00). "scale green component"
  	^(g bitOr: rb) bitOr: (destinationWord bitAnd: 16rFF000000) "recompose"!

Item was changed:
  ----- Method: BitBltSimulation>>alphaSourceBlendBits16 (in category 'inner loop') -----
  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 |
  	<inline: false> "This particular method should be optimized in itself"
+ 	<var: 'sourceWord' type: #'unsigned int'>
+ 	<var: 'destWord' type: #'unsigned int'>
+ 	<var: 'dstMask' type: #'unsigned int'>
- 	<var: #sourceWord type: #'unsigned int'>
- 	<var: #destWord type: #'unsigned int'>
- 	<var: #dstMask type: #'unsigned int'>
  	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 >> 24.
  			srcAlpha = 255 ifTrue:[
  				"Dither from 32 to 16 bit"
  				sourceWord := self dither32To16: sourceWord threshold: ditherThreshold.
  				sourceWord = 0 
  					ifTrue:[sourceWord := 1 << srcShift]
  					ifFalse: [sourceWord := sourceWord << srcShift].
  				"Store masked value"
  				self dstLongAt: dstIndex put: sourceWord mask: dstMask.
  			] ifFalse:[ "srcAlpha ~= 255"
  				srcAlpha = 0 ifFalse:[ "0 < srcAlpha < 255"
  					"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 alphaBlendScaled: 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.
  	].!

Item was changed:
  ----- Method: BitBltSimulation>>alphaSourceBlendBits32 (in category 'inner loop') -----
  alphaSourceBlendBits32
  	"This version assumes 
  		combinationRule = 34
  		sourcePixSize = destPixSize = 32
  		sourceForm ~= destForm.
  	Note: The inner loop has been optimized for dealing
  		with the special cases of srcAlpha = 0.0 and srcAlpha = 1.0 
  	"
  	| srcIndex dstIndex sourceWord srcAlpha destWord deltaX deltaY srcY dstY |
  	<inline: false> "This particular method should be optimized in itself"
+ 	<var: 'sourceWord' type: #'unsigned int'>
+ 	<var: 'destWord' type: #'unsigned int'>
- 	<var: #sourceWord type: #'unsigned int'>
- 	<var: #destWord type: #'unsigned int'>
  
  	"Give the compile a couple of hints"
  
  	"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)"
  
  	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 >> 24.
  			srcAlpha = 255 ifTrue:[
  				self dstLongAt: dstIndex put: sourceWord.
  				srcIndex := srcIndex + 4.
  				dstIndex := dstIndex + 4.
  				"Now copy as many words as possible with alpha = 255"
  				[(deltaX := deltaX - 1) ~= 0 and:[
  					(sourceWord := self srcLongAt: srcIndex) >> 24 = 255]]
  						whileTrue:[
  							self dstLongAt: dstIndex put: sourceWord.
  							srcIndex := srcIndex + 4.
  							dstIndex := dstIndex + 4.
  						].
  				"Adjust deltaX"
  				deltaX := deltaX + 1.
  			] ifFalse:[ "srcAlpha ~= 255"
  				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) >> 24 = 0]]
  						whileTrue:[
  							srcIndex := srcIndex + 4.
  							dstIndex := dstIndex + 4.
  						].
  					"Adjust deltaX"
  					deltaX := deltaX + 1.
  				] ifFalse:[ "0 < srcAlpha < 255"
  					"If we have to mix colors then just copy a single word"
  					destWord := self dstLongAt: dstIndex.
  					destWord := self alphaBlendScaled: sourceWord with: destWord.
  					self dstLongAt: dstIndex put: destWord.
  					srcIndex := srcIndex + 4.
  					dstIndex := dstIndex + 4.
  				].
  			].
  		].
  		srcY := srcY + 1.
  		dstY := dstY + 1.
  	].!

Item was changed:
  ----- Method: BitBltSimulation>>alphaSourceBlendBits8 (in category 'inner loop') -----
  alphaSourceBlendBits8
  	"This version assumes 
  		combinationRule = 34
  		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 |
  	<inline: false>
+ 	<var: 'mappingTable' type: #'unsigned int *'>
+ 	<var: 'sourceWord' type: #'unsigned int'>
+ 	<var: 'destWord' type: #'unsigned int'>
+ 	<var: 'dstMask' type: #'unsigned int'>
- 	<var: #mappingTable type:'unsigned int *'>
- 	<var: #sourceWord type: #'unsigned int'>
- 	<var: #destWord type: #'unsigned int'>
- 	<var: #dstMask type: #'unsigned int'>
  	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 >> 24.
  			srcAlpha > 31 ifTrue:["Everything below 31 is transparent"
  				srcAlpha < 224 ifTrue:["Everything above 224 is opaque"
  					destWord := self dstLongAt: dstIndex.
  					destWord := destWord bitAnd: dstMask bitInvert32.
  					destWord := destWord >> srcShift.
  					destWord := mappingTable at: destWord.
  					sourceWord := self alphaBlendScaled: 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 = 24
  					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.
  	].!

Item was changed:
  ----- Method: BitBltSimulation>>alphaUnscale:with: (in category 'combination rules') -----
  alphaUnscale: sourceWord with: destinationWord
  	"Unscale (divide) the destination with its alpha channel.
  	Note that sourceWord is ignored."
  	| alpha rb g rgb carry |
  	<inline: false>	"Do NOT inline this into optimized loops"
  	<returnTypeC: 'unsigned int'>
+ 	<var: 'sourceWord' type: #'unsigned int'>
+ 	<var: 'destinationWord' type: #'unsigned int'>
+ 	<var: 'rb' type: #'unsigned int'>
+ 	<var: 'g' type: #'unsigned int'>
+ 	<var: 'rgb' type: #'unsigned int'>
+ 	<var: 'alpha' type: #'unsigned int'>
+ 	<var: 'carry' type: #'unsigned int'>
- 	<var: #sourceWord type: 'unsigned int'>
- 	<var: #destinationWord type: 'unsigned int'>
- 	<var: #rb type: 'unsigned int'>
- 	<var: #g type: 'unsigned int'>
- 	<var: #rgb type: 'unsigned int'>
- 	<var: #alpha type: 'unsigned int'>
- 	<var: #carry type: 'unsigned int'>
  	alpha := destinationWord >> 24.  "High 8 bits is opacity (ARGB format)"
  	alpha = 0 ifTrue: [^0].
  	rb := (destinationWord bitAnd: 16rFF00FF) << 8 / alpha. "unscale red and blue components"
  	g := (destinationWord bitAnd: 16r00FF00) / alpha. "unscale green component"
  	carry := ((rb >> 8 bitAnd: 16rAA00AA) >> 1 bitOr: (rb >> 8 bitAnd: 16r550055) << 1)
  		bitOr: ((g bitAnd: 16r00AA00) >> 1 bitOr: (g bitAnd: 16r005500) << 1).
  	carry := (carry bitAnd: 16rCCCCCC) >> 2 bitOr: (carry bitAnd: 16r333333) << 2.
  	carry := (carry bitAnd: 16rF0F0F0) >> 4 bitOr: (carry bitAnd: 16r0F0F0F) << 4.
  	rgb := (rb bitAnd: 16rFF00FF) bitOr: (g << 8 bitAnd: 16r00FF00).
  	rgb := rgb bitOr: carry.  "saturate RGB components if division overflows"
  	^rgb bitOr: (destinationWord bitAnd: 16rFF000000) "restore alpha"!

Item was changed:
  ----- Method: BitBltSimulation>>bitAnd:with: (in category 'combination rules') -----
  bitAnd: sourceWord with: destinationWord
  	<returnTypeC: 'unsigned int'>
+ 	<var: 'sourceWord' type: #'unsigned int'>
+ 	<var: 'destinationWord' type: #'unsigned int'>
- 	<var: #sourceWord type: 'unsigned int'>
- 	<var: #destinationWord type: 'unsigned int'>
  	^sourceWord bitAnd: destinationWord!

Item was changed:
  ----- Method: BitBltSimulation>>bitAndInvert:with: (in category 'combination rules') -----
  bitAndInvert: sourceWord with: destinationWord
  	<returnTypeC: 'unsigned int'>
+ 	<var: 'sourceWord' type: #'unsigned int'>
+ 	<var: 'destinationWord' type: #'unsigned int'>
- 	<var: #sourceWord type: 'unsigned int'>
- 	<var: #destinationWord type: 'unsigned int'>
  	^sourceWord bitAnd: destinationWord bitInvert32!

Item was changed:
  ----- Method: BitBltSimulation>>bitInvertAnd:with: (in category 'combination rules') -----
  bitInvertAnd: sourceWord with: destinationWord
  	<returnTypeC: 'unsigned int'>
+ 	<var: 'sourceWord' type: #'unsigned int'>
+ 	<var: 'destinationWord' type: #'unsigned int'>
- 	<var: #sourceWord type: 'unsigned int'>
- 	<var: #destinationWord type: 'unsigned int'>
  	^sourceWord bitInvert32 bitAnd: destinationWord!

Item was changed:
  ----- Method: BitBltSimulation>>bitInvertAndInvert:with: (in category 'combination rules') -----
  bitInvertAndInvert: sourceWord with: destinationWord
  	<returnTypeC: 'unsigned int'>
+ 	<var: 'sourceWord' type: #'unsigned int'>
+ 	<var: 'destinationWord' type: #'unsigned int'>
- 	<var: #sourceWord type: 'unsigned int'>
- 	<var: #destinationWord type: 'unsigned int'>
  	^sourceWord bitInvert32 bitAnd: destinationWord bitInvert32!

Item was changed:
  ----- Method: BitBltSimulation>>bitInvertDestination:with: (in category 'combination rules') -----
  bitInvertDestination: sourceWord with: destinationWord
  	<returnTypeC: 'unsigned int'>
+ 	<var: 'sourceWord' type: #'unsigned int'>
+ 	<var: 'destinationWord' type: #'unsigned int'>
- 	<var: #sourceWord type: 'unsigned int'>
- 	<var: #destinationWord type: 'unsigned int'>
  	^destinationWord bitInvert32!

Item was changed:
  ----- Method: BitBltSimulation>>bitInvertOr:with: (in category 'combination rules') -----
  bitInvertOr: sourceWord with: destinationWord
  	<returnTypeC: 'unsigned int'>
+ 	<var: 'sourceWord' type: #'unsigned int'>
+ 	<var: 'destinationWord' type: #'unsigned int'>
- 	<var: #sourceWord type: 'unsigned int'>
- 	<var: #destinationWord type: 'unsigned int'>
  	^sourceWord bitInvert32 bitOr: destinationWord!

Item was changed:
  ----- Method: BitBltSimulation>>bitInvertOrInvert:with: (in category 'combination rules') -----
  bitInvertOrInvert: sourceWord with: destinationWord
  	<returnTypeC: 'unsigned int'>
+ 	<var: 'sourceWord' type: #'unsigned int'>
+ 	<var: 'destinationWord' type: #'unsigned int'>
- 	<var: #sourceWord type: 'unsigned int'>
- 	<var: #destinationWord type: 'unsigned int'>
  	^sourceWord bitInvert32 bitOr: destinationWord bitInvert32!

Item was changed:
  ----- Method: BitBltSimulation>>bitInvertSource:with: (in category 'combination rules') -----
  bitInvertSource: sourceWord with: destinationWord
  	<returnTypeC: 'unsigned int'>
+ 	<var: 'sourceWord' type: #'unsigned int'>
+ 	<var: 'destinationWord' type: #'unsigned int'>
- 	<var: #sourceWord type: 'unsigned int'>
- 	<var: #destinationWord type: 'unsigned int'>
  	^sourceWord bitInvert32!

Item was changed:
  ----- Method: BitBltSimulation>>bitInvertXor:with: (in category 'combination rules') -----
  bitInvertXor: sourceWord with: destinationWord
  	<returnTypeC: 'unsigned int'>
+ 	<var: 'sourceWord' type: #'unsigned int'>
+ 	<var: 'destinationWord' type: #'unsigned int'>
- 	<var: #sourceWord type: 'unsigned int'>
- 	<var: #destinationWord type: 'unsigned int'>
  	^sourceWord bitInvert32 bitXor: destinationWord!

Item was changed:
  ----- Method: BitBltSimulation>>bitOr:with: (in category 'combination rules') -----
  bitOr: sourceWord with: destinationWord
  	<returnTypeC: 'unsigned int'>
+ 	<var: 'sourceWord' type: #'unsigned int'>
+ 	<var: 'destinationWord' type: #'unsigned int'>
- 	<var: #sourceWord type: 'unsigned int'>
- 	<var: #destinationWord type: 'unsigned int'>
  	^sourceWord bitOr: destinationWord!

Item was changed:
  ----- Method: BitBltSimulation>>bitOrInvert:with: (in category 'combination rules') -----
  bitOrInvert: sourceWord with: destinationWord
  	<returnTypeC: 'unsigned int'>
+ 	<var: 'sourceWord' type: #'unsigned int'>
+ 	<var: 'destinationWord' type: #'unsigned int'>
- 	<var: #sourceWord type: 'unsigned int'>
- 	<var: #destinationWord type: 'unsigned int'>
  	^sourceWord bitOr: destinationWord bitInvert32!

Item was changed:
  ----- Method: BitBltSimulation>>bitXor:with: (in category 'combination rules') -----
  bitXor: sourceWord with: destinationWord
  	<returnTypeC: 'unsigned int'>
+ 	<var: 'sourceWord' type: #'unsigned int'>
+ 	<var: 'destinationWord' type: #'unsigned int'>
- 	<var: #sourceWord type: 'unsigned int'>
- 	<var: #destinationWord type: 'unsigned int'>
  	^sourceWord bitXor: destinationWord!

Item was changed:
  ----- Method: BitBltSimulation>>clearWord:with: (in category 'combination rules') -----
  clearWord: sourceWord with: destinationWord
  	<returnTypeC: 'unsigned int'>
+ 	<var: 'sourceWord' type: #'unsigned int'>
+ 	<var: 'destinationWord' type: #'unsigned int'>
- 	<var: #sourceWord type: 'unsigned int'>
- 	<var: #destinationWord type: 'unsigned int'>
  	^ 0!

Item was changed:
  ----- Method: BitBltSimulation>>copyBits:Fallback: (in category 'setup') -----
  copyBits: op Fallback: flags
  	"Recover from the fast path specialised code saying Help-I-cant-cope"
  	|done |
  	<static: false>
  	<returnTypeC: 'void'>
  	<inline: false>
+ 	<var: 'op' type: #'operation_t *'>
+ 	<var: 'flags' type: #'unsigned int'>
- 	<var: #op type: 'operation_t *'>
- 	<var: #flags type:'unsigned int'>
  	self cppIf: #'ENABLE_FAST_BLT'
  		ifTrue:[
  			"recover values from the operation struct used by the fast ARM code"
  			self cCode:'
  	combinationRule = op->combinationRule;
  	noSource = op->noSource;
  	sourceBits = (sqInt) op->src.bits;
  	sourcePitch = op->src.pitch;
  	sourceDepth = op->src.depth;
  	sourceMSB = op->src.msb;
  	sx = op->src.x;
  	sy = op->src.y;
  	destBits = (sqInt) op->dest.bits;
  	destPitch = op->dest.pitch;
  	destDepth = op->dest.depth;
  	destMSB = op->dest.msb;
  	dx = op->dest.x;
  	dy = op->dest.y;
  	bbW = op->width;
  	bbH = op->height;
  	cmFlags = op->cmFlags;
  	cmShiftTable = (void *) op->cmShiftTable;
  	cmMaskTable = (void *) op->cmMaskTable;
  	cmMask = op->cmMask;
  	cmLookupTable = (void *) op->cmLookupTable;
  	noHalftone = op->noHalftone;
  	halftoneHeight = op->halftoneHeight;
  	halftoneBase = (sqInt) op->halftoneBase;
  	if (combinationRule == 30 || combinationRule == 31) {
  		sourceAlpha = op->opt.sourceAlpha;
  	}
  	if (combinationRule == 41) {
  		componentAlphaModeColor = op->opt.componentAlpha.componentAlphaModeColor;
  		componentAlphaModeAlpha = op->opt.componentAlpha.componentAlphaModeAlpha;
  		gammaLookupTable = (void *) op->opt.componentAlpha.gammaLookupTable;
  		ungammaLookupTable = (void *) op->opt.componentAlpha.ungammaLookupTable;
  	}'.
  	
  				destPPW := 32 / destDepth.
  				sourcePPW := 32 / sourceDepth.
  				cmBitsPerColor := 0.
  				cmMask = 16r1FF ifTrue: [cmBitsPerColor := 3].
  				cmMask = 16rFFF ifTrue: [cmBitsPerColor := 4].
  				cmMask = 16r7FFF ifTrue: [cmBitsPerColor := 5].
  				" In some places, sourceForm and destForm are compared in order to detect
  				 whether we're reading and writing the same image. However, these have
  				 not always been initialised by the time we get here, so substitute
  				 sourceBits and destBits if so. "
  				(sourceForm == 0 and: [destForm == 0])
  					ifTrue:
  						[sourceForm := sourceBits.
  						destForm := destBits].
  	
  				"Try a shortcut for stuff that should be run as quickly as possible"
  				done := self tryCopyingBitsQuickly.
  				done ifTrue:[^nil].
  
  				bitCount := 0.
  				"Choose and perform the actual copy loop."
  				self performCopyLoop]
  
  	
  
  
  !

Item was changed:
  ----- Method: BitBltSimulation>>copyLoop (in category 'inner loop') -----
  copyLoop
  	| prevWord thisWord skewWord halftoneWord mergeWord hInc y unskew skewMask notSkewMask mergeFnwith destWord |
  	"This version of the inner loop assumes noSource = false."
  	<inline: false>
+ 	<var: 'prevWord' type: #'unsigned int'>
+ 	<var: 'thisWord' type: #'unsigned int'>
+ 	<var: 'skewWord' type: #'unsigned int'>
+ 	<var: 'halftoneWord' type: #'unsigned int'>
+ 	<var: 'mergeWord' type: #'unsigned int'>
+ 	<var: 'destWord' type: #'unsigned int'>
+ 	<var: 'skewMask' type: #'unsigned int'>
+ 	<var: 'notSkewMask' type: #'unsigned int'>
+ 	<var: 'unskew' type: #int> "unskew is a bitShift and MUST remain signed, while skewMask is unsigned."
+ 	<var: 'mergeFnwith' declareC: 'unsigned int (*mergeFnwith)(unsigned int, unsigned int)'>
+ 	mergeFnwith := self cCoerce: (opTable at: combinationRule+1) to: #'unsigned int (*)(unsigned int, unsigned int)'.
- 	<var: #prevWord type: #'unsigned int'>
- 	<var: #thisWord type: #'unsigned int'>
- 	<var: #skewWord type: #'unsigned int'>
- 	<var: #halftoneWord type: #'unsigned int'>
- 	<var: #mergeWord type: #'unsigned int'>
- 	<var: #destWord type: #'unsigned int'>
- 	<var: #skewMask type: #'unsigned int'>
- 	<var: #notSkewMask type: #'unsigned int'>
- 	<var: #unskew type: #int> "unskew is a bitShift and MUST remain signed, while skewMask is unsigned."
- 	<var: #mergeFnwith declareC: 'unsigned int (*mergeFnwith)(unsigned int, unsigned int)'>
- 	mergeFnwith := self cCoerce: (opTable at: combinationRule+1) to: 'unsigned int (*)(unsigned int, unsigned int)'.
  	mergeFnwith.  "null ref for compiler"
  
  	self deny: (preload and: [skew = 0]).
  	self assert: (skew between: -31 and: 31).
  
  	hInc := hDir * 4.  "Byte delta"
  	skew < 0
  		ifTrue: [unskew := skew + 32. skewMask := AllOnes << (0 - skew).
  				self cCode: [] inSmalltalk: [skewMask := skewMask bitAnd: 16rFFFFFFFF]]
  		ifFalse:
  			[skew = 0
  				ifTrue: [unskew := 0. skewMask := AllOnes]
  				ifFalse: [unskew := skew - 32. skewMask := AllOnes >> skew]].
  
  	notSkewMask := skewMask bitInvert32.
  	noHalftone
  		ifTrue: [halftoneWord := AllOnes.  halftoneHeight := 0]
  		ifFalse: [halftoneWord := self halftoneAt: 0].
  
  	y := dy.
  	"Here is the vertical loop, in two versions, one for the combinationRule = 3 copy mode, one for the general case."
  	combinationRule = 3
  		ifTrue:
  			[1 to: bbH do: "here is the vertical loop for combinationRule = 3 copy mode; no need to call merge"
  				[ :i |
  				halftoneHeight > 1 ifTrue:  "Otherwise, its always the same"
  					[halftoneWord := self halftoneAt: y.
  					y := y + vDir].
  				preload
  					ifTrue: "load the 64-bit shifter"
  						[prevWord := self srcLongAt: sourceIndex.
  						self incSrcIndex: hInc]
  					ifFalse:
  						[prevWord := 0].
  
  				"Note: the horizontal loop has been expanded into three parts for speed:"
  
  				"This first section requires masking of the destination store..."
  				destMask := mask1.
  				thisWord := self srcLongAt: sourceIndex.  "pick up next word"
  				self incSrcIndex: hInc.
  				skewWord := ((prevWord bitAnd: notSkewMask) bitShift: unskew)
  								bitOr:  "32-bit rotate"
  									((thisWord bitAnd: skewMask) bitShift: skew).
  				prevWord := thisWord.
  				destWord := self dstLongAt: destIndex.
  				destWord := (destMask bitAnd: (skewWord bitAnd: halftoneWord))
  								bitOr: (destWord bitAnd: destMask bitInvert32).
  				self dstLongAt: destIndex put: destWord.
  				self incDestIndex: hInc.
  
  				"This central horizontal loop requires no store masking"
  				destMask := AllOnes.
  				(skew = 0 and: [halftoneWord = AllOnes])
  					ifTrue: "Very special inner loop for STORE mode with no skew -- just move words"
  						[(preload and: [hDir = 1])
  							ifTrue:
  								[2 to: nWords-1 do: 
  									[ :word |  "Note loop starts with prevWord loaded (due to preload)"
  									self dstLongAt: destIndex put: prevWord.
  									self incDestIndex: hInc.
  									prevWord := self srcLongAt: sourceIndex.
  									self incSrcIndex: hInc]]
  							ifFalse:
  								[2 to: nWords-1 do: 
  									[ :word |
  									thisWord := self srcLongAt: sourceIndex.
  									self incSrcIndex: hInc.
  									self dstLongAt: destIndex put: thisWord.
  									self incDestIndex: hInc].
  								 prevWord := thisWord]]
  						ifFalse:
  							[2 to: nWords-1 do: 
  								[ :word |
  								thisWord := self srcLongAt: sourceIndex.
  								self incSrcIndex: hInc.
  								skewWord := ((prevWord bitAnd: notSkewMask) bitShift: unskew)
  												bitOr:  "32-bit rotate"
  											((thisWord bitAnd: skewMask) bitShift: skew).
  								prevWord := thisWord.
  								self dstLongAt: destIndex put: (skewWord bitAnd: halftoneWord).
  								self incDestIndex: hInc]].
  
  				"This last section, if used, requires masking of the destination store..."
  				nWords > 1 ifTrue:
  					[destMask := mask2.
  					thisWord :=((skewMask bitShift: skew) bitAnd: mask2) = 0
  						ifTrue: [0 "we don't need more bits, they will all come from prevWord"]
  						ifFalse: [self srcLongAt: sourceIndex.  "pick up last bits from next word".].
  					self incSrcIndex: hInc. "Note: this will be undone by inncSrcIndex: sourceDelta below if undue"
  					skewWord := ((prevWord bitAnd: notSkewMask) bitShift: unskew)
  									bitOr:  "32-bit rotate"
  										((thisWord bitAnd: skewMask) bitShift: skew).
  					destWord := self dstLongAt: destIndex.
  					destWord := (destMask bitAnd: (skewWord bitAnd: halftoneWord))
  									bitOr: (destWord bitAnd: destMask bitInvert32).
  					self dstLongAt: destIndex put: destWord.
  					self incDestIndex: hInc].
  
  				self incSrcIndex: sourceDelta.
  				self incDestIndex: destDelta]]
  		ifFalse:
  			[1 to: bbH do: "here is the vertical loop for the general case (combinationRule ~= 3)"
  				[ :i |
  				halftoneHeight > 1 ifTrue:  "Otherwise, its always the same"
  					[halftoneWord := self halftoneAt: y.
  					y := y + vDir].
  				preload
  					ifTrue: "load the 64-bit shifter"
  						[prevWord := self srcLongAt: sourceIndex.
  						self incSrcIndex: hInc]
  					ifFalse:
  						[prevWord := 0].
  
  				"Note: the horizontal loop has been expanded into three parts for speed:"
  
  				"This first section requires masking of the destination store..."
  				destMask := mask1.
  				thisWord := self srcLongAt: sourceIndex.  "pick up next word"
  				self incSrcIndex: hInc.
  				skewWord := ((prevWord bitAnd: notSkewMask) bitShift: unskew)
  								bitOr:  "32-bit rotate"
  							((thisWord bitAnd: skewMask) bitShift: skew).
  				prevWord := thisWord.
  				destWord := self dstLongAt: destIndex.
  				mergeWord := self mergeFn: (skewWord bitAnd: halftoneWord) with: destWord.
  				destWord := (destMask bitAnd: mergeWord)
  								bitOr: (destWord bitAnd: destMask bitInvert32).
  				self dstLongAt: destIndex put: destWord.
  				self incDestIndex: hInc.
  
  				"This central horizontal loop requires no store masking"
  				destMask := AllOnes.
  				2 to: nWords-1 do: "Normal inner loop does merge:"
  					[ :word |
  					thisWord := self srcLongAt: sourceIndex.  "pick up next word"
  					self incSrcIndex: hInc.
  					skewWord := ((prevWord bitAnd: notSkewMask) bitShift: unskew)
  									bitOr:  "32-bit rotate"
  								((thisWord bitAnd: skewMask) bitShift: skew).
  					prevWord := thisWord.
  					mergeWord := self mergeFn: (skewWord bitAnd: halftoneWord)
  									with: (self dstLongAt: destIndex).
  					self dstLongAt: destIndex put: mergeWord.
  					self incDestIndex: hInc].
  
  				"This last section, if used, requires masking of the destination store..."
  				nWords > 1 ifTrue:
  					[destMask := mask2.
  					thisWord :=((skewMask bitShift: skew) bitAnd: mask2) = 0
  						ifTrue: [0 "we don't need more bits, they will all come from prevWord"]
  						ifFalse: [self srcLongAt: sourceIndex.  "pick up last bits from next word".].
  					self incSrcIndex: hInc. "Note: this will be undone by incSrcIndex: sourceDelta below if undue"
  					skewWord := ((prevWord bitAnd: notSkewMask) bitShift: unskew)
  									bitOr:  "32-bit rotate"
  								((thisWord bitAnd: skewMask) bitShift: skew).
  					destWord := self dstLongAt: destIndex.
  					mergeWord := self mergeFn: (skewWord bitAnd: halftoneWord) with: destWord.
  					destWord := (destMask bitAnd: mergeWord)
  									bitOr: (destWord bitAnd: destMask bitInvert32).
  					self dstLongAt: destIndex put: destWord.
  					self incDestIndex: hInc].
  
  				self incSrcIndex: sourceDelta.
  				self incDestIndex: destDelta]]!

Item was changed:
  ----- Method: BitBltSimulation>>copyLoopNoSource (in category 'inner loop') -----
  copyLoopNoSource
  	"Faster copyLoop when source not used.  hDir and vDir are both
  	positive, and perload and skew are unused"
  	| halftoneWord mergeWord mergeFnwith destWord |
  	<inline: false>
+ 	<var: 'mergeFnwith' declareC: 'unsigned int (*mergeFnwith)(unsigned int, unsigned int)'>
+ 	<var: 'halftoneWord' type: #'unsigned int'>
+ 	<var: 'mergeWord' type: #'unsigned int'>
+ 	<var: 'destWord' type: #'unsigned int'>
+ 	mergeFnwith := self cCoerce: (opTable at: combinationRule+1) to: #'unsigned int (*)(unsigned int, unsigned int)'.
- 	<var: #mergeFnwith declareC: 'unsigned int (*mergeFnwith)(unsigned int, unsigned int)'>
- 	<var: #halftoneWord type: #'unsigned int'>
- 	<var: #mergeWord type: #'unsigned int'>
- 	<var: #destWord type: #'unsigned int'>
- 	mergeFnwith := self cCoerce: (opTable at: combinationRule+1) to: 'unsigned int (*)(unsigned int, unsigned int)'.
  	mergeFnwith.  "null ref for compiler"
  
  	noHalftone ifTrue:
  		[halftoneWord := AllOnes].
  	1 to: bbH do: "here is the vertical loop"
  		[ :i |
  		noHalftone ifFalse:
  			[halftoneWord := self halftoneAt: dy+i-1].
  
  	"Note: the horizontal loop has been expanded into three parts for speed:"
  
  		"This first section requires masking of the destination store..."
  		destMask := mask1.
  		destWord := self dstLongAt: destIndex.
  		mergeWord := self mergeFn: halftoneWord
  						with: destWord.
  		destWord := (destMask bitAnd: mergeWord) bitOr: 
  						(destWord bitAnd: destMask bitInvert32).
  		self dstLongAt: destIndex put: destWord.
  		self incDestIndex: 4.
  
  	"This central horizontal loop requires no store masking"
  		destMask := AllOnes.
  		combinationRule = 3
  			ifTrue: "Special inner loop for STORE"
  				[destWord := halftoneWord.
  				2 to: nWords-1 do:[ :word |
  					self dstLongAt: destIndex put: destWord.
  					self incDestIndex: 4]]
  			ifFalse: "Normal inner loop does merge"
  				[2 to: nWords-1 do:[ :word | "Normal inner loop does merge"
  					destWord := self dstLongAt: destIndex.
  					mergeWord := self mergeFn: halftoneWord with: destWord.
  					self dstLongAt: destIndex put: mergeWord.
  					self incDestIndex: 4]].
  
  		"This last section, if used, requires masking of the destination store..."
  		nWords > 1 ifTrue:
  			[destMask := mask2.
  			destWord := self dstLongAt: destIndex.
  			mergeWord := self mergeFn: halftoneWord with: destWord.
  			destWord := (destMask bitAnd: mergeWord) bitOr:
  							(destWord bitAnd: destMask bitInvert32).
  			self dstLongAt: destIndex put: destWord.
  			self incDestIndex: 4].
  
  		self incDestIndex: destDelta]!

Item was changed:
  ----- Method: BitBltSimulation>>copyLoopPixMap (in category 'inner loop') -----
  copyLoopPixMap
  	"This version of the inner loop maps source pixels
  	to a destination form with different depth.  Because it is already
  	unweildy, the loop is not unrolled as in the other versions.
  	Preload, skew and skewMask are all overlooked, since pickSourcePixels
  	delivers its destination word already properly aligned.
  	Note that pickSourcePixels could be copied in-line at the top of
  	the horizontal loop, and some of its inits moved out of the loop."
  	"ar 12/7/1999:
  	The loop has been rewritten to use only one pickSourcePixels call.
  	The idea is that the call itself could be inlined. If we decide not
  	to inline pickSourcePixels we could optimize the loop instead."
  	| skewWord halftoneWord mergeWord scrStartBits nSourceIncs startBits endBits sourcePixMask destPixMask mergeFnwith nPix srcShift dstShift destWord words srcShiftInc dstShiftInc dstShiftLeft mapperFlags |
  	<inline: false>
+ 	<var: 'mergeFnwith' declareC: 'unsigned int (*mergeFnwith)(unsigned int, unsigned int)'>
+ 	<var: 'skewWord' type: #'unsigned int'>
+ 	<var: 'halftoneWord' type: #'unsigned int'>
+ 	<var: 'mergeWord' type: #'unsigned int'>
+ 	<var: 'destWord' type: #'unsigned int'>
+ 	<var: 'sourcePixMask' type: #'unsigned int'>
+ 	<var: 'destPixMask' type: #'unsigned int'>
+ 	mergeFnwith := self cCoerce: (opTable at: combinationRule+1) to: #'unsigned int (*)(unsigned int, unsigned int)'.
- 	<var: #mergeFnwith declareC: 'unsigned int (*mergeFnwith)(unsigned int, unsigned int)'>
- 	<var: #skewWord type: #'unsigned int'>
- 	<var: #halftoneWord type: #'unsigned int'>
- 	<var: #mergeWord type: #'unsigned int'>
- 	<var: #destWord type: #'unsigned int'>
- 	<var: #sourcePixMask type: #'unsigned int'>
- 	<var: #destPixMask type: #'unsigned int'>
- 	mergeFnwith := self cCoerce: (opTable at: combinationRule+1) to: 'unsigned int (*)(unsigned int, unsigned int)'.
  	mergeFnwith.  "null ref for compiler"
  
  	"Additional inits peculiar to unequal source and dest pix size..."
  	sourcePPW := 32//sourceDepth.
  	sourcePixMask := maskTable at: sourceDepth.
  	destPixMask := maskTable at: destDepth.
  	mapperFlags := cmFlags bitAnd: ColorMapNewStyle bitInvert32.
  	sourceIndex := sourceBits +
  					(sy * sourcePitch) + ((sx // sourcePPW) *4).
  	scrStartBits := sourcePPW - (sx bitAnd: sourcePPW-1).
  	bbW < scrStartBits
  		ifTrue: [nSourceIncs := 0]
  		ifFalse: [nSourceIncs := (bbW - scrStartBits)//sourcePPW + 1].
  	sourceDelta := sourcePitch - (nSourceIncs * 4).
  
  	"Note following two items were already calculated in destmask setup!!"
  	startBits := destPPW - (dx bitAnd: destPPW-1).
  	endBits := ((dx + bbW - 1) bitAnd: destPPW-1) + 1.
  
  	bbW < startBits ifTrue:[startBits := bbW].
  
  	"Precomputed shifts for pickSourcePixels"
  	srcShift := ((sx bitAnd: sourcePPW - 1) * sourceDepth).
  	dstShift := ((dx bitAnd: destPPW - 1) * destDepth).
  	srcShiftInc := sourceDepth.
  	dstShiftInc := destDepth.
  	dstShiftLeft := 0.
  	sourceMSB ifTrue:[
  		srcShift := 32 - sourceDepth - srcShift.
  		srcShiftInc := 0 - srcShiftInc].
  	destMSB ifTrue:[
  		dstShift := 32 - destDepth - dstShift.
  		dstShiftInc := 0 - dstShiftInc.
  		dstShiftLeft := 32 - destDepth].
  	noHalftone ifTrue:
  		[halftoneWord := AllOnes].
  	1 to: bbH do: "here is the vertical loop"
  		[ :i |
  		noHalftone ifFalse:
  			[halftoneWord := self halftoneAt: dy+i-1].
  		"setup first load"
  		srcBitShift := srcShift.
  		dstBitShift := dstShift.
  		destMask := mask1.
  		nPix := startBits.
  		"Here is the horizontal loop..."
  		words := nWords.
  			["pick up the word"
  			skewWord := self pickSourcePixels: nPix flags: mapperFlags 
  								srcMask: sourcePixMask destMask: destPixMask
  								srcShiftInc: srcShiftInc dstShiftInc: dstShiftInc.
  			"align next word to leftmost pixel"
  			dstBitShift := dstShiftLeft.
  
  			destMask = AllOnes ifTrue:["avoid read-modify-write"
  				mergeWord := self mergeFn: (skewWord bitAnd: halftoneWord)
  								with: (self dstLongAt: destIndex).
  				self dstLongAt: destIndex put: (destMask bitAnd: mergeWord).
  			] ifFalse:[ "General version using dest masking"
  				destWord := self dstLongAt: destIndex.
  				mergeWord := self mergeFn: (skewWord bitAnd: halftoneWord)
  								with: (destWord bitAnd: destMask).
  				destWord := (destMask bitAnd: mergeWord) bitOr:
  								(destWord bitAnd: destMask bitInvert32).
  				self dstLongAt: destIndex put: destWord.
  			].
  			self incDestIndex: 4.
  			words = 2 "e.g., is the next word the last word?"
  				ifTrue:["set mask for last word in this row"
  						destMask := mask2.
  						nPix := endBits]
  				ifFalse:["use fullword mask for inner loop"
  						destMask := AllOnes.
  						nPix := destPPW].
  			(words := words - 1) = 0] whileFalse.
  		"--- end of inner loop ---"
  		self incSrcIndex: sourceDelta.
  		self incDestIndex: destDelta]
  !

Item was changed:
  ----- Method: BitBltSimulation>>default8To32Table (in category 'pixel mapping') -----
  default8To32Table
  	"Return the default translation table from 1..8 bit indexed colors to 32bit"
  	"The table has been generated by the following statements"
  	"| pvs hex |
  	String streamContents:[:s|
  		s nextPutAll:'static unsigned int theTable[256] = { '.
  		pvs := (Color colorMapIfNeededFrom: 8 to: 32) asArray.
  		1 to: pvs size do:[:i|
  			i > 1 ifTrue:[s nextPutAll:', '].
  			(i-1 \\ 8) = 0 ifTrue:[s cr].
  			s nextPutAll:'0x'.
  			hex := (pvs at: i) printStringBase: 16.
  			s nextPutAll: (hex copyFrom: 4 to: hex size).
  		].
  		s nextPutAll:'};'.
  	]."
  	| theTable |
  	<returnTypeC:'unsigned int *'>
+ 	<var: 'theTable' declareC:'static unsigned int theTable[256] = { 
- 	<var: #theTable declareC:'static unsigned int theTable[256] = { 
  0x0, 0xFF000001, 0xFFFFFFFF, 0xFF808080, 0xFFFF0000, 0xFF00FF00, 0xFF0000FF, 0xFF00FFFF, 
  0xFFFFFF00, 0xFFFF00FF, 0xFF202020, 0xFF404040, 0xFF606060, 0xFF9F9F9F, 0xFFBFBFBF, 0xFFDFDFDF, 
  0xFF080808, 0xFF101010, 0xFF181818, 0xFF282828, 0xFF303030, 0xFF383838, 0xFF484848, 0xFF505050, 
  0xFF585858, 0xFF686868, 0xFF707070, 0xFF787878, 0xFF878787, 0xFF8F8F8F, 0xFF979797, 0xFFA7A7A7, 
  0xFFAFAFAF, 0xFFB7B7B7, 0xFFC7C7C7, 0xFFCFCFCF, 0xFFD7D7D7, 0xFFE7E7E7, 0xFFEFEFEF, 0xFFF7F7F7, 
  0xFF000001, 0xFF003300, 0xFF006600, 0xFF009900, 0xFF00CC00, 0xFF00FF00, 0xFF000033, 0xFF003333, 
  0xFF006633, 0xFF009933, 0xFF00CC33, 0xFF00FF33, 0xFF000066, 0xFF003366, 0xFF006666, 0xFF009966, 
  0xFF00CC66, 0xFF00FF66, 0xFF000099, 0xFF003399, 0xFF006699, 0xFF009999, 0xFF00CC99, 0xFF00FF99, 
  0xFF0000CC, 0xFF0033CC, 0xFF0066CC, 0xFF0099CC, 0xFF00CCCC, 0xFF00FFCC, 0xFF0000FF, 0xFF0033FF, 
  0xFF0066FF, 0xFF0099FF, 0xFF00CCFF, 0xFF00FFFF, 0xFF330000, 0xFF333300, 0xFF336600, 0xFF339900, 
  0xFF33CC00, 0xFF33FF00, 0xFF330033, 0xFF333333, 0xFF336633, 0xFF339933, 0xFF33CC33, 0xFF33FF33, 
  0xFF330066, 0xFF333366, 0xFF336666, 0xFF339966, 0xFF33CC66, 0xFF33FF66, 0xFF330099, 0xFF333399, 
  0xFF336699, 0xFF339999, 0xFF33CC99, 0xFF33FF99, 0xFF3300CC, 0xFF3333CC, 0xFF3366CC, 0xFF3399CC, 
  0xFF33CCCC, 0xFF33FFCC, 0xFF3300FF, 0xFF3333FF, 0xFF3366FF, 0xFF3399FF, 0xFF33CCFF, 0xFF33FFFF, 
  0xFF660000, 0xFF663300, 0xFF666600, 0xFF669900, 0xFF66CC00, 0xFF66FF00, 0xFF660033, 0xFF663333, 
  0xFF666633, 0xFF669933, 0xFF66CC33, 0xFF66FF33, 0xFF660066, 0xFF663366, 0xFF666666, 0xFF669966, 
  0xFF66CC66, 0xFF66FF66, 0xFF660099, 0xFF663399, 0xFF666699, 0xFF669999, 0xFF66CC99, 0xFF66FF99, 
  0xFF6600CC, 0xFF6633CC, 0xFF6666CC, 0xFF6699CC, 0xFF66CCCC, 0xFF66FFCC, 0xFF6600FF, 0xFF6633FF, 
  0xFF6666FF, 0xFF6699FF, 0xFF66CCFF, 0xFF66FFFF, 0xFF990000, 0xFF993300, 0xFF996600, 0xFF999900, 
  0xFF99CC00, 0xFF99FF00, 0xFF990033, 0xFF993333, 0xFF996633, 0xFF999933, 0xFF99CC33, 0xFF99FF33, 
  0xFF990066, 0xFF993366, 0xFF996666, 0xFF999966, 0xFF99CC66, 0xFF99FF66, 0xFF990099, 0xFF993399, 
  0xFF996699, 0xFF999999, 0xFF99CC99, 0xFF99FF99, 0xFF9900CC, 0xFF9933CC, 0xFF9966CC, 0xFF9999CC, 
  0xFF99CCCC, 0xFF99FFCC, 0xFF9900FF, 0xFF9933FF, 0xFF9966FF, 0xFF9999FF, 0xFF99CCFF, 0xFF99FFFF, 
  0xFFCC0000, 0xFFCC3300, 0xFFCC6600, 0xFFCC9900, 0xFFCCCC00, 0xFFCCFF00, 0xFFCC0033, 0xFFCC3333, 
  0xFFCC6633, 0xFFCC9933, 0xFFCCCC33, 0xFFCCFF33, 0xFFCC0066, 0xFFCC3366, 0xFFCC6666, 0xFFCC9966, 
  0xFFCCCC66, 0xFFCCFF66, 0xFFCC0099, 0xFFCC3399, 0xFFCC6699, 0xFFCC9999, 0xFFCCCC99, 0xFFCCFF99, 
  0xFFCC00CC, 0xFFCC33CC, 0xFFCC66CC, 0xFFCC99CC, 0xFFCCCCCC, 0xFFCCFFCC, 0xFFCC00FF, 0xFFCC33FF, 
  0xFFCC66FF, 0xFFCC99FF, 0xFFCCCCFF, 0xFFCCFFFF, 0xFFFF0000, 0xFFFF3300, 0xFFFF6600, 0xFFFF9900, 
  0xFFFFCC00, 0xFFFFFF00, 0xFFFF0033, 0xFFFF3333, 0xFFFF6633, 0xFFFF9933, 0xFFFFCC33, 0xFFFFFF33, 
  0xFFFF0066, 0xFFFF3366, 0xFFFF6666, 0xFFFF9966, 0xFFFFCC66, 0xFFFFFF66, 0xFFFF0099, 0xFFFF3399, 
  0xFFFF6699, 0xFFFF9999, 0xFFFFCC99, 0xFFFFFF99, 0xFFFF00CC, 0xFFFF33CC, 0xFFFF66CC, 0xFFFF99CC, 
  0xFFFFCCCC, 0xFFFFFFCC, 0xFFFF00FF, 0xFFFF33FF, 0xFFFF66FF, 0xFFFF99FF, 0xFFFFCCFF, 0xFFFFFFFF};'>
  	^theTable!

Item was changed:
  ----- Method: BitBltSimulation>>destinationWord:with: (in category 'combination rules') -----
  destinationWord: sourceWord with: destinationWord
  	<returnTypeC: 'unsigned int'>
+ 	<var: 'sourceWord' type: #'unsigned int'>
+ 	<var: 'destinationWord' type: #'unsigned int'>
- 	<var: #sourceWord type: 'unsigned int'>
- 	<var: #destinationWord type: 'unsigned int'>
  	^destinationWord!

Item was changed:
  ----- Method: BitBltSimulation>>dither32To16:threshold: (in category 'pixel mapping') -----
  dither32To16: srcWord threshold: ditherValue
  	"Dither the given 32bit word to 16 bit. Ignore alpha."
  	| addThreshold  |
  	<inline: true> "You bet"
  	<returnTypeC: 'unsigned int'>
+ 	<var: 'srcWord' type: #'unsigned int'>
- 	<var: #srcWord type: 'unsigned int'>
  	addThreshold := ditherValue bitShift: 8.
  	^((dither8Lookup at: (addThreshold+((srcWord bitShift: -16) bitAnd: 255))) bitShift: 10) + 
  		((dither8Lookup at: (addThreshold+((srcWord bitShift: -8) bitAnd: 255))) bitShift: 5) + 
  		(dither8Lookup at: (addThreshold+(srcWord bitAnd: 255))).
  !

Item was changed:
  ----- Method: BitBltSimulation>>expensiveDither32To16:threshold: (in category 'pixel mapping') -----
  expensiveDither32To16: srcWord threshold: ditherValue
  	"Dither the given 32bit word to 16 bit. Ignore alpha."
  	| pv threshold value out |
  	<inline: true> "You bet"
  	<returnTypeC: 'unsigned int'>
+ 	<var: 'srcWord' type: #'unsigned int'>
- 	<var: #srcWord type: 'unsigned int'>
  	pv := srcWord bitAnd: 255.
  	threshold := ditherThresholds16 at: (pv bitAnd: 7).
  	value := ditherValues16 at: (pv bitShift: -3).
  	ditherValue < threshold
  		ifTrue:[out := value + 1]
  		ifFalse:[out := value].
  	pv := (srcWord bitShift: -8) bitAnd: 255.
  	threshold := ditherThresholds16 at: (pv bitAnd: 7).
  	value := ditherValues16 at: (pv bitShift: -3).
  	ditherValue < threshold
  		ifTrue:[out := out bitOr: (value+1 bitShift:5)]
  		ifFalse:[out := out bitOr: (value bitShift: 5)].
  	pv := (srcWord bitShift: -16) bitAnd: 255.
  	threshold := ditherThresholds16 at: (pv bitAnd: 7).
  	value := ditherValues16 at: (pv bitShift: -3).
  	ditherValue < threshold
  		ifTrue:[out := out bitOr: (value+1 bitShift:10)]
  		ifFalse:[out := out bitOr: (value bitShift: 10)].
  	^out!

Item was changed:
  ----- Method: BitBltSimulation>>fetchIntOrFloat:ofObject: (in category 'interpreter interface') -----
  fetchIntOrFloat: fieldIndex ofObject: objectPointer
  	"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."
  	| fieldOop floatValue |
+ 	<var: 'floatValue' type: #double>
- 	<var: #floatValue type:'double '>
  	fieldOop := interpreterProxy fetchPointer: fieldIndex ofObject: objectPointer.
  	(interpreterProxy isIntegerObject: fieldOop)
  		ifTrue:[^interpreterProxy integerValueOf: fieldOop].
  	floatValue := interpreterProxy floatValueOf: fieldOop.
  	(-2147483648.0 <= floatValue and:[floatValue <= 2147483647.0])
  		ifFalse:[interpreterProxy primitiveFail. ^0].
  	^floatValue asInteger!

Item was changed:
  ----- Method: BitBltSimulation>>fetchIntOrFloat:ofObject:ifNil: (in category 'interpreter interface') -----
  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."
  	| fieldOop floatValue |
+ 	<var: 'floatValue' type: #double>
- 	<var: #floatValue type:'double '>
  	fieldOop := interpreterProxy fetchPointer: fieldIndex ofObject: objectPointer.
  	(interpreterProxy isIntegerObject: fieldOop)
  		ifTrue:[^interpreterProxy integerValueOf: fieldOop].
  	(fieldOop = interpreterProxy nilObject) ifTrue:[^defaultValue].
  	floatValue := interpreterProxy floatValueOf: fieldOop.
  	(-2147483648.0 <= floatValue and:[floatValue <= 2147483647.0])
  		ifFalse:[interpreterProxy primitiveFail. ^0].
  	^floatValue asInteger!

Item was changed:
  ----- Method: BitBltSimulation>>fixAlpha:with: (in category 'combination rules') -----
  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."
  	<returnTypeC: 'unsigned int'>
+ 	<var: 'sourceWord' type: #'unsigned int'>
+ 	<var: 'destinationWord' type: #'unsigned int'>
- 	<var: #sourceWord type: 'unsigned int'>
- 	<var: #destinationWord type: 'unsigned int'>
  	destDepth = 32 ifFalse:[^destinationWord]. "no-op for non 32bpp"
  	destinationWord = 0 ifTrue:[^0].
  	(destinationWord bitAnd: 16rFF000000) = 0 ifFalse:[^destinationWord].
  	^destinationWord bitOr: (sourceWord bitAnd: 16rFF000000)
  !

Item was changed:
  ----- Method: BitBltSimulation>>isIdentityMap:with: (in category 'interpreter interface') -----
  isIdentityMap: shifts with: masks
  	"Return true if shiftTable/maskTable define an identity mapping."
+ 	<var: 'shifts' type: #'int *'>
+ 	<var: 'masks' type: #'unsigned int *'>
- 	<var: #shifts type:'int *'>
- 	<var: #masks type:'unsigned int *'>
  	(shifts == nil or:[masks == nil]) ifTrue:[^true].
  	((shifts at: RedIndex) = 0 
  		and:[(shifts at: GreenIndex) = 0
  		and:[(shifts at: BlueIndex) = 0 
  		and:[(shifts at: AlphaIndex) = 0
  			and:[((masks at: RedIndex) = 16rFF0000)
  			and:[((masks at: GreenIndex) = 16r00FF00)
  			and:[((masks at: BlueIndex) = 16r0000FF)
  			and:[((masks at: AlphaIndex) = 16rFF000000)]]]]]]])
  		ifTrue:[^true].
  	^false!

Item was changed:
  ----- Method: BitBltSimulation>>merge:with: (in category 'combination rules') -----
  merge: sourceWord with: destinationWord
  	| mergeFnwith |
  	"Sender warpLoop is too big to include this in-line"
+ 	<var: 'mergeFnwith' declareC: 'unsigned int (*mergeFnwith)(unsigned int, unsigned int)'>
- 	<var: #mergeFnwith declareC: 'unsigned int (*mergeFnwith)(unsigned int, unsigned int)'>
  	<returnTypeC: 'unsigned int'>
+ 	<var: 'sourceWord' type: #'unsigned int'>
+ 	<var: 'destinationWord' type: #'unsigned int'>
+ 	mergeFnwith := self cCoerce: (opTable at: combinationRule+1) to: #'unsigned int (*)(unsigned int, unsigned int)'.
- 	<var: #sourceWord type: 'unsigned int'>
- 	<var: #destinationWord type: 'unsigned int'>
- 	mergeFnwith := self cCoerce: (opTable at: combinationRule+1) to: 'unsigned int (*)(unsigned int, unsigned int)'.
  	mergeFnwith.  "null ref for compiler"
  
  	^ self mergeFn: sourceWord with: destinationWord!

Item was changed:
  ----- Method: BitBltSimulation>>moduleUnloaded: (in category 'initialize-release') -----
  moduleUnloaded: aModuleName
  	"The module with the given name was just unloaded.
  	 Make sure we have no dangling references."
  	<export: true>
+ 	<var: 'aModuleName' type: #'char *'>
- 	<var: #aModuleName type: 'char *'>
  	(aModuleName strcmp: 'SurfacePlugin') = 0 ifTrue: "The surface plugin just shut down. How nasty."
  		[querySurfaceFn := 0.
  		 lockSurfaceFn := 0.
  		 unlockSurfaceFn := 0]!

Item was changed:
  ----- Method: BitBltSimulation>>partitionedAND:to:nBits:nPartitions: (in category 'combination rules') -----
  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 |
  	<returnTypeC: 'unsigned int'>
+ 	<var: 'word1' type: #'unsigned int'>
+ 	<var: 'word2' type: #'unsigned int'>
+ 	<var: 'result' type: #'unsigned int'>
+ 	<var: 'mask' type: #'unsigned int'>
- 	<var: #word1 type: 'unsigned int'>
- 	<var: #word2 type: 'unsigned int'>
- 	<var: #result type: 'unsigned int'>
- 	<var: #mask type: 'unsigned int'>
  	mask := maskTable at: nBits.  "partition mask starts at the right"
  	result := 0.
  	nBits = 32
  		ifTrue:
  			[word1 = mask ifTrue: [result := result bitOr: word2]]
  		ifFalse:
  			[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!

Item was changed:
  ----- Method: BitBltSimulation>>partitionedAdd:to:nBits:componentMask:carryOverflowMask: (in category 'combination rules') -----
  partitionedAdd: word1 to: word2 nBits: nBits componentMask: componentMask carryOverflowMask: carryOverflowMask
  	"Add word1 to word2 as nParts partitions of nBits each.
  	This is useful for packed pixels, or packed colors"
  	| carryOverflow sum w1 w2 |
  	"Use unsigned int everywhere because it has a well known arithmetic model without undefined behavior w.r.t. overflow and shifts"
  	<returnTypeC: 'unsigned int'>
+ 	 <var: 'word1' type: #'unsigned int'>
+ 	<var: 'word2' type: #'unsigned int'>
+ 	 <var: 'w1' type: #'unsigned int'>
+ 	<var: 'w2' type: #'unsigned int'>
+ 	<var: 'componentMask' type: #'unsigned int'>
+ 	<var: 'carryOverflowMask' type: #'unsigned int'>
+ 	<var: 'carryOverflow' type: #'unsigned int'>
+ 	<var: 'sum' type: #'unsigned int'>
- 	 <var: #word1 type: 'unsigned int'>
- 	<var: #word2 type: 'unsigned int'>
- 	 <var: #w1 type: 'unsigned int'>
- 	<var: #w2 type: 'unsigned int'>
- 	<var: #componentMask type: 'unsigned int'>
- 	<var: #carryOverflowMask type: 'unsigned int'>
- 	<var: #carryOverflow type: 'unsigned int'>
- 	<var: #sum type: 'unsigned int'>
  	w1 := word1 bitAnd: carryOverflowMask. "mask to remove high bit of each component"
  	w2 := word2 bitAnd: carryOverflowMask.
  	sum := (word1 bitXor: w1)+(word2 bitXor: w2). "sum without high bit to avoid overflowing over next component"
  	carryOverflow := (w1 bitAnd: w2) bitOr: ((w1 bitOr: w2) bitAnd: sum). "detect overflow condition for saturating"
  	^((sum bitXor: w1)bitXor:w2) "sum high bit without overflow"
  		bitOr: carryOverflow>>(nBits-1) * componentMask "saturate in case of overflow"!

Item was changed:
  ----- Method: BitBltSimulation>>partitionedMax:with:nBits:nPartitions: (in category 'combination rules') -----
  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)"
  	<returnTypeC: 'unsigned int'>
+ 	<var: 'word1' type: #'unsigned int'>
+ 	<var: 'word2' type: #'unsigned int'>
+ 	<var: 'mask' type: #'unsigned int'>
+ 	<var: 'result' type: #'unsigned int'>
- 	<var: #word1 type: 'unsigned int'>
- 	<var: #word2 type: 'unsigned int'>
- 	<var: #mask type: 'unsigned int'>
- 	<var: #result type: 'unsigned int'>
  	nBits = 32
  		ifTrue:
  			[result := word2 max: word1]
  		ifFalse:
  			[result := 0.
  			mask := maskTable at: nBits.  "partition mask starts at the right"
  			1 to: nParts do:
  				[:i |
  				result := result bitOr: ((word2 bitAnd: mask) max: (word1 bitAnd: mask)).
  				mask := mask << nBits  "slide left to next partition"]].
  	^ result
  !

Item was changed:
  ----- Method: BitBltSimulation>>partitionedMin:with:nBits:nPartitions: (in category 'combination rules') -----
  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)"
  	<returnTypeC: 'unsigned int'>
+ 	<var: 'word1' type: #'unsigned int'>
+ 	<var: 'word2' type: #'unsigned int'>
+ 	<var: 'mask' type: #'unsigned int'>
+ 	<var: 'result' type: #'unsigned int'>
- 	<var: #word1 type: 'unsigned int'>
- 	<var: #word2 type: 'unsigned int'>
- 	<var: #mask type: 'unsigned int'>
- 	<var: #result type: 'unsigned int'>
  	nBits = 32
  		ifTrue:
  			[result := word2 min: word1]
  		ifFalse:
  			[result := 0.
  			mask := maskTable at: nBits.  "partition mask starts at the right"
  			1 to: nParts do:
  				[:i |
  				result := result bitOr: ((word2 bitAnd: mask) min: (word1 bitAnd: mask)).
  				mask := mask << nBits  "slide left to next partition"]].
  	^ result
  !

Item was changed:
  ----- Method: BitBltSimulation>>partitionedMul:with:nBits:nPartitions: (in category 'combination rules') -----
  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)"
  	<returnTypeC: 'unsigned int'>
+ 	<var: 'word1' type: #'unsigned int'>
+ 	<var: 'word2' type: #'unsigned int'>
+ 	<var: 'sMask' type: #'unsigned int'>
+ 	<var: 'dMask' type: #'unsigned int'>
+ 	<var: 'result' type: #'unsigned int'>
+ 	<var: 'product' type: #'unsigned int'>
- 	<var: #word1 type: 'unsigned int'>
- 	<var: #word2 type: 'unsigned int'>
- 	<var: #sMask type: 'unsigned int'>
- 	<var: #dMask type: 'unsigned int'>
- 	<var: #result type: 'unsigned int'>
- 	<var: #product type: 'unsigned int'>
  	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"!

Item was changed:
  ----- Method: BitBltSimulation>>partitionedRgbComponentAlpha:dest:nBits:nPartitions: (in category 'combination rules') -----
  partitionedRgbComponentAlpha: sourceWord dest: destWord nBits: nBits nPartitions: nParts
  	| mask result p1 p2 v |
  	<returnTypeC: 'unsigned int'>
+ 	<var: 'sourceWord' type: #'unsigned int'>
+ 	<var: 'destWord' type: #'unsigned int'>
+ 	<var: 'p1' type: #'unsigned int'>
+ 	<var: 'p2' type: #'unsigned int'>
+ 	<var: 'mask' type: #'unsigned int'>
+ 	<var: 'result' type: #'unsigned int'>
- 	<var: #sourceWord type: 'unsigned int'>
- 	<var: #destWord type: 'unsigned int'>
- 	<var: #p1 type: 'unsigned int'>
- 	<var: #p2 type: 'unsigned int'>
- 	<var: #mask type: 'unsigned int'>
- 	<var: #result type: 'unsigned int'>
  	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
  !

Item was changed:
  ----- Method: BitBltSimulation>>partitionedSub:from:nBits:nPartitions: (in category 'combination rules') -----
  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)"
  	<returnTypeC: 'unsigned int'>
+ 	<var: 'word1' type: #'unsigned int'>
+ 	<var: 'word2' type: #'unsigned int'>
+ 	<var: 'p1' type: #'unsigned int'>
+ 	<var: 'p2' type: #'unsigned int'>
+ 	<var: 'mask' type: #'unsigned int'>
+ 	<var: 'result' type: #'unsigned int'>
- 	<var: #word1 type: 'unsigned int'>
- 	<var: #word2 type: 'unsigned int'>
- 	<var: #p1 type: 'unsigned int'>
- 	<var: #p2 type: 'unsigned int'>
- 	<var: #mask type: 'unsigned int'>
- 	<var: #result type: 'unsigned int'>
  	nBits = 32
  		ifTrue:
  			[result := word1 < word2
  				ifTrue: [word2 - word1]
  				ifFalse: [word1 - word2]]
  		ifFalse:
  			[result := 0.
  			mask := maskTable at: nBits.  "partition mask starts at the right"
  			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
  !

Item was changed:
  ----- Method: BitBltSimulation>>pickSourcePixels:flags:srcMask:destMask:srcShiftInc:dstShiftInc: (in category 'combination rules') -----
  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 |
  	<inline: true> "oh please"
  	<returnTypeC: 'unsigned int'>
+ 	<var: 'sourceWord' type: #'unsigned int'>
+ 	<var: 'destWord' type: #'unsigned int'>
- 	<var: #sourceWord type: #'unsigned int'>
- 	<var: #destWord type: #'unsigned int'>
  	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"
  			sourceWord := self srcLongAt: sourceIndex.
  			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:
  				[srcShift := sourceMSB ifTrue: [srcShift + 32] ifFalse: [srcShift - 32].
  				 self incSrcIndex: 4].
  		(nPix := nPix - 1) = 0] whileFalse.
  	] ifFalse:[
  		[	"grab, colormap and mix in pixel"
  			sourceWord := self srcLongAt: sourceIndex.
  			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:
  				[srcShift := sourceMSB ifTrue: [srcShift + 32] ifFalse: [srcShift - 32].
  				 self incSrcIndex: 4].
  		(nPix := nPix - 1) = 0] whileFalse.
  	].
  	srcBitShift := srcShift. "Store back"
  	^destWord
  !

Item was changed:
  ----- Method: BitBltSimulation>>pickWarpPixelAtX:y: (in category 'pixel mapping') -----
  pickWarpPixelAtX: xx y: yy
  	"Pick a single pixel from the source for WarpBlt.
  	Note: This method is crucial for WarpBlt speed w/o smoothing
  	and still relatively important when smoothing is used."
  	| x y srcIndex sourceWord sourcePix |
  	<inline: true> "*please*"
  	<returnTypeC: #'unsigned int'>
+ 	<var: 'sourceWord' type: #'unsigned int'>
- 	<var: #sourceWord type: #'unsigned int'>
  
  	"note: it would be much faster if we could just
  	avoid these stupid tests for being inside sourceForm."
  	(xx < 0 or:[yy < 0 or:[
  		(x := xx >> BinaryPoint) >= sourceWidth or:[
  			(y := yy >> BinaryPoint) >= sourceHeight]]]) ifTrue:[^0]. "out of bounds"
  
  	"Fetch source word.
  	Note: We should really update srcIndex with sx and sy so that
  	we don't have to do the computation below. We might even be
  	able to simplify the out of bounds test from above."
  	srcIndex := sourceBits + (y * sourcePitch) + (x >> warpAlignShift * 4).
  	sourceWord := self srcLongAt: srcIndex.
  
  	"Extract pixel from word"
  	srcBitShift := warpBitShiftTable at: (x bitAnd: warpAlignMask).
  	sourcePix := sourceWord >> srcBitShift bitAnd: warpSrcMask.
  	^sourcePix!

Item was changed:
  ----- Method: BitBltSimulation>>pixClear:with: (in category 'combination rules') -----
  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 |
  	<inline: false>
  	<returnTypeC: 'unsigned int'>
+ 	<var: 'sourceWord' type: #'unsigned int'>
+ 	<var: 'destinationWord' type: #'unsigned int'>
+ 	<var: 'mask' type: #'unsigned int'>
+ 	<var: 'pv' type: #'unsigned int'>
+ 	<var: 'result' type: #'unsigned int'>
- 	<var: #sourceWord type: 'unsigned int'>
- 	<var: #destinationWord type: 'unsigned int'>
- 	<var: #mask type: 'unsigned int'>
- 	<var: #pv type: 'unsigned int'>
- 	<var: #result type: 'unsigned int'>
  	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!

Item was changed:
  ----- Method: BitBltSimulation>>pixMask:with: (in category 'combination rules') -----
  pixMask: sourceWord with: destinationWord
  	<inline: false>
  	<returnTypeC: 'unsigned int'>
+ 	<var: 'sourceWord' type: #'unsigned int'>
+ 	<var: 'destinationWord' type: #'unsigned int'>
- 	<var: #sourceWord type: 'unsigned int'>
- 	<var: #destinationWord type: 'unsigned int'>
  	^ self partitionedAND: sourceWord bitInvert32 to: destinationWord
  					nBits: destDepth nPartitions: destPPW!

Item was changed:
  ----- Method: BitBltSimulation>>pixPaint:with: (in category 'combination rules') -----
  pixPaint: sourceWord with: destinationWord
  	<inline: false>
  	<returnTypeC: 'unsigned int'>
+ 	<var: 'sourceWord' type: #'unsigned int'>
+ 	<var: 'destinationWord' type: #'unsigned int'>
- 	<var: #sourceWord type: 'unsigned int'>
- 	<var: #destinationWord type: 'unsigned int'>
  	sourceWord = 0 ifTrue: [^ destinationWord].
  	^ sourceWord bitOr:
  		(self partitionedAND: sourceWord bitInvert32 to: destinationWord
  						nBits: destDepth nPartitions: destPPW)!

Item was changed:
  ----- Method: BitBltSimulation>>pixSwap:with: (in category 'combination rules') -----
  pixSwap: sourceWord with: destWord
  	"Swap the pixels in destWord"
  	| result shift lowMask highMask |
  	<inline: false>
  	<returnTypeC: 'unsigned int'>
+ 	<var: 'sourceWord' type: #'unsigned int'>
+ 	<var: 'destWord' type: #'unsigned int'>
+ 	<var: 'lowMask' type: #'unsigned int'>
+ 	<var: 'highMask' type: #'unsigned int'>
+ 	<var: 'result' type: #'unsigned int'>
- 	<var: #sourceWord type: 'unsigned int'>
- 	<var: #destWord type: 'unsigned int'>
- 	<var: #lowMask type: 'unsigned int'>
- 	<var: #highMask type: 'unsigned int'>
- 	<var: #result type: 'unsigned int'>
  	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!

Item was changed:
  ----- Method: BitBltSimulation>>primitiveDisplayString (in category 'primitives') -----
  primitiveDisplayString
  	<export: true>
  	| kernDelta xTable glyphMap stopIndex startIndex sourceString bbObj maxGlyph ascii glyphIndex sourcePtr left quickBlt |
+ 	<var: 'sourcePtr' type: #'char *'>
- 	<var: #sourcePtr type: #'char *'>
  	interpreterProxy methodArgumentCount = 6 ifFalse:
  		[^interpreterProxy primitiveFail].
  	kernDelta := interpreterProxy stackIntegerValue: 0.
  	xTable := interpreterProxy stackValue: 1.
  	glyphMap := interpreterProxy stackValue: 2.
  	stopIndex := interpreterProxy stackIntegerValue: 3.
  	startIndex := interpreterProxy stackIntegerValue: 4.
  	sourceString := interpreterProxy stackValue: 5.
  	bbObj := interpreterProxy stackObjectValue: 6.
  	interpreterProxy failed ifTrue:
  		[^nil].
  
  	((interpreterProxy isArray: xTable)
  	 and: [(interpreterProxy isArray: glyphMap)
  	 and: [(interpreterProxy slotSizeOf: glyphMap) = 256
  	 and: [(interpreterProxy isBytes: sourceString)
  	 and: [startIndex > 0
  	 and: [stopIndex >= 0 "to avoid failing for empty strings..."
  	 and: [stopIndex <= (interpreterProxy byteSizeOf: sourceString)
  	 and: [(self loadBitBltFrom: bbObj)
  	 and: [combinationRule ~= 30 "these two need extra source alpha"
  	 and: [combinationRule ~= 31]]]]]]]]]) ifFalse:
  		[^interpreterProxy primitiveFail].
  	stopIndex = 0 ifTrue:
  		[^interpreterProxy pop: 6 "the string is empty; pop args, return rcvr"].
  	maxGlyph := (interpreterProxy slotSizeOf: xTable) - 2.
  	"See if we can go directly into copyLoopPixMap (usually we can)"
  	quickBlt := destBits ~= 0 "no OS surfaces please"
  				and:[sourceBits ~= 0 "and again"
  				and:[noSource = false "needs a source"
  				and:[sourceForm ~= destForm "no blits onto self"
  				and:[cmFlags ~= 0 
  					 or:[sourceMSB ~= destMSB 
  					 or:[sourceDepth ~= destDepth]]]]]]. "no point using slower version"
  	quickBlt
  		ifTrue:
  			[endOfSource := sourceBits + (sourcePitch * sourceHeight).
  			 endOfDestination := destBits + (destPitch * destHeight)]
  		ifFalse:
  			[self lockSurfaces ifFalse:
  				[^interpreterProxy primitiveFail]].
  	left := destX.
  	sourcePtr := interpreterProxy firstIndexableField: sourceString.
  	startIndex to: stopIndex do:
  		[:charIndex|
  		ascii := interpreterProxy byteAtPointer: sourcePtr + charIndex - 1.
  		glyphIndex := interpreterProxy fetchInteger: ascii ofObject: glyphMap.
  		(glyphIndex < 0 or: [glyphIndex > maxGlyph])  ifTrue:
  			[^interpreterProxy primitiveFail].
  		sourceX := interpreterProxy fetchInteger: glyphIndex ofObject: xTable.
  		width := (interpreterProxy fetchInteger: glyphIndex + 1 ofObject: xTable) - sourceX.
  		interpreterProxy failed ifTrue:
  			[^nil].
  		self clipRange.	"Must clip here"
  		(bbW > 0 and: [bbH > 0]) ifTrue:
  			[quickBlt
  				ifTrue:
  					[self destMaskAndPointerInit.
  					 self copyLoopPixMap.
  					 "both, hDir and vDir are known to be > 0"
  					 affectedL := dx.
  					 affectedR := dx + bbW.
  					 affectedT := dy.
  					 affectedB := dy + bbH]
  				ifFalse:
  					[self copyBitsLockedAndClipped]].
  		interpreterProxy failed ifTrue:
  			[^nil].
  		destX := destX + width + kernDelta].
  	affectedL := left.
  	quickBlt ifFalse:
  		[self unlockSurfaces].
  	self showDisplayBits.
  	"store destX back"	
  	interpreterProxy storeInteger: BBDestXIndex ofObject: bbObj withValue: destX.
  	interpreterProxy pop: 6 "pop args, return rcvr"!

Item was changed:
  ----- Method: BitBltSimulation>>rgbAdd:with: (in category 'combination rules') -----
  rgbAdd: sourceWord with: destinationWord
  	<inline: false>
  	<returnTypeC: 'unsigned int'>
+ 	<var: 'sourceWord' type: #'unsigned int'>
+ 	<var: 'destinationWord' type: #'unsigned int'>
+ 	<var: 'carryOverflowMask' type: #'unsigned int'>
+ 	<var: 'componentMask' type: #'unsigned int'>
- 	<var: #sourceWord type: 'unsigned int'>
- 	<var: #destinationWord type: 'unsigned int'>
- 	<var: #carryOverflowMask type: 'unsigned int'>
- 	<var: #componentMask type: 'unsigned int'>
  	| componentMask carryOverflowMask |
  	destDepth < 16 ifTrue:
  		["Add each pixel separately"
  		componentMask := 1<<destDepth-1.
  		carryOverflowMask := 16rFFFFFFFF//componentMask<<(destDepth-1).
  		^ self partitionedAdd: sourceWord to: destinationWord
  						nBits: destDepth componentMask: componentMask carryOverflowMask: carryOverflowMask].
  	destDepth = 16 ifTrue:
  		["Add RGB components of each pixel separately"
  		componentMask := 16r1F.
  		carryOverflowMask := 16r42104210.
  		^ (self partitionedAdd: (sourceWord bitAnd: 16r7FFF7FFF) to: (destinationWord bitAnd: 16r7FFF7FFF) "make sure that the unused bit is at 0"
  						nBits: 5 componentMask: componentMask carryOverflowMask: carryOverflowMask)]
  	ifFalse:
  		["Add RGBA components of the pixel separately"
  		componentMask := 16rFF.
  		carryOverflowMask := 16r80808080.
  		^ self partitionedAdd: sourceWord to: destinationWord
  						nBits: 8 componentMask: componentMask carryOverflowMask: carryOverflowMask]!

Item was changed:
  ----- Method: BitBltSimulation>>rgbComponentAlpha16 (in category 'combination rules') -----
  rgbComponentAlpha16
  	"This version assumes 
  		combinationRule = 41
  		sourcePixSize = 32
  		destPixSize = 16
  		sourceForm ~= destForm.
  	"
  	<inline: false>  "This particular method should be optimized in itself"
+ 	<var: 'sourceWord' type: #'unsigned int'>
+ 	<var: 'destWord' type: #'unsigned int'>
+ 	<var: 'dstMask' type: #'unsigned int'>
- 	<var: #sourceWord type: #'unsigned int'>
- 	<var: #destWord type: #'unsigned int'>
- 	<var: #dstMask type: #'unsigned int'>
  	
  	| 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).
  			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.
  	].
  !

Item was changed:
  ----- Method: BitBltSimulation>>rgbComponentAlpha32 (in category 'combination rules') -----
  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 |
  
  	<inline: false> "This particular method should be optimized in itself"
  
  	"Give the compile a couple of hints"
+ 	<var: 'deltaX' type: #'register sqInt'>
+ 	<var: 'sourceWord' type: #'unsigned int'>
+ 	<var: 'destWord' type: #'unsigned int'>
- 	<var: #deltaX type: 'register sqInt'>
- 	<var: #sourceWord type: #'unsigned int'>
- 	<var: #destWord type: #'unsigned int'>
  
  	"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)"
+ 	<var: 'srcIndex' type: #'register sqIntptr_t'>
+ 	<var: 'dstIndex' type: #'register sqIntptr_t'>
- 	<var: #srcIndex type: 'register sqIntptr_t'>
- 	<var: #dstIndex type: 'register sqIntptr_t'>
  	
  	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.
  	].!

Item was changed:
  ----- Method: BitBltSimulation>>rgbComponentAlpha8 (in category 'combination rules') -----
  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 |
  	
  	<inline: false>  "This particular method should be optimized in itself"
+ 	<var: 'mappingTable' declareC:'unsigned int *mappingTable'>
+ 	<var: 'sourceWord' type: #'unsigned int'>
+ 	<var: 'destWord' type: #'unsigned int'>
+ 	<var: 'dstMask' type: #'unsigned int'>
- 	<var: #mappingTable declareC:'unsigned int *mappingTable'>
- 	<var: #sourceWord type: #'unsigned int'>
- 	<var: #destWord type: #'unsigned int'>
- 	<var: #dstMask type: #'unsigned int'>
  	
  	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.
  	].
  !

Item was changed:
  ----- Method: BitBltSimulation>>rgbDiff:with: (in category 'combination rules') -----
  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 |
  	<inline: false>
  	<returnTypeC: 'unsigned int'>
+ 	<var: 'sourceWord' type: #'unsigned int'>
+ 	<var: 'destinationWord' type: #'unsigned int'>
+ 	<var: 'sourceShifted' type: #'unsigned int'>
+ 	<var: 'destShifted' type: #'unsigned int'>
+ 	<var: 'maskShifted' type: #'unsigned int'>
+ 	<var: 'pixMask' type: #'unsigned int'>
+ 	<var: 'rgbMask' type: #'unsigned int'>
- 	<var: #sourceWord type: 'unsigned int'>
- 	<var: #destinationWord type: 'unsigned int'>
- 	<var: #sourceShifted type: 'unsigned int'>
- 	<var: #destShifted type: 'unsigned int'>
- 	<var: #maskShifted type: 'unsigned int'>
- 	<var: #pixMask type: 'unsigned int'>
- 	<var: #rgbMask type: 'unsigned int'>
  	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"
  !

Item was changed:
  ----- Method: BitBltSimulation>>rgbMax:with: (in category 'combination rules') -----
  rgbMax: sourceWord with: destinationWord
  	<inline: false>
  	<returnTypeC: 'unsigned int'>
+ 	<var: 'sourceWord' type: #'unsigned int'>
+ 	<var: 'destinationWord' type: #'unsigned int'>
- 	<var: #sourceWord type: 'unsigned int'>
- 	<var: #destinationWord type: 'unsigned int'>
  	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]!

Item was changed:
  ----- Method: BitBltSimulation>>rgbMin:with: (in category 'combination rules') -----
  rgbMin: sourceWord with: destinationWord
  	<inline: false>
  	<returnTypeC: 'unsigned int'>
+ 	<var: 'sourceWord' type: #'unsigned int'>
+ 	<var: 'destinationWord' type: #'unsigned int'>
- 	<var: #sourceWord type: 'unsigned int'>
- 	<var: #destinationWord type: 'unsigned int'>
  	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]!

Item was changed:
  ----- Method: BitBltSimulation>>rgbMinInvert:with: (in category 'combination rules') -----
  rgbMinInvert: wordToInvert with: destinationWord
  	| sourceWord |
  	<inline: false>
  	<returnTypeC: 'unsigned int'>
+ 	<var: 'wordToInvert' type: #'unsigned int'>
+ 	<var: 'sourceWord' type: #'unsigned int'>
+ 	<var: 'destinationWord' type: #'unsigned int'>
- 	<var: #wordToInvert type: 'unsigned int'>
- 	<var: #sourceWord type: 'unsigned int'>
- 	<var: #destinationWord type: 'unsigned int'>
  	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]!

Item was changed:
  ----- Method: BitBltSimulation>>rgbMul:with: (in category 'combination rules') -----
  rgbMul: sourceWord with: destinationWord
  	<inline: false>
  	<returnTypeC: 'unsigned int'>
+ 	<var: 'sourceWord' type: #'unsigned int'>
+ 	<var: 'destinationWord' type: #'unsigned int'>
- 	<var: #sourceWord type: 'unsigned int'>
- 	<var: #destinationWord type: 'unsigned int'>
  	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]]. "!

Item was changed:
  ----- Method: BitBltSimulation>>rgbSub:with: (in category 'combination rules') -----
  rgbSub: sourceWord with: destinationWord
  	<inline: false>
  	<returnTypeC: 'unsigned int'>
+ 	<var: 'sourceWord' type: #'unsigned int'>
+ 	<var: 'destinationWord' type: #'unsigned int'>
- 	<var: #sourceWord type: 'unsigned int'>
- 	<var: #destinationWord type: 'unsigned int'>
  	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]!

Item was changed:
  ----- Method: BitBltSimulation>>setupColorMasksFrom:to: (in category 'interpreter interface') -----
  setupColorMasksFrom: srcBits to: targetBits
  	"Setup color masks for converting an incoming RGB pixel value from srcBits to targetBits."
  	| mask shifts masks deltaBits |
+ 	<var: 'shifts' declareC:'static int shifts[4] = {0, 0, 0, 0}'>
+ 	<var: 'masks' declareC:'static unsigned int masks[4] = {0, 0, 0, 0}'>
- 	<var: #shifts declareC:'static int shifts[4] = {0, 0, 0, 0}'>
- 	<var: #masks declareC:'static unsigned int masks[4] = {0, 0, 0, 0}'>
  	self cCode:'' inSmalltalk:[
  		shifts := CArrayAccessor on: (IntegerArray new: 4).
  		masks := CArrayAccessor on: (WordArray new: 4).
  	].
  	deltaBits := targetBits - srcBits.
  	deltaBits = 0 ifTrue:[^0].
  	deltaBits <= 0
  		ifTrue:[	mask := 1 << targetBits - 1.
  				"Mask for extracting a color part of the source"
  				masks at: RedIndex put: mask << (srcBits*2 - deltaBits).
  				masks at: GreenIndex put: mask << (srcBits - deltaBits).
  				masks at: BlueIndex put: mask << (0 - deltaBits).
  				masks at: AlphaIndex put: 0]
  		ifFalse:[	mask := 1 << srcBits - 1.
  				"Mask for extracting a color part of the source"
  				masks at: RedIndex put: mask << (srcBits*2).
  				masks at: GreenIndex put: mask << srcBits.
  				masks at: BlueIndex put: mask].
  
  	"Shifts for adjusting each value in a cm RGB value"
  	shifts at: RedIndex put: deltaBits * 3.
  	shifts at: GreenIndex put: deltaBits * 2.
  	shifts at: BlueIndex put: deltaBits.
  	shifts at: AlphaIndex put: 0.
  
  	cmShiftTable := shifts.
  	cmMaskTable := masks.
  	cmFlags := cmFlags bitOr: (ColorMapPresent bitOr: ColorMapFixedPart).
  !

Item was changed:
  ----- Method: BitBltSimulation>>sourceWord:with: (in category 'combination rules') -----
  sourceWord: sourceWord with: destinationWord
  	<returnTypeC: 'unsigned int'>
+ 	<var: 'sourceWord' type: #'unsigned int'>
+ 	<var: 'destinationWord' type: #'unsigned int'>
- 	<var: #sourceWord type: 'unsigned int'>
- 	<var: #destinationWord type: 'unsigned int'>
  	^sourceWord!

Item was changed:
  ----- Method: BitBltSimulation>>subWord:with: (in category 'combination rules') -----
  subWord: sourceWord with: destinationWord
  	<returnTypeC: 'unsigned int'>
+ 	<var: 'sourceWord' type: #'unsigned int'>
+ 	<var: 'destinationWord' type: #'unsigned int'>
- 	<var: #sourceWord type: 'unsigned int'>
- 	<var: #destinationWord type: 'unsigned int'>
  	^sourceWord - destinationWord!

Item was changed:
  ----- Method: BitBltSimulation>>tallyIntoMap:with: (in category 'combination rules') -----
  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 |
  	<inline: false>
  	<returnTypeC: 'unsigned int'>
+ 	<var: 'sourceWord' type: #'unsigned int'>
+ 	<var: 'destinationWord' type: #'unsigned int'>
+ 	<var: 'pixMask' type: #'unsigned int'>
+ 	<var: 'destShifted' type: #'unsigned int'>
+ 	<var: 'maskShifted' type: #'unsigned int'>
- 	<var: #sourceWord type: 'unsigned int'>
- 	<var: #destinationWord type: 'unsigned int'>
- 	<var: #pixMask type: 'unsigned int'>
- 	<var: #destShifted type: 'unsigned int'>
- 	<var: #maskShifted type: 'unsigned int'>
  	(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"!

Item was changed:
  ----- Method: BitBltSimulation>>warpLoop (in category 'inner loop') -----
  warpLoop
  	"This version of the inner loop traverses an arbirary quadrilateral
  	source, thus producing a general affine transformation."
  	| skewWord halftoneWord mergeWord startBits
  	  deltaP12x deltaP12y deltaP43x deltaP43y pAx pAy pBx pBy
  	  xDelta yDelta smoothingCount sourceMapOop
  	  nSteps nPix words destWord endBits mergeFnwith dstShiftInc dstShiftLeft mapperFlags |
  	<inline: false>	
+ 	<var: 'mergeFnwith' declareC: 'unsigned int (*mergeFnwith)(unsigned int, unsigned int)'>
+ 	<var: 'skewWord' type: #'unsigned int'>
+ 	<var: 'halftoneWord' type: #'unsigned int'>
+ 	<var: 'mergeWord' type: #'unsigned int'>
+ 	<var: 'destWord' type: #'unsigned int'>
+ 	mergeFnwith := self cCoerce: (opTable at: combinationRule+1) to: #'unsigned int (*)(unsigned int, unsigned int)'.
- 	<var: #mergeFnwith declareC: 'unsigned int (*mergeFnwith)(unsigned int, unsigned int)'>
- 	<var: #skewWord type: #'unsigned int'>
- 	<var: #halftoneWord type: #'unsigned int'>
- 	<var: #mergeWord type: #'unsigned int'>
- 	<var: #destWord type: #'unsigned int'>
- 	mergeFnwith := self cCoerce: (opTable at: combinationRule+1) to: 'unsigned int (*)(unsigned int, unsigned int)'.
  	mergeFnwith.  "null ref for compiler"
  
  	(interpreterProxy slotSizeOf: bitBltOop) >= (BBWarpBase+12)
  		ifFalse: [^ interpreterProxy primitiveFail].
  	nSteps := height-1.  nSteps <= 0 ifTrue: [nSteps := 1].
  
  	pAx := self fetchIntOrFloat: BBWarpBase ofObject: bitBltOop.
  	words := self fetchIntOrFloat: BBWarpBase+3 ofObject: bitBltOop.
  	deltaP12x := self deltaFrom: pAx to: words nSteps: nSteps.
  	deltaP12x < 0 ifTrue: [pAx := words - (nSteps*deltaP12x)].
  
  	pAy := self fetchIntOrFloat: BBWarpBase+1 ofObject: bitBltOop.
  	words := self fetchIntOrFloat: BBWarpBase+4 ofObject: bitBltOop.
  	deltaP12y := self deltaFrom: pAy to: words nSteps: nSteps.
  	deltaP12y < 0 ifTrue: [pAy := words - (nSteps*deltaP12y)].
  
  	pBx := self fetchIntOrFloat: BBWarpBase+9 ofObject: bitBltOop.
  	words := self fetchIntOrFloat: BBWarpBase+6 ofObject: bitBltOop.
  	deltaP43x := self deltaFrom: pBx to: words nSteps: nSteps.
  	deltaP43x < 0 ifTrue: [pBx := words - (nSteps*deltaP43x)].
  
  	pBy := self fetchIntOrFloat: BBWarpBase+10 ofObject: bitBltOop.
  	words := self fetchIntOrFloat: BBWarpBase+7 ofObject: bitBltOop.
  	deltaP43y := self deltaFrom: pBy to: words nSteps: nSteps.
  	deltaP43y < 0 ifTrue: [pBy := words - (nSteps*deltaP43y)].
  
  	interpreterProxy failed ifTrue: [^ false].  "ie if non-integers above"
  	interpreterProxy methodArgumentCount = 2
  		ifTrue:
  			[smoothingCount := interpreterProxy stackIntegerValue: 1.
  			 sourceMapOop := interpreterProxy stackValue: 0.
  			 sourceMapOop = interpreterProxy nilObject
  				ifTrue:
  					[sourceDepth < 16 ifTrue: "color map is required to smooth non-RGB dest"
  						[^interpreterProxy primitiveFail]]
  				ifFalse:
  					[(interpreterProxy slotSizeOf: sourceMapOop) < (1 << sourceDepth) ifTrue: "sourceMap must be long enough for sourceDepth"
  						[^interpreterProxy primitiveFail].
  					sourceMapOop := self oopForPointer: (interpreterProxy firstIndexableField: sourceMapOop)]]
  		ifFalse:
  			[smoothingCount := 1.
  			 sourceMapOop := interpreterProxy nilObject].
  	nSteps := width-1.  nSteps <= 0 ifTrue: [nSteps := 1].
  	startBits := destPPW - (dx bitAnd: destPPW-1).
  	endBits := ((dx + bbW - 1) bitAnd: destPPW-1) + 1.
   	bbW < startBits ifTrue:[startBits := bbW].
  
  	destY < clipY ifTrue:[
  		"Advance increments if there was clipping in y"
  		pAx := pAx + (clipY - destY * deltaP12x).
  		pAy := pAy + (clipY - destY * deltaP12y).
  		pBx := pBx + (clipY - destY * deltaP43x).
  		pBy := pBy + (clipY - destY * deltaP43y)].
  
  	"Setup values for faster pixel fetching."
  	self warpLoopSetup.
  	"Setup color mapping if not provided"
  	(smoothingCount > 1 and:[(cmFlags bitAnd: ColorMapNewStyle) = 0]) ifTrue:
  		[cmLookupTable
  			ifNil: [destDepth = 16 ifTrue: [self setupColorMasksFrom: 8 to: 5]]
  			ifNotNil: [self setupColorMasksFrom: 8 to: cmBitsPerColor]].
  	mapperFlags := cmFlags bitAnd: ColorMapNewStyle bitInvert32.
  
  	destMSB
  		ifTrue:[	dstShiftInc := 0 - destDepth.
  				dstShiftLeft := 32 - destDepth]
  		ifFalse:[	dstShiftInc := destDepth.
  				dstShiftLeft := 0].
  	noHalftone ifTrue:
  		[halftoneWord := AllOnes].
  	1 to: bbH do:
  		[ :i | "here is the vertical loop..."
  		xDelta := self deltaFrom: pAx to: pBx nSteps: nSteps.
   		xDelta >= 0 ifTrue: [sx := pAx] ifFalse: [sx := pBx - (nSteps*xDelta)].
  		yDelta := self deltaFrom: pAy to: pBy nSteps: nSteps.
   		yDelta >= 0 ifTrue: [sy := pAy] ifFalse: [sy := pBy - (nSteps*yDelta)].
  
  		destMSB
  			ifTrue:[dstBitShift := 32 - ((dx bitAnd: destPPW - 1) + 1 * destDepth)]
  			ifFalse:[dstBitShift := (dx bitAnd: destPPW - 1) * destDepth].
  
  		(destX < clipX) ifTrue:[
  			"Advance increments if there was clipping in x"
  			sx := sx + (clipX - destX * xDelta).
  			sy := sy + (clipX - destX * yDelta).
  		].
  
  		noHalftone ifFalse:
  			[halftoneWord := self halftoneAt: dy + i - 1].
  		destMask := mask1.
  		nPix := startBits.
  		"Here is the inner loop..."
  		words := nWords.
  			["pick up word"
  			smoothingCount = 1 ifTrue:["Faster if not smoothing"
  				skewWord := self warpPickSourcePixels: nPix
  								xDeltah: xDelta yDeltah: yDelta
  								xDeltav: deltaP12x yDeltav: deltaP12y
  								dstShiftInc: dstShiftInc flags: mapperFlags.
  			] ifFalse:["more difficult with smoothing"
  				skewWord := self warpPickSmoothPixels: nPix
  						xDeltah: xDelta yDeltah: yDelta
  						xDeltav: deltaP12x yDeltav: deltaP12y
  						sourceMap: sourceMapOop
  						smoothing: smoothingCount
  						dstShiftInc: dstShiftInc.
  			].
  			"align next word access to left most pixel"
  			dstBitShift := dstShiftLeft.
  			destMask = AllOnes ifTrue:["avoid read-modify-write"
  				mergeWord := self mergeFn: (skewWord bitAnd: halftoneWord)
  								with: (self dstLongAt: destIndex).
  				self dstLongAt: destIndex put: (destMask bitAnd: mergeWord).
  			] ifFalse:[ "General version using dest masking"
  				destWord := self dstLongAt: destIndex.
  				mergeWord := self mergeFn: (skewWord bitAnd: halftoneWord)
  								with: (destWord bitAnd: destMask).
  				destWord := (destMask bitAnd: mergeWord) bitOr:
  								(destWord bitAnd: destMask bitInvert32).
  				self dstLongAt: destIndex put: destWord.
  			].
  			self incDestIndex: 4.
  			words = 2 "e.g., is the next word the last word?"
  				ifTrue:["set mask for last word in this row"
  						destMask := mask2.
  						nPix := endBits]
  				ifFalse:["use fullword mask for inner loop"
  						destMask := AllOnes.
  						nPix := destPPW].
  			(words := words - 1) = 0] whileFalse.
  		"--- end of inner loop ---"
  		pAx := pAx + deltaP12x.
  		pAy := pAy + deltaP12y.
  		pBx := pBx + deltaP43x.
  		pBy := pBy + deltaP43y.
  		self incDestIndex: destDelta]!

Item was changed:
  ----- Method: BitBltSimulation>>warpPickSmoothPixels:xDeltah:yDeltah:xDeltav:yDeltav:sourceMap:smoothing:dstShiftInc: (in category 'pixel mapping') -----
  warpPickSmoothPixels: nPixels
  	xDeltah: xDeltah yDeltah: yDeltah
  	xDeltav: xDeltav yDeltav: yDeltav
  	sourceMap: sourceMap
  	smoothing: n
  	dstShiftInc: dstShiftInc
  	"Pick n (sub-) pixels from the source form, mapped by sourceMap,
  	average the RGB values, map by colorMap and return the new word.
  	This version is only called from WarpBlt with smoothingCount > 1"
  	| rgb x y a r g b xx yy xdh ydh xdv ydv dstMask destWord i j k nPix |
  	<inline: false> "nope - too much stuff in here"
+ 	<var: 'rgb' type: #'unsigned int'>
- 	<var: #rgb type: #'unsigned int'>
  	dstMask := maskTable at: destDepth.
  	destWord := 0.
  	n = 2 "Try avoiding divides for most common n (divide by 2 is generated as shift)"
  		ifTrue:[xdh := xDeltah // 2. ydh := yDeltah // 2. 
  				xdv := xDeltav // 2. ydv := yDeltav // 2]
  		ifFalse:[xdh := xDeltah // n. ydh := yDeltah // n. 
  				xdv := xDeltav // n. ydv := yDeltav // n].
  	i := nPixels.
  	[
  		x := sx. y := sy.
  		a := r := g := b := 0.
  		"Pick and average n*n subpixels"
  		nPix := 0.  "actual number of pixels (not clipped and not transparent)"
  		j := n.
  		[
  			xx := x. yy := y.
  			k := n.
  			[
  				"get a single subpixel"
  				rgb := self pickWarpPixelAtX: xx y: yy.
  				(combinationRule=25 "PAINT" and: [rgb = 0]) ifFalse:[
  					"If not clipped and not transparent, then tally rgb values"
  					nPix := nPix + 1.
  					sourceDepth < 16 ifTrue:[
  						"Get RGBA values from sourcemap table"
  						rgb := interpreterProxy long32At: sourceMap + (rgb << 2).
  					] ifFalse:["Already in RGB format"
  						sourceDepth = 16 
  								ifTrue:[rgb := self rgbMap16To32: rgb]
  								ifFalse:[rgb := self rgbMap32To32: rgb]].
  					b := b + (rgb bitAnd: 255).
  					g := g + (rgb >> 8 bitAnd: 255).
  					r := r + (rgb >> 16 bitAnd: 255).
  					a := a + (rgb >> 24)].
  				xx := xx + xdh.
  				yy := yy + ydh.
  			(k := k - 1) = 0] whileFalse.
  			x := x + xdv.
  			y := y + ydv.
  		(j := j - 1) = 0] whileFalse.
  
  		(nPix = 0 or: [combinationRule=25 "PAINT" and: [nPix < (n * n // 2)]]) ifTrue:[
  			rgb := 0  "All pixels were 0, or most were transparent"
  		] ifFalse:[
  			"normalize rgba sums"
  			nPix = 4 "Try to avoid divides for most common n"
  				ifTrue:[r := r >> 2.	g := g >> 2.	b := b >> 2.	a := a >> 2]
  				ifFalse:[	r := r // nPix.	g := g // nPix.	b := b // nPix.	a := a // nPix].
  			rgb := (a << 24) + (r << 16) + (g << 8) + b.
  
  			"map the pixel"
  			rgb = 0 ifTrue: [
  				"only generate zero if pixel is really transparent"
  				(r + g + b + a) > 0 ifTrue: [rgb := 1]].
  			rgb := self mapPixel: rgb flags: cmFlags.
  		].
  		"Mix it in"
  		destWord := destWord bitOr: (rgb bitAnd: dstMask) << dstBitShift.
  		dstBitShift := dstBitShift + dstShiftInc.
  		sx := sx + xDeltah.
  		sy := sy + yDeltah.
  	(i := i - 1) = 0] whileFalse.
  
  	^destWord
  !



More information about the Vm-dev mailing list