[pypy-commit] lang-smalltalk bitblt: Add BlueBook BitBlt simulation. This has been generalized to use a configurable WordSize, and a "sanitize inputs" method has been added to deal with assumptions.

timfel noreply at buildbot.pypy.org
Sat Mar 16 13:35:33 CET 2013


Author: Tim Felgentreff <timfelgentreff at gmail.com>
Branch: bitblt
Changeset: r181:c1447657197d
Date: 2013-03-15 10:43 +0100
http://bitbucket.org/pypy/lang-smalltalk/changeset/c1447657197d/

Log:	Add BlueBook BitBlt simulation. This has been generalized to use a
	configurable WordSize, and a "sanitize inputs" method has been added
	to deal with assumptions.

diff --git a/BitBltSim.14.cs b/BitBltSim.14.cs
new file mode 100644
--- /dev/null
+++ b/BitBltSim.14.cs
@@ -0,0 +1,1 @@
+'From Squeak4.4 of 15 December 2012 [latest update: #12303] on 15 March 2013 at 10:42:24 am'!
Object subclass: #BitBlt
	instanceVariableNames: 'destForm sourceForm halftoneForm combinationRule destX destY width height sourceX sourceY clipX clipY clipWidth clipHeight colorMap simW simH simSx simSy simDx simDy simDestBits simDestRaster simSourceBits simSourceRaster simHalftoneBits simSkew simMask1 simMask2 simSkewMask simNWords simHDir simVDir simPreload simSourceIndex simDestIndex simSourceDelta simDestDelta '
	classVariableNames: 'AllOnes RightMasks WordSize0 WordSize '
	poolDictionaries: ''
	category: 'Graphics-Support'!

!BitBlt methodsFor: 'private'!
clipRange
	destX >= clipX
		ifTrue: 
			[simSx _ sourceX.
			simDx _ destX.
			simW _ width]
		ifFalse: 
			[simSx _ sourceX + (clipX - destX).
			simW _ width - (clipX - destX).
			simDx _ clipX].
	simDx + simW > (clipX + clipWidth) ifTrue: [simW _ simW - (simDx + simW - (clipX + clipWidth))].
	destY >= clipY
		ifTrue: 
			[simSy _ sourceY.
			simDy _ destY.
			simH _ height]
		ifFalse: 
			[simSy _ sourceY + clipY - destY.
			simH _ height - (clipY - destY).
			simDy _ clipY].
	simDy + simH > (clipY + clipHeight) ifTrue: [simH _ simH - (simDy + simH - (clipY + clipHeight))].
	simSx < 0
		ifTrue: 
			[simDx _ simDx - simSx.
			simW _ simW + simSx.
			simSx _ 0].
	simSx + simW > sourceForm width ifTrue: [simW _ simW - (simSx + simW - sourceForm width)].
	simSy < 0
		ifTrue: 
			[simDy _ simDy - simSy.
			simH _ simH + simSy.
			simSy _ 0].
	simSy + simH > sourceForm height ifTrue: [simH _ simH - (simSy + simH - sourceForm height)]! !

!BitBlt methodsFor: 'private' stamp: 'tfel 3/13/2013 12:02'!
copyBitsAgain
	<primitive: 96>
	self simulateCopyBits.! !

