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

commits at source.squeak.org commits at source.squeak.org
Tue Oct 16 00:08:24 UTC 2018


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

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

Name: VMMaker.oscog-eem.2457
Author: eem
Time: 15 October 2018, 5:07:51.317632 pm
UUID: 18deefc8-1a84-4c5f-ab59-02af686dfc0b
Ancestors: VMMaker.oscog-AlistairGrant.2456

BitBltPlugin/BitBltSimulation

Add asserts and variables for bounds checking destination and source access.

Use the _: style for calling the surface functions.

Mark all memory access methods as <inline: #always> so as not to bother generating rthe uninlined versions.

=============== Diff against VMMaker.oscog-AlistairGrant.2456 ===============

Item was changed:
  SmartSyntaxInterpreterPlugin subclass: #BitBltSimulation
+ 	instanceVariableNames: 'destForm sourceForm halftoneForm combinationRule destX destY width height sourceX sourceY clipX clipY clipWidth clipHeight sourceWidth sourceHeight sourceDepth sourcePitch sourceBits sourcePPW sourceMSB destWidth destHeight destDepth destPitch destBits destPPW destMSB bitCount skew mask1 mask2 preload nWords destMask hDir vDir sourceIndex sourceDelta destIndex destDelta sx sy dx dy bbW bbH halftoneHeight noSource noHalftone halftoneBase sourceAlpha srcBitShift dstBitShift bitBltOop affectedL affectedR affectedT affectedB opTable maskTable ditherMatrix4x4 ditherThresholds16 ditherValues16 hasSurfaceLock warpSrcShift warpSrcMask warpAlignShift warpAlignMask warpBitShiftTable querySurfaceFn lockSurfaceFn unlockSurfaceFn isWarping cmFlags cmMask cmShiftTable cmMaskTable cmLookupTable cmBitsPerColor dither8Lookup componentAlphaModeColor componentAlphaModeAlpha ungammaLookupTable gammaLookupTable numGCsOnInvocation bitBltIsReceiver endOfDestination endOfSource'
- 	instanceVariableNames: 'destForm sourceForm halftoneForm combinationRule destX destY width height sourceX sourceY clipX clipY clipWidth clipHeight sourceWidth sourceHeight sourceDepth sourcePitch sourceBits sourcePPW sourceMSB destWidth destHeight destDepth destPitch destBits destPPW destMSB bitCount skew mask1 mask2 preload nWords destMask hDir vDir sourceIndex sourceDelta destIndex destDelta sx sy dx dy bbW bbH halftoneHeight noSource noHalftone halftoneBase sourceAlpha srcBitShift dstBitShift bitBltOop affectedL affectedR affectedT affectedB opTable maskTable ditherMatrix4x4 ditherThresholds16 ditherValues16 hasSurfaceLock warpSrcShift warpSrcMask warpAlignShift warpAlignMask warpBitShiftTable querySurfaceFn lockSurfaceFn unlockSurfaceFn isWarping cmFlags cmMask cmShiftTable cmMaskTable cmLookupTable cmBitsPerColor dither8Lookup componentAlphaModeColor componentAlphaModeAlpha ungammaLookupTable gammaLookupTable numGCsOnInvocation bitBltIsReceiver'
  	classVariableNames: 'AllOnes AlphaIndex BBClipHeightIndex BBClipWidthIndex BBClipXIndex BBClipYIndex BBColorMapIndex BBDestFormIndex BBDestXIndex BBDestYIndex BBHalftoneFormIndex BBHeightIndex BBLastIndex BBRuleIndex BBSourceFormIndex BBSourceXIndex BBSourceYIndex BBWarpBase BBWidthIndex BBXTableIndex BEBitBltIndex BinaryPoint BlueIndex ColorMapFixedPart ColorMapIndexedPart ColorMapNewStyle ColorMapPresent CrossedX EndOfRun FixedPt1 FormBitsIndex FormDepthIndex FormHeightIndex FormWidthIndex GreenIndex OpTable OpTableSize RedIndex'
  	poolDictionaries: ''
  	category: 'VMMaker-Interpreter'!
  
  !BitBltSimulation commentStamp: 'tpr 3/25/2013 16:50' prior: 0!
  This class implements BitBlt, much as specified in the Blue Book spec.
  
  Performance has been enhanced through the use of pointer variables such as sourceIndex and destIndex, and by separating several special cases of the inner loop.
  
  Operation has been extended to color, with support for 1, 2, 4, 8, 16, and 32-bit pixel sizes.  Conversion between different pixel sizes is facilitated by accepting an optional color map.
  
  In addition to the original 16 combination rules, this BitBlt supports
  	16	fail (for old paint mode)
  	17	fail (for old mask mode)
  	18	sourceWord + destinationWord
  	19	sourceWord - destinationWord
  	20	rgbAdd: sourceWord with: destinationWord
  	21	rgbSub: sourceWord with: destinationWord
  	22	OLDrgbDiff: sourceWord with: destinationWord
  	23	OLDtallyIntoMap: destinationWord -- old vers doesn't clip to bit boundary
  	24	alphaBlend: sourceWord with: destinationWord
  	25	pixPaint: sourceWord with: destinationWord
  	26	pixMask: sourceWord with: destinationWord
  	27	rgbMax: sourceWord with: destinationWord
  	28	rgbMin: sourceWord with: destinationWord
  	29	rgbMin: sourceWord bitInvert32 with: destinationWord
  	30	alphaBlendConst: sourceWord with: destinationWord -- alpha passed as an arg
  	31	alphaPaintConst: sourceWord with: destinationWord -- alpha passed as an arg
  	32	rgbDiff: sourceWord with: destinationWord
  	33	tallyIntoMap: destinationWord
  	34	alphaBlendScaled: sourceWord with: destinationWord
  	35 alphaBlendScaled: sourceWord with:	"unused here - only used by FXBlt"
  	36 alphaBlendScaled: sourceWord with:	"unused here - only used by FXBlt"
  	37 rgbMul: sourceWord with: destinationWord
  	38 pixSwap: sourceWord with: destinationWord
  	39 pixClear: sourceWord with: destinationWord
  	40 fixAlpha: sourceWord with: destinationWord
  	41 rgbComponentAlpha: sourceWord with: destinationWord
  
  This implementation has also been fitted with an experimental "warp drive" that allows abritrary scaling and rotation (and even limited affine deformations) with all BitBlt storage modes supported.
  
  To add a new rule to BitBlt...
  	1.  add the new rule method or methods in the category 'combination rules' of BBSim
  	2.  describe it in the class comment  of BBSim and in the class comment for BitBlt
  	3.  add refs to initializeRuleTable in proper positions
  	4.  add refs to initBBOpTable, following the pattern
  !