!BitBlt methodsFor: 'simulation' stamp: 'tfel 3/15/2013 10:31'!
calculateOffsets
	"check if we need to preload buffer
	(i.e., two words of source needed for first word of destination)"
	simPreload _ (sourceForm notNil) and:
						[simSkew ~= 0 and: [simSkew <= (simSx bitAnd: WordSize0)]].
	simHDir < 0 ifTrue: [simPreload _ simPreload == false].
	"calculate starting offsets"
	simSourceIndex _ simSy * simSourceRaster + (simSx // WordSize).
	simDestIndex _ simDy * simDestRaster + (simDx // WordSize).
	"calculate increments from end of 1 line to start of next"
	simSourceDelta _
		(simSourceRaster * simVDir) -
			(simNWords + (simPreload ifTrue: [1] ifFalse: [0]) * simHDir).
	simDestDelta _ (simDestRaster * simVDir) - (simNWords * simHDir)! !

!BitBlt methodsFor: 'simulation' stamp: 'tfel 3/15/2013 10:28'!
checkOverlap
	| t |
	"check for possible overlap of source and destination"
	simHDir _ simVDir _ 1. "defaults for no overlap"
	(sourceForm == destForm and: [simDy >= simSy])
		ifTrue:
			[simDy > simSy "have to start at bottom"
				ifTrue: [simVDir _ -1. simSy _ simSy + simH - 1. simDy _ simDy + simH - 1]
				ifFalse: [simDx > simSx "y's are equal, but x's are backward"
							ifTrue: [simHDir _ -1.
									simSx _ simSx + simW - 1.
									"start at right"
									simDx _ simDx + simW - 1.
									"and fix up masks"
									simSkewMask _ simSkewMask bitInvert.
									t _ simMask1.
									simMask1 _ simMask2.
									simMask2 _ t]]]! !

!BitBlt methodsFor: 'simulation' stamp: 'tfel 3/15/2013 10:26'!
computeMasks
	| startBits endBits |
	"calculate skeq and edge masks"
	simDestBits _ destForm bits.
	simDestRaster _ destForm width - 1 // WordSize + 1.
	sourceForm notNil
		ifTrue: [simSourceBits _ sourceForm bits.
				simSourceRaster _ sourceForm width - 1 // WordSize + 1].
	halftoneForm notNil
		ifTrue: [simHalftoneBits _ halftoneForm bits].
	simSkew _ (simSx - simDx) bitAnd: WordSize0.
	"how many bits source gets skewed to right"
	startBits _ WordSize - (simDx bitAnd: WordSize0).
	"how many bits in first word"
	simMask1 _ RightMasks at: startBits + 1.
	endBits _ WordSize0 - ((simDx + simW - 1) bitAnd: WordSize0).
	"how many bits in last word"
	simMask2 _ (RightMasks at: endBits + 1) bitInvert.
	simSkewMask _
		(simSkew = 0
			ifTrue: [0]
			ifFalse: [RightMasks at: WordSize - simSkew + 1]).
	"determine number of words stored per line; merge masks if necessary"
	simW < startBits
		ifTrue: [simMask1 _ simMask1 bitAnd: simMask2.
				simMask2 _ 0.
				simNWords _ 1]
		ifFalse: [simNWords _ (simW - startBits - 1) // WordSize + 2].! !

!BitBlt methodsFor: 'simulation' stamp: 'tfel 3/15/2013 10:39'!
copyLoop
	| prevWord thisWord skewWord mergeMask
	  halftoneWord mergeWord |
	1 to: simH do: "here is the vertical loop"
		[:i | 
		(halftoneForm notNil)
			ifTrue:
				"XXX Accessing simHalftoneBits with wrap-around ... different from BlueBook"
				[halftoneWord _ simHalftoneBits at: (1 + ((simDy bitAnd: WordSize0) \\ simHalftoneBits size)).
				simDy _ simDy + simVDir]
			ifFalse: [halftoneWord _ AllOnes].
		skewWord _ halftoneWord.
		simPreload
			ifTrue: [prevWord _ simSourceBits at: simSourceIndex + 1.
					"load the 32bit shifter" 1 halt.
					simSourceIndex _ simSourceIndex + simHDir]
			ifFalse: [prevWord _ 0].
		mergeMask _ simMask1.
		1 to: simNWords do: "here is the inner horizontal loop"
			[:word |
			sourceForm notNil "if source is used"
				ifTrue:
					[prevWord _ prevWord bitAnd: simSkewMask.
					thisWord _ simSourceBits at: simSourceIndex + 1.
												"pick up next word"
					skewWord _
						prevWord bitOr: (thisWord bitAnd: simSkewMask bitInvert).
					prevWord _ thisWord.
					skewWord _ (skewWord bitShift: simSkew) bitOr:
											(skewWord bitShift: simSkew - WordSize)].
															"WordSize-bit rotate"
			mergeWord _ self merge: (skewWord bitAnd: halftoneWord)
								with: (simDestBits at: simDestIndex + 1).
			simDestBits
				at: simDestIndex + 1
				put: ((mergeMask bitAnd: mergeWord)
							bitOr: (mergeMask bitInvert
									bitAnd: (simDestBits at: simDestIndex + 1))).
			simSourceIndex _ simSourceIndex + simHDir.
			simDestIndex _ simDestIndex + simHDir.
			word = (simNWords - 1)
				ifTrue: [mergeMask _ simMask2]
				ifFalse: [mergeMask _ AllOnes]].
		simSourceIndex _ simSourceIndex + simSourceDelta.
		simDestIndex _ simDestIndex + simDestDelta]! !

!BitBlt methodsFor: 'simulation' stamp: 'tfel 3/15/2013 10:40'!
merge: srcWord with: dstWord
	"These are the 16 combination rules."
	combinationRule = 0 ifTrue: [^ 0].
	combinationRule = 1 ifTrue: [^ srcWord bitAnd: dstWord].
	combinationRule = 2 ifTrue: [^ srcWord bitAnd: dstWord bitInvert].
	combinationRule = 3 ifTrue: [^ srcWord].
	combinationRule = 4 ifTrue: [^ srcWord bitInvert bitAnd: dstWord].
	combinationRule = 5 ifTrue: [^ dstWord].
	combinationRule = 6 ifTrue: [^ srcWord bitXor: dstWord].
	combinationRule = 7 ifTrue: [^ srcWord bitOr: dstWord].
	combinationRule = 8 ifTrue: [^ srcWord bitInvert bitAnd: dstWord bitInvert].
	combinationRule = 9 ifTrue: [^ srcWord bitInvert bitXor: dstWord].
	combinationRule = 10 ifTrue: [^ dstWord bitInvert].
	combinationRule = 11 ifTrue: [^ srcWord bitOr: dstWord bitInvert].
	combinationRule = 12 ifTrue: [^ srcWord bitInvert].
	combinationRule = 13 ifTrue: [^ srcWord bitInvert bitOr: dstWord].
	combinationRule = 14 ifTrue: [^ srcWord bitInvert bitOr: dstWord bitInvert].
	combinationRule = 15 ifTrue: [^ AllOnes]! !

!BitBlt methodsFor: 'simulation' stamp: 'tfel 3/15/2013 10:16'!
sanitizeInput

	destForm unhibernate.
	sourceForm
		ifNil: [sourceForm := destForm]
		ifNotNil: [sourceForm unhibernate].
	halftoneForm ifNotNil: [
		halftoneForm isForm
			ifFalse: [halftoneForm := Form new
										bits: halftoneForm;
										yourself].
		halftoneForm unhibernate].
	width ifNil: [width := sourceForm width].
	height ifNil: [height := sourceForm height].
	self roundVariables.! !

!BitBlt methodsFor: 'simulation' stamp: 'tfel 3/15/2013 10:20'!
simClipRange
	"clip and adjust source origin and extent appropriately"
	"first in x"
	destX >= clipX
		ifTrue: [simSx _ sourceX. simDx _ destX. simW _ width]
		ifFalse: [simSx _ sourceX + (clipX - destX).
				simW _ width - (clipX - destX).
				simDx _ clipX].
	simDx + simW > (clipX + clipWidth)
		ifTrue: [simW _ simW - ((simDx + simW) - (clipX + clipWidth))].
	"then in y"
	destY >= clipY
		ifTrue: [simSy _ sourceY. simDy _ destY. simH _ height]
		ifFalse: [simSy _ sourceY + clipY - destY.
				simH _ height - clipY - destY.
				simDy _ clipY].
	simDy + simH > (clipY + clipHeight)
		ifTrue: [simH _ simH - ((simDy + simH) - (clipY + clipHeight))].
	simSx < 0
		ifTrue: [simDx _ simDx - simSx. simW _ simW + simSx. simSx _ 0].
	simSx + simW > sourceForm width
		ifTrue: [simW _ simW - (simSx + simW - sourceForm width)].
	simSy < 0
		ifTrue: [simDy _ simDy - simSy. simH _ simH + simSy. simSy _ 0].
	simSy + simH > sourceForm height
		ifTrue: [simH _ simH - (simSy + simH - sourceForm height)].
! !

!BitBlt methodsFor: 'simulation' stamp: 'tfel 3/15/2013 10:12'!
simulateCopyBits

	self sanitizeInput.
	self simClipRange.
	(simW <= 0 or: [simH <= 0])
		ifTrue: [^ self].
	self computeMasks.
	self checkOverlap.
	self calculateOffsets.
	self copyLoop.! !


!BitBlt class methodsFor: 'benchmarks' stamp: 'tfel 3/13/2013 14:48'!
simpleBenchmark
	| aBitBlt depth f time |
	depth := Display depth.
	Display newDepth: 1.
	time := Time millisecondsToRun: [
		f := Form extent: 20 @ 20.
		f fillBlack.
		aBitBlt := BitBlt
			destForm: Display
			sourceForm: f
			fillColor: Color gray
			combinationRule: 5
			destOrigin: Sensor cursorPoint
			sourceOrigin: 0 @ 0
			extent: f extent
			clipRect: Display computeBoundingBox.
		aBitBlt simulateCopyBits].
	Display newDepth: depth.
	^ time! !

!BitBlt class methodsFor: 'examples' stamp: 'tfel 3/13/2013 13:40'!
exampleOne
	"This tests BitBlt by displaying the result of all sixteen combination rules that BitBlt is capable of using. (Please see the comment in BitBlt for the meaning of the combination rules). This only works at Display depth of 1. (Rule 15 does not work?)"
	| pathClass path displayDepth |

	displayDepth := Display depth.
	Display newDepth: 1.

	(Smalltalk hasClassNamed: #Path)
		ifTrue: [pathClass := Smalltalk at: #Path.
				path := pathClass new.
				0 to: 3 do: [:i | 0 to: 3 do: [:j | path add: j * 100 @ (i * 75)]].
				path := path translateBy: 60 @ 40.]
		ifFalse: ["For mini image, where Path isn't available"
				path := OrderedCollection new: 16.
				#(40 115 190 265) do: [:y |
					#(60 160 260 360) do: [:x |
						path add: x at y]]].
	Display fillWhite.
	1 to: 16 do: [:index | BitBlt
			exampleAt: (path at: index)
			rule: index - 1
			fillColor: nil].

	[Sensor anyButtonPressed] whileFalse: [].
	Display newDepth: displayDepth.

	"BitBlt exampleOne"! !

!BitBlt class methodsFor: 'examples' stamp: 'tfel 3/13/2013 13:12'!
exampleTwo
	"This is to test painting with a gray tone. It also tests that the seaming with gray patterns is correct in the microcode. Lets you paint for a while and then automatically stops. This only works at Depth of 1."
	| f aBitBlt displayDepth |
	"create a small black Form source as a brush. "
	displayDepth := Display depth.
	Display newDepth: 1.
	f := Form extent: 20 @ 20.
	f fillBlack.
	"create a BitBlt which will OR gray into the display. "
	aBitBlt := BitBlt
		destForm: Display
		sourceForm: f
		fillColor: Color gray
		combinationRule: Form over
		destOrigin: Sensor cursorPoint
		sourceOrigin: 0 @ 0
		extent: f extent
		clipRect: Display computeBoundingBox.
	"paint the gray Form on the screen for a while. "
	[Sensor anyButtonPressed] whileFalse: 
		[aBitBlt destOrigin: Sensor cursorPoint.
		aBitBlt simulateCopyBits].
	Display newDepth: displayDepth.
	"BitBlt exampleTwo"! !

!BitBlt class methodsFor: 'private' stamp: 'tfel 3/13/2013 09:05'!
exampleAt: originPoint rule: rule fillColor: mask 
	"This builds a source and destination form and copies the source to the
	destination using the specifed rule and mask. It is called from the method
	named exampleOne. Only works with Display depth of 1"

	| s d border aBitBlt | 
	border:=Form extent: 32 at 32.
	border fillBlack.
	border fill: (1 at 1 extent: 30 at 30) fillColor: Color white.
	s := Form extent: 32 at 32.
	s fillWhite.
	s fillBlack: (7 at 7 corner: 25 at 25).
	d := Form extent: 32 at 32.
	d fillWhite.
	d fillBlack: (0 at 0 corner: 32 at 16).

	s displayOn: Display at: originPoint.
	border displayOn: Display at: originPoint rule: Form under.
	d displayOn: Display at: originPoint + (s width @0).
	border displayOn: Display at: originPoint + (s width @0) rule: Form under.

	d displayOn: Display at: originPoint + (s extent // (2 @ 1)). 
	aBitBlt := BitBlt
		destForm: Display
		sourceForm: s
		fillColor: mask
		combinationRule: rule
		destOrigin: originPoint + (s extent // (2 @ 1))
		sourceOrigin: 0 @ 0
		extent: s extent
		clipRect: Display computeBoundingBox.
	aBitBlt simulateCopyBits.
	border 
		displayOn: Display at: originPoint + (s extent // (2 @ 1))
		rule: Form under.

	"BitBlt exampleAt: 100 at 100 rule: 0 fillColor: nil"  ! !

!BitBlt class methodsFor: 'class initialization' stamp: 'tfel 3/15/2013 10:23'!
initialize
	"self initialize"
	super initialize.
	WordSize := 32.
	WordSize0 := WordSize - 1.
	RightMasks _ #(0), (1 to: WordSize) collect: [:m | (2 raisedTo: m) - 1].
	AllOnes _ (2 raisedTo: WordSize) - 1.
! !

BitBlt initialize!
Object subclass: #BitBlt
	instanceVariableNames: 'destForm sourceForm halftoneForm combinationRule destX destY width height sourceX sourceY clipX clipY clipWidth clipHeight colorMap simW simH simSx simSy simDx simDy simDestBits simDestRaster simSourceBits simSourceRaster simHalftoneBits simSkew simMask1 simMask2 simSkewMask simNWords simHDir simVDir simPreload simSourceIndex simDestIndex simSourceDelta simDestDelta'
	classVariableNames: 'AllOnes RightMasks WordSize WordSize0'
	poolDictionaries: ''
	category: 'Graphics-Support'!
\ No newline at end of file


More information about the pypy-commit mailing list