Item was changed:
  ----- Method: BitBltSimulation class>>declareCVarsIn: (in category 'translation') -----
  declareCVarsIn: aCCodeGenerator
  
  	"add option of  fast path BitBLT code header"
  	aCCodeGenerator
  		addHeaderFile:'"sqAssert.h"';
  		addHeaderFile:'#ifdef ENABLE_FAST_BLT
  #include "BitBltDispatch.h"
  #else
  // to handle the unavoidable decl in the spec of copyBitsFallback();
  #define operation_t void
  #endif'.
  		
  	aCCodeGenerator var: 'opTable'
  		declareC: 'void *opTable[' , OpTableSize printString , ']'.
  	aCCodeGenerator var: 'maskTable'
  		declareC:'int maskTable[33] = {
  0, 1, 3, 0, 15, 31, 0, 0, 255, 0, 0, 0, 0, 0, 0, 0, 65535,
  0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, -1
  }'.
  	aCCodeGenerator var: 'ditherMatrix4x4'
  		declareC:'const int ditherMatrix4x4[16] = {
  0,	8,	2,	10,
  12,	4,	14,	6,
  3,	11,	1,	9,
  15,	7,	13,	5
  }'.
  	aCCodeGenerator var: 'ditherThresholds16'
  		declareC:'const int ditherThresholds16[8] = { 0, 2, 4, 6, 8, 12, 14, 16 }'.
  	aCCodeGenerator var: 'ditherValues16'
  		declareC:'const int ditherValues16[32] = {
  0, 0, 1, 2, 3, 4, 5, 6, 7, 8, 9, 10, 11, 12, 13, 14,
  15, 16, 17, 18, 19, 20, 21, 22, 23, 24, 25, 26, 27, 28, 29, 30
  }'.
  
  	aCCodeGenerator var: 'warpBitShiftTable'
  		declareC:'int warpBitShiftTable[32]'.
  
  	aCCodeGenerator var:'cmShiftTable' 
  		type:'int *'.
  	aCCodeGenerator var:'cmMaskTable' 
  		type:'unsigned int *'.
  	aCCodeGenerator var:'cmLookupTable' 
  		type:'unsigned int *'.
  
  	aCCodeGenerator var: 'dither8Lookup'
  		declareC:' unsigned char dither8Lookup[4096]'.
  
  	aCCodeGenerator var:'ungammaLookupTable' 
  		type: 'unsigned char *'.
  	aCCodeGenerator var:'gammaLookupTable' 
  		type: 'unsigned char *'.
  
  	aCCodeGenerator
  		var: 'querySurfaceFn' declareC: 'int (*querySurfaceFn)(sqIntptr_t, int*, int*, int*, int*)';
  		var: 'lockSurfaceFn' declareC: 'sqIntptr_t (*lockSurfaceFn)(sqIntptr_t, int*, int, int, int, int)';
  		var: 'unlockSurfaceFn' declareC: 'int (*unlockSurfaceFn)(sqIntptr_t, int, int, int, int)'.
  	
  	#(sourcePitch sourceWidth sourceHeight sourceDepth sourceMSB sx sy
  		destPitch destWidth destHeight destDepth destMSB dx dy bbW bbH)
+ 		do: [:ivar | aCCodeGenerator var: ivar type: #int].
+ 
+ 	#('sourceIndex' 'destIndex' 'endOfDestination' 'endOfSource') do:
+ 		[:ivar| aCCodeGenerator var: ivar type: #usqInt]!
- 		do: [:ivar | aCCodeGenerator var: ivar type: #int]!

Item was changed:
  ----- Method: BitBltSimulation>>dstLongAt: (in category 'memory access') -----
  dstLongAt: idx
+ 	<inline: #always>
+ 	self assert: idx asUnsignedInteger < endOfDestination.
- 
  	^self long32At: idx!

Item was changed:
  ----- Method: BitBltSimulation>>dstLongAt:put: (in category 'memory access') -----
  dstLongAt: idx put: value
+ 	<inline: #always>
+ 	"We omit the assert here since dstLongAt:put: is always preceded by a dstLongAt: which does have an assert.
+ 	self assert: idx asUnsignedInteger < endOfDestination."
- 
  	^self long32At: idx put: value!

Item was changed:
  ----- Method: BitBltSimulation>>dstLongAt:put:mask: (in category 'memory access') -----
  dstLongAt: idx put: srcValue mask: dstMask
  	"Store the given value back into destination form, using dstMask
+ 	 to mask out the bits to be modified. This is an essential
+ 	 read-modify-write operation on the destination form."
+ 	<inline: #always>
- 	to mask out the bits to be modified. This is an essiantial
- 	read-modify-write operation on the destination form."
  	| dstValue |
- 	<inline: true>
  	dstValue := self dstLongAt: idx.
  	dstValue := dstValue bitAnd: dstMask.
  	dstValue := dstValue bitOr: srcValue.
  	self dstLongAt: idx put: dstValue.!

Item was changed:
  ----- Method: BitBltSimulation>>halftoneAt: (in category 'memory access') -----
  halftoneAt: idx
  	"Return a value from the halftone pattern."
+ 	<inline: #always>
- 
  	^self long32At: halftoneBase + (idx \\ halftoneHeight * 4)!

Item was changed:
  ----- Method: BitBltSimulation>>incDestIndex: (in category 'memory access') -----
  incDestIndex: offset
+ 	<inline: #always>
+ 	^destIndex := destIndex + offset
- 	<inline: true>
- 	^ destIndex := destIndex + offset
  !

Item was changed:
  ----- Method: BitBltSimulation>>incSrcIndex: (in category 'memory access') -----
  incSrcIndex: offset
+ 	<inline: #always>
+ 	^sourceIndex := sourceIndex + offset
- 	<inline: true>
- 	^ sourceIndex := sourceIndex + offset
  !

Item was changed:
  ----- Method: BitBltSimulation>>loadBitBltDestForm (in category 'interpreter interface') -----
  loadBitBltDestForm
  	"Load the dest form for BitBlt. Answer false if anything is wrong, true otherwise."
  
  	| destBitsSize |
  	<inline: true>
  	((interpreterProxy isPointers: destForm)
  	 and: [(interpreterProxy slotSizeOf: destForm) >= 4]) ifFalse:
  		[^false].
  	destBits := interpreterProxy fetchPointer: FormBitsIndex ofObject: destForm.
  	destWidth := interpreterProxy fetchInteger: FormWidthIndex ofObject: destForm.
  	destHeight := interpreterProxy fetchInteger: FormHeightIndex ofObject: destForm.
  	(destWidth >= 0 and: [destHeight >= 0]) ifFalse:
  		[^false].
  	destDepth := interpreterProxy fetchInteger: FormDepthIndex ofObject: destForm.
+ 	(destMSB := destDepth > 0) ifFalse:
- 	destMSB := destDepth > 0.
- 	destDepth < 0 ifTrue:
  		[destDepth := 0 - destDepth].
  	"Ignore an integer bits handle for Display in which case 
  	the appropriate values will be obtained by calling ioLockSurfaceBits()."
  	(interpreterProxy isIntegerObject: destBits)
  		ifTrue: "Query for actual surface dimensions"
  			[querySurfaceFn = 0 ifTrue: [self loadSurfacePlugin ifFalse: [^false]].
+ 			 (self querySurfaceFn: (interpreterProxy integerValueOf: destBits)
+ 								_: (self addressOf: destWidth put: [:v| destWidth := v])
+ 								_: (self addressOf: destHeight put: [:v| destHeight := v])
+ 								_: (self addressOf: destDepth put: [:v| destDepth := v])
+ 								_: (self addressOf: destMSB put: [:v| destMSB := v])) ifFalse:
- 			 (self query: (interpreterProxy integerValueOf: destBits)
- 				Sur: (self addressOf: destWidth)
- 				fa: (self addressOf: destHeight)
- 				ce: (self addressOf: destDepth)
- 				Fn: (self addressOf: destMSB)) ifFalse:
  					[interpreterProxy primitiveFailFor: PrimErrCallbackError.
  					 ^false].
  			destPPW := 32 // destDepth.
  			destBits := destPitch := 0]
  		ifFalse:
  			[(interpreterProxy isWordsOrBytes: destBits) ifFalse:
  				[^false].
  			destPPW := 32 // destDepth.
  			destPitch := destWidth + (destPPW-1) // destPPW * 4.
  			destBitsSize := interpreterProxy byteSizeOf: destBits.
  			destBitsSize >= (destPitch * destHeight) ifFalse:
  				[^false].
  			"Skip header since external bits don't have one"
  			destBits := self oopForPointer: (interpreterProxy firstIndexableField: destBits)].
  	^true!

Item was changed:
  ----- Method: BitBltSimulation>>loadBitBltSourceForm (in category 'interpreter interface') -----
  loadBitBltSourceForm
  	"Load the source form for BitBlt. Return false if anything is wrong, true otherwise."
  	| sourceBitsSize |
  	<inline: true>
  	((interpreterProxy isPointers: sourceForm)
  	 and: [(interpreterProxy slotSizeOf: sourceForm) >= 4]) ifFalse:
  		[^false].
  	sourceBits := interpreterProxy fetchPointer: FormBitsIndex ofObject: sourceForm.
  	sourceWidth := self fetchIntOrFloat: FormWidthIndex ofObject: sourceForm.
  	sourceHeight := self fetchIntOrFloat: FormHeightIndex ofObject: sourceForm.
  	(sourceWidth >= 0 and: [sourceHeight >= 0]) ifFalse:
  		[^false].
  	sourceDepth := interpreterProxy fetchInteger: FormDepthIndex ofObject: sourceForm.
+ 	(sourceMSB := sourceDepth > 0) ifFalse:
- 	sourceMSB := sourceDepth > 0.
- 	sourceDepth < 0 ifTrue:
  		[sourceDepth := 0 - sourceDepth].
  	"Ignore an integer bits handle for Display in which case
  	 the appropriate values will be obtained by calling ioLockSurfaceBits()."
  	(interpreterProxy isIntegerObject: sourceBits)
  		ifTrue: "Query for actual surface dimensions"
  			[querySurfaceFn = 0 ifTrue: [self loadSurfacePlugin ifFalse:[^false]].
+ 			 (self querySurfaceFn: (interpreterProxy integerValueOf: sourceBits)
+ 								_: (self addressOf: sourceWidth put: [:v| sourceWidth := v])
+ 								_: (self addressOf: sourceHeight put: [:v| sourceHeight := v])
+ 								_: (self addressOf: sourceDepth put: [:v| sourceDepth := v])
+ 								_: (self addressOf: sourceMSB put: [:v| sourceMSB := v])) ifFalse:
- 			 (self query: (interpreterProxy integerValueOf: sourceBits)
- 				Sur: (self addressOf: sourceWidth)
- 				fa: (self addressOf: sourceHeight)
- 				ce: (self addressOf: sourceDepth)
- 				Fn: (self addressOf: sourceMSB)) ifFalse:
  					[interpreterProxy primitiveFailFor: PrimErrCallbackError.
  					 ^false].
  			sourcePPW := 32 // sourceDepth.
  			sourceBits := sourcePitch := 0]
  		ifFalse:
  			[(interpreterProxy isWordsOrBytes: sourceBits) ifFalse:
  				[^false].
  			sourcePPW := 32 // sourceDepth.
  			sourcePitch := sourceWidth + (sourcePPW-1) // sourcePPW * 4.
  			sourceBitsSize := interpreterProxy byteSizeOf: sourceBits.
  			sourceBitsSize >= (sourcePitch * sourceHeight) ifFalse:
  				[^false].
  			"Skip header since external bits don't have one"
  			sourceBits := self oopForPointer: (interpreterProxy firstIndexableField: sourceBits)].
  	^true!

Item was removed:
- ----- Method: BitBltSimulation>>lock:Su:rf:ac:eF:n: (in category 'surface support') -----
- lock: sourceHandle Su: pitchPtr rf: x ac: y eF: w n: h
- 	"Simulate the lockSurfaceFn function call as a failure to load the surface."
- 	<doNotGenerate>
- 	^0!

Item was added:
+ ----- Method: BitBltSimulation>>lockSurfaceFn:_:_:_:_:_: (in category 'surface support') -----
+ lockSurfaceFn: sourceHandle _: pitchPtr _: x _: y _: w _: h
+ 	"Simulate the lockSurfaceFn function call as a failure to load the surface."
+ 	<doNotGenerate>
+ 	^0!

Item was changed:
  ----- Method: BitBltSimulation>>lockSurfaces (in category 'surface support') -----
  lockSurfaces
  	"Get a pointer to the bits of any OS surfaces."
  	"Notes: 
  	* For equal source/dest handles only one locking operation is performed.
  	This is to prevent locking of overlapping areas which does not work with
  	certain APIs (as an example, DirectDraw prevents locking of overlapping areas). 
  	A special case for non-overlapping but equal source/dest handle would 
  	be possible but we would have to transfer this information over to 
  	unlockSurfaces somehow (currently, only one unlock operation is 
  	performed for equal source and dest handles). Also, this would require
  	a change in the notion of ioLockSurface() which is right now interpreted
  	as a hint and not as a requirement to lock only the specific portion of
  	the surface.
  
  	* The arguments in ioLockSurface() provide the implementation with
  	an explicit hint what area is affected. It can be very useful to
  	know the max. affected area beforehand if getting the bits requires expensive
  	copy operations (e.g., like a roundtrip to the X server or a glReadPixel op).
  	However, the returned pointer *MUST* point to the virtual origin of the surface
  	and not to the beginning of the rectangle. The promise made by BitBlt
  	is to never access data outside the given rectangle (aligned to 4byte boundaries!!)
  	so it is okay to return a pointer to the virtual origin that is actually outside
  	the valid memory area.
  
  	* The area provided in ioLockSurface() is already clipped (e.g., it will always
  	be inside the source and dest boundingBox) but it is not aligned to word boundaries
  	yet. It is up to the support code to compute accurate alignment if necessary.
  
  	* Warping always requires the entire source surface to be locked because
  	there is no beforehand knowledge about what area will actually be traversed.
  
  	* Fail if a GC has occurred since the primitive started (presumably in the lockSurface
  	   function), because one or more of the primitives' parameters may have been moved.
  	"
  	| sourceHandle destHandle l r t b |
  	<inline: true>
  	self assert: numGCsOnInvocation = interpreterProxy statNumGCs.
  	hasSurfaceLock := false.
  	destBits = 0 ifTrue: "Blitting *to* OS surface"
  		[lockSurfaceFn = 0 ifTrue: [self loadSurfacePlugin ifFalse: [^false]].
  		 destHandle := interpreterProxy fetchInteger: FormBitsIndex ofObject: destForm.
  		 (sourceBits ~= 0 or: [noSource]) ifFalse:
  			[sourceHandle := interpreterProxy fetchInteger: FormBitsIndex ofObject: sourceForm.
  			 "Handle the special case of equal source and dest handles"
  			 sourceHandle = destHandle ifTrue:
  				"If we have overlapping source/dest we lock the entire area
  				so that there is only one area transmitted"
  				[isWarping
  					ifFalse: "When warping we always need the entire surface for the source"
+ 						[sourceBits := self lockSurfaceFn: sourceHandle
+ 														_: (self addressOf: sourcePitch)
+ 														_: 0
+ 														_: 0
+ 														_: sourceWidth
+ 														_: sourceHeight]
- 						[sourceBits := self lock: sourceHandle
- 											Su: (self addressOf: sourcePitch)
- 											rf: 0
- 											ac: 0
- 											eF: sourceWidth
- 											n: sourceHeight]
  					ifTrue: "Otherwise use overlapping area"
  						[l := sx min: dx. r := (sx max: dx) + bbW.
+ 						 t := sy min: dy. b := (sy max: dy) + bbH.
+ 						 sourceBits := self lockSurfaceFn: sourceHandle
+ 														_: (self addressOf: sourcePitch)
+ 														_: l
+ 														_: t
+ 														_: r - l
+ 														_: b - t].
- 						t := sy min: dy. b := (sy max: dy) + bbH.
- 						sourceBits := self lock: sourceHandle
- 											Su: (self addressOf: sourcePitch)
- 											rf: l
- 											ac: t
- 											eF: r - l
- 											n: b - t].
  				destBits := sourceBits.
  				destPitch := sourcePitch.
  				hasSurfaceLock := true.
  				numGCsOnInvocation ~= interpreterProxy statNumGCs ifTrue:
  					[self unlockSurfaces.
  					 interpreterProxy primitiveFailFor: PrimErrObjectMoved.
  					 ^false].
  				destBits = 0 ifTrue:
  					[self unlockSurfaces.
  					 interpreterProxy primitiveFailFor: PrimErrCallbackError.
  					 ^false].
+ 				endOfDestination := endOfSource := sourceBits + (sourcePitch * sourceHeight).
  				^true]].
  		"Fall through - if not equal it'll be handled below"
+ 		destBits := self lockSurfaceFn: destHandle
+ 									_: (self addressOf: destPitch)
+ 									_: dx
+ 									_: dy
+ 									_: bbW
+ 									_: bbH.
- 		destBits := self lock: destHandle
- 						Su: (self addressOf: destPitch)
- 						rf: dx
- 						ac: dy
- 						eF: bbW
- 						n: bbH.
  		hasSurfaceLock := true.
  		numGCsOnInvocation ~= interpreterProxy statNumGCs ifTrue:
  			[self unlockSurfaces.
  			 interpreterProxy primitiveFailFor: PrimErrObjectMoved.
  			 ^false].
  		destBits = 0 ifTrue:
  			[interpreterProxy primitiveFailFor: PrimErrCallbackError]].
  
  	(sourceBits ~= 0 or: [noSource]) ifFalse: "Blitting *from* OS surface"
  		[sourceHandle := interpreterProxy fetchInteger: FormBitsIndex ofObject: sourceForm.
  		 interpreterProxy failed ifTrue: [^false]. "fetch sourceHandle could fail"
  		lockSurfaceFn = 0 ifTrue:[self loadSurfacePlugin ifFalse:[^false]].
  		"Warping requiring the entire surface"
  		isWarping
  			ifTrue:
+ 				[sourceBits := self lockSurfaceFn: sourceHandle
+ 												_: (self addressOf: sourcePitch)
+ 												_: 0
+ 												_: 0
+ 												_: sourceWidth
+ 												_: sourceHeight]
- 				[sourceBits := self lock: sourceHandle
- 												Su: (self addressOf: sourcePitch)
- 												rf: 0
- 												ac: 0
- 												eF: sourceWidth
- 												n: sourceHeight]
  			ifFalse:
+ 				[sourceBits := self lockSurfaceFn: sourceHandle
+ 												_: (self addressOf: sourcePitch)
+ 												_: sx
+ 												_: sy
+ 												_: bbW
+ 												_: bbH].
- 				[sourceBits := self lock: sourceHandle
- 									Su: (self addressOf: sourcePitch)
- 									rf: sx
- 									ac: sy
- 									eF: bbW
- 									n: bbH].
  		hasSurfaceLock := true.
  		numGCsOnInvocation ~= interpreterProxy statNumGCs ifTrue:
  			[self unlockSurfaces.
  			 interpreterProxy primitiveFailFor: PrimErrObjectMoved.
  			 ^false].
  		sourceBits = 0 ifTrue:
  			[interpreterProxy primitiveFailFor: PrimErrCallbackError]].
+ 	endOfSource := sourceBits + (sourcePitch * sourceHeight).
+ 	endOfDestination := destBits + (destPitch * destHeight).
  	^destBits ~= 0 and: [sourceBits ~= 0 or: [noSource]]!

Item was removed:
- ----- Method: BitBltSimulation>>query:Sur:fa:ce:Fn: (in category 'surface support') -----
- query: handle Sur: widthPtr fa: heightPtr ce: depthPtr Fn: endianPtr
- 	"Query the dimension of an OS surface.
- 	This method is provided so that in case the inst vars of the
- 	source form are broken, *actual* values of the OS surface
- 	can be obtained. This might, for instance, happen if the user
- 	resizes the main window.
- 	This is a simulation of the querySurfaceFn function call; simulate as a failure."
- 	<doNotGenerate>
- 	^false!

Item was added:
+ ----- Method: BitBltSimulation>>querySurfaceFn:_:_:_:_: (in category 'surface support') -----
+ querySurfaceFn: handle _: widthPtr _: heightPtr _: depthPtr _: endianPtr
+ 	"Query the dimension of an OS surface.
+ 	This method is provided so that in case the inst vars of the
+ 	source form are broken, *actual* values of the OS surface
+ 	can be obtained. This might, for instance, happen if the user
+ 	resizes the main window.
+ 	This is a simulation of the querySurfaceFn function call; simulate as a failure."
+ 	<doNotGenerate>
+ 	^false!

Item was changed:
  ----- Method: BitBltSimulation>>srcLongAt: (in category 'memory access') -----
  srcLongAt: idx
+ 	<inline: #always>
+ 	self assert: idx asUnsignedInteger < endOfSource.
- 
  	^self long32At: idx!

Item was changed:
  ----- Method: BitBltSimulation>>tallyMapAt: (in category 'memory access') -----
  tallyMapAt: idx
  	"Return the word at position idx from the colorMap"
+ 	<inline: #always>
  	^cmLookupTable at: (idx bitAnd: cmMask)!

Item was changed:
  ----- Method: BitBltSimulation>>tallyMapAt:put: (in category 'memory access') -----
  tallyMapAt: idx put: value
  	"Store the word at position idx in the colorMap"
+ 	<inline: #always>
  	^cmLookupTable at: (idx bitAnd: cmMask) put: value!

Item was removed:
- ----- Method: BitBltSimulation>>unlock:Sur:fa:ce:Fn: (in category 'surface support') -----
- unlock: handle Sur: x fa: y ce: w Fn: h
- 	"Simulate the unlockSurfaceFn function call."
- 	<doNotGenerate>
- 	^self!

Item was changed:
  ----- Method: BitBltSimulation>>unlockSurfaces (in category 'surface support') -----
  unlockSurfaces
  	"Unlock the bits of any OS surfaces."
  	"See the comment in lockSurfaces. Similar rules apply. That is, the area provided in ioUnlockSurface
  	 can be used to determine the dirty region after drawing. If a source is unlocked, then the area will
  	 be (0,0,0,0) to indicate that no portion is dirty.  Note that if a GC happens during unlockSourceFn
  	 (if it is effectively a callback) no matter.  No bits are touched after unlock."
  	| sourceHandle destHandle destLocked |
  	hasSurfaceLock ifFalse: [^self].
  	unlockSurfaceFn = 0 ifTrue:
  		[self loadSurfacePlugin ifFalse:
  			[^self]].
  	self ensureDestAndSourceFormsAreValid.
  	destLocked := false.
  	destHandle := interpreterProxy fetchPointer: FormBitsIndex ofObject: destForm.
  	(interpreterProxy isIntegerObject: destHandle) ifTrue: "The destBits are always assumed to be dirty"
+ 		[self unlockSurfaceFn: (interpreterProxy integerValueOf: destHandle)
+ 							_: affectedL
+ 							_: affectedT
+ 							_: affectedR - affectedL
+ 							_: affectedB - affectedT.
- 		[self unlock: (interpreterProxy integerValueOf: destHandle)
- 			Sur: affectedL
- 			fa: affectedT
- 			ce: affectedR - affectedL
- 			Fn: affectedB - affectedT.
  		 destBits := destPitch := 0.
  		 destLocked := true].
  	noSource ifFalse:
  		[self ensureDestAndSourceFormsAreValid.
  		 sourceHandle := interpreterProxy fetchPointer: FormBitsIndex ofObject: sourceForm.
  		 (interpreterProxy isIntegerObject: sourceHandle) ifTrue:
  			["Only unlock sourceHandle if different from destHandle"
  			 (destLocked and: [sourceHandle = destHandle]) ifFalse:
  				[self unlock: (interpreterProxy integerValueOf: sourceHandle) Sur: 0 fa: 0 ce: 0 Fn: 0].
  			sourceBits := sourcePitch := 0]].
  	hasSurfaceLock := false.
  	self cCode: [] inSmalltalk:
  		[interpreterProxy displayObject = destForm ifTrue:
  			[interpreterProxy getDeferDisplayUpdates ifFalse:
  				[interpreterProxy fullDisplayUpdate]]]!

Item was changed:
  ----- Method: BitBltSimulator>>dstLongAt: (in category 'debug support') -----
  dstLongAt: dstIndex
+ 	interpreterProxy isInterpreterProxy ifTrue:
+ 		[^dstIndex long32At: 0].
+ 	^super dstLongAt: dstIndex!
- 
- 	interpreterProxy isInterpreterProxy
- 		ifTrue:[^dstIndex long32At: 0].
- 	((dstIndex anyMask: 3) or:[dstIndex + 4 < destBits or:[
- 		dstIndex > (destBits + (destPitch * destHeight))]])
- 			ifTrue:[self error:'Out of bounds'].
- 	^self long32At: dstIndex!

Item was changed:
  ----- Method: BitBltSimulator>>dstLongAt:put: (in category 'debug support') -----
  dstLongAt: dstIndex put: value
+ 	interpreterProxy isInterpreterProxy ifTrue:
+ 		[^dstIndex long32At: 0 put: value].
+ 	^super dstLongAt: dstIndex put: value!
- 
- 	interpreterProxy isInterpreterProxy
- 		ifTrue:[^dstIndex long32At: 0 put: value].
- 	((dstIndex anyMask: 3) or:[dstIndex < destBits or:[
- 		dstIndex >= (destBits + (destPitch * destHeight))]])
- 			ifTrue:[self error:'Out of bounds'].
- 	^self long32At: dstIndex put: value!

Item was changed:
  ----- Method: BitBltSimulator>>halftoneAt: (in category 'memory access') -----
  halftoneAt: idx
+ 	interpreterProxy isInterpreterProxy ifTrue:
+ 		[^(halftoneBase + (idx \\ halftoneHeight * 4)) long32At: 0].
+ 	^super halftoneAt: idx!
- 
- 	^self
- 		cCode: [(halftoneBase + (idx \\ halftoneHeight * 4)) long32At: 0]
- 		inSmalltalk: [super halftoneAt: idx]!

Item was changed:
  ----- Method: BitBltSimulator>>srcLongAt: (in category 'debug support') -----
  srcLongAt: srcIndex
+ 	interpreterProxy isInterpreterProxy ifTrue:
+ 		[^srcIndex long32At: 0].
+ 	^super srcLongAt: srcIndex!
- 
- 	interpreterProxy isInterpreterProxy
- 		ifTrue:[^srcIndex long32At: 0].
- 	((srcIndex anyMask: 3) or:[srcIndex + 4 < sourceBits or:[
- 		srcIndex > (sourceBits + (sourcePitch * sourceHeight))]])
- 			ifTrue:[self error:'Out of bounds'].
- 	^self long32At: srcIndex!



More information about the Vm-dev mailing list