[pypy-commit] lang-smalltalk default: merge bitblt

timfel noreply at buildbot.pypy.org
Mon Mar 18 14:12:54 CET 2013


Author: Tim Felgentreff <timfelgentreff at gmail.com>
Branch: 
Changeset: r212:4530b0bf03a4
Date: 2013-03-18 14:12 +0100
http://bitbucket.org/pypy/lang-smalltalk/changeset/4530b0bf03a4/

Log:	merge bitblt

diff --git a/BitBltSim.19.cs b/BitBltSim.19.cs
new file mode 100644
--- /dev/null
+++ b/BitBltSim.19.cs
@@ -0,0 +1,674 @@
+'From Squeak4.4 of 15 December 2012 [latest update: #12303] on 17 March 2013 at 4:20:53 pm'!
+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 simInDebug '
+	classVariableNames: 'AllOnes RightMasks WordSize0 WordSize '
+	poolDictionaries: ''
+	category: 'Graphics-Support'!
+TestCase subclass: #BitBltSimTest
+	instanceVariableNames: 'path '
+	classVariableNames: ''
+	poolDictionaries: ''
+	category: 'GraphicsTests-Primitives'!
+
+!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/17/2013 16:16'!
+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 bitInvert32.
+									t _ simMask1.
+									simMask1 _ simMask2.
+									simMask2 _ t]]]! !
+
+!BitBlt methodsFor: 'simulation' stamp: 'tfel 3/17/2013 16:16'!
+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) bitInvert32.
+	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/17/2013 16:17'!
+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 \\ simHalftoneBits size)).
+				simDy _ simDy + simVDir]
+			ifFalse: [halftoneWord _ AllOnes].
+		skewWord _ halftoneWord.
+		simPreload
+			ifTrue: [prevWord _ simSourceBits at: simSourceIndex + 1.
+					"load the 32bit shifter. TODO: check if this is WordSize dependent"
+					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.
+						    "XXX: Hack to work around out-of-bounds access"
+					thisWord := simSourceBits at: (simSourceIndex \\ simSourceBits size) + 1.
+										      	 "pick up next word"
+					skewWord _
+						prevWord bitOr: (thisWord bitAnd: simSkewMask bitInvert32).
+					prevWord _ thisWord.
+					"Change from BB: bitAnd: AllOnes to stay in word bounds"
+					skewWord _ ((skewWord bitShift: simSkew) bitAnd: AllOnes) 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 bitInvert32
+									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/17/2013 16:17'!
+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 bitInvert32].
+	combinationRule = 3 ifTrue: [^ srcWord].
+	combinationRule = 4 ifTrue: [^ srcWord bitInvert32 bitAnd: dstWord].
+	combinationRule = 5 ifTrue: [^ dstWord].
+	combinationRule = 6 ifTrue: [^ srcWord bitXor: dstWord].
+	combinationRule = 7 ifTrue: [^ srcWord bitOr: dstWord].
+	combinationRule = 8 ifTrue: [^ srcWord bitInvert32 bitAnd: dstWord bitInvert32].
+	combinationRule = 9 ifTrue: [^ srcWord bitInvert32 bitXor: dstWord].
+	combinationRule = 10 ifTrue: [^ dstWord bitInvert32].
+	combinationRule = 11 ifTrue: [^ srcWord bitOr: dstWord bitInvert32].
+	combinationRule = 12 ifTrue: [^ srcWord bitInvert32].
+	combinationRule = 13 ifTrue: [^ srcWord bitInvert32 bitOr: dstWord].
+	combinationRule = 14 ifTrue: [^ srcWord bitInvert32 bitOr: dstWord bitInvert32].
+	combinationRule = 15 ifTrue: [^ dstWord]! !
+
+!BitBlt methodsFor: 'simulation' stamp: 'tfel 3/15/2013 14:49'!
+sanitizeInput
+
+	destForm unhibernate.
+	sourceForm
+		ifNil: [sourceForm := destForm]
+		ifNotNil: [sourceForm unhibernate].
+	halftoneForm ifNotNil: [
+		(halftoneForm isKindOf: Form)
+			ifFalse: [halftoneForm := Form new
+										bits: halftoneForm;
+										yourself].
+		halftoneForm unhibernate].
+	width ifNil: [width := sourceForm width].
+	height ifNil: [height := sourceForm height].! !
+
+!BitBlt methodsFor: 'simulation' stamp: 'tfel 3/15/2013 13:04'!
+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/16/2013 17:31'!
+simDebug: aString
+
+	simInDebug == true
+		ifTrue: [1 to: 400 by: 20
+			   do: [:word | Display bits at: word put: 0].
+			simInDebug _ false]
+		ifFalse: [1 to: 400 by: 20
+			    do: [:word | Display bits at: word put: 4294967295].
+			simInDebug _ true]
+! !
+
+!BitBlt methodsFor: 'simulation' stamp: 'tfel 3/16/2013 17:30'!
+simulateCopyBits
+
+	"self simDebug: Time now asString."
+	self sanitizeInput.
+	self simClipRange.
+	(simW <= 0 or: [simH <= 0])
+		ifTrue: [^ self].
+	self computeMasks.
+	self checkOverlap.
+	self calculateOffsets.
+	self copyLoop.! !
+
+
+!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/15/2013 14:32'!
+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.
+! !
+
+
+!BitBltSimTest methodsFor: 'sourceForm' stamp: 'tfel 3/15/2013 14:24'!
+destForm
+	"black top half, white bottom half"
+	| bitmap |
+	bitmap := Bitmap new: 32.
+	 #(4294967295 4294967295 4294967295 4294967295
+		4294967295 4294967295 4294967295 4294967295
+		4294967295 4294967295 4294967295 4294967295
+		4294967295 4294967295 4294967295 4294967295
+		0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0) withIndexDo: [:word :idx |
+			bitmap at: idx put: word].
+	^ (Form extent: 32 at 32 depth: 1)
+		bits: bitmap;
+		yourself! !
+
+!BitBltSimTest methodsFor: 'sourceForm' stamp: 'tfel 3/15/2013 14:24'!
+sourceForm
+	"white form with black rect in the middle"
+	| bitmap |
+	bitmap := Bitmap new: 32.
+	#(0 0 0 0 0 0 0 33554304 33554304 33554304 33554304
+	33554304 33554304 33554304 33554304 33554304
+	33554304 33554304 33554304 33554304 33554304
+	33554304 33554304 33554304 33554304 0 0 0 0 0 0 0) withIndexDo: [:word :idx |
+		bitmap at: idx put: word].
+	^ (Form extent: 32 at 32 depth: 1)
+		bits: bitmap;
+		yourself! !
+
+!BitBltSimTest methodsFor: 'testing' stamp: 'tfel 3/15/2013 11:24'!
+test1
+
+	self runTest: 1.! !
+
+!BitBltSimTest methodsFor: 'testing' stamp: 'tfel 3/15/2013 11:41'!
+test10
+
+	self runTest: 10.! !
+
+!BitBltSimTest methodsFor: 'testing' stamp: 'tfel 3/15/2013 11:39'!
+test11
+
+	self runTest: 11.! !
+
+!BitBltSimTest methodsFor: 'testing' stamp: 'tfel 3/15/2013 11:28'!
+test12
+
+	self runTest: 12.! !
+
+!BitBltSimTest methodsFor: 'testing' stamp: 'tfel 3/15/2013 11:28'!
+test13
+
+	self runTest: 13.! !
+
+!BitBltSimTest methodsFor: 'testing' stamp: 'tfel 3/15/2013 11:29'!
+test14
+
+	self runTest: 14.! !
+
+!BitBltSimTest methodsFor: 'testing' stamp: 'tfel 3/15/2013 11:29'!
+test15
+
+	self runTest: 15.! !
+
+!BitBltSimTest methodsFor: 'testing' stamp: 'tfel 3/15/2013 11:29'!
+test16
+
+	self runTest: 16.! !
+
+!BitBltSimTest methodsFor: 'testing' stamp: 'tfel 3/15/2013 11:24'!
+test2
+
+	self runTest: 2.! !
+
+!BitBltSimTest methodsFor: 'testing' stamp: 'tfel 3/15/2013 11:24'!
+test3
+
+	self runTest: 3.! !
+
+!BitBltSimTest methodsFor: 'testing' stamp: 'tfel 3/15/2013 11:24'!
+test4
+
+	self runTest: 4.! !
+
+!BitBltSimTest methodsFor: 'testing' stamp: 'tfel 3/15/2013 11:24'!
+test5
+
+	self runTest: 5.! !
+
+!BitBltSimTest methodsFor: 'testing' stamp: 'tfel 3/15/2013 11:24'!
+test6
+
+	self runTest: 6.! !
+
+!BitBltSimTest methodsFor: 'testing' stamp: 'tfel 3/15/2013 11:24'!
+test7
+
+	self runTest: 7.! !
+
+!BitBltSimTest methodsFor: 'testing' stamp: 'tfel 3/15/2013 11:24'!
+test8
+
+	self runTest: 8.! !
+
+!BitBltSimTest methodsFor: 'testing' stamp: 'tfel 3/15/2013 11:24'!
+test9
+
+	self runTest: 9.! !
+
+!BitBltSimTest methodsFor: 'test data' stamp: 'tfel 3/15/2013 14:43'!
+bitsForTest: index
+	| results |
+	results := #(
+		#(0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0)
+		
+		#(0 0 0 0 0 0 0 33554304 33554304 33554304 33554304 33554304 33554304 33554304 33554304 33554304 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0)
+
+		#(0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 33554304 33554304 33554304 33554304 33554304 33554304 33554304 33554304 33554304 0 0 0 0 0 0 0)
+
+		#(0 0 0 0 0 0 0 33554304 33554304 33554304 33554304 33554304 33554304 33554304 33554304 33554304 33554304 33554304 33554304 33554304 33554304 33554304 33554304 33554304 33554304 0 0 0 0 0 0 0)
+
+		#(4294967295 4294967295 4294967295 4294967295 4294967295 4294967295 4294967295 4261412991 4261412991 4261412991 4261412991 4261412991 4261412991 4261412991 4261412991 4261412991 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0)
+
+		#(4294967295 4294967295 4294967295 4294967295 4294967295 4294967295 4294967295 4294967295 4294967295 4294967295 4294967295 4294967295 4294967295 4294967295 4294967295 4294967295 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0)
+
+		#(4294967295 4294967295 4294967295 4294967295 4294967295 4294967295 4294967295 4261412991 4261412991 4261412991 4261412991 4261412991 4261412991 4261412991 4261412991 4261412991 33554304 33554304 33554304 33554304 33554304 33554304 33554304 33554304 33554304 0 0 0 0 0 0 0)
+
+		#(4294967295 4294967295 4294967295 4294967295 4294967295 4294967295 4294967295 4294967295 4294967295 4294967295 4294967295 4294967295 4294967295 4294967295 4294967295 4294967295 33554304 33554304 33554304 33554304 33554304 33554304 33554304 33554304 33554304 0 0 0 0 0 0 0)
+
+		#(0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 4261412991 4261412991 4261412991 4261412991 4261412991 4261412991 4261412991 4261412991 4261412991 4294967295 4294967295 4294967295 4294967295 4294967295 4294967295 4294967295)
+
+		#(0 0 0 0 0 0 0 33554304 33554304 33554304 33554304 33554304 33554304 33554304 33554304 33554304 4261412991 4261412991 4261412991 4261412991 4261412991 4261412991 4261412991 4261412991 4261412991 4294967295 4294967295 4294967295 4294967295 4294967295 4294967295 4294967295)
+
+		#(0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 4294967295 4294967295 4294967295 4294967295 4294967295 4294967295 4294967295 4294967295 4294967295 4294967295 4294967295 4294967295 4294967295 4294967295 4294967295 4294967295)
+
+		#(0 0 0 0 0 0 0 33554304 33554304 33554304 33554304 33554304 33554304 33554304 33554304 33554304 4294967295 4294967295 4294967295 4294967295 4294967295 4294967295 4294967295 4294967295 4294967295 4294967295 4294967295 4294967295 4294967295 4294967295 4294967295 4294967295)
+
+		#(4294967295 4294967295 4294967295 4294967295 4294967295 4294967295 4294967295 4261412991 4261412991 4261412991 4261412991 4261412991 4261412991 4261412991 4261412991 4261412991 4261412991 4261412991 4261412991 4261412991 4261412991 4261412991 4261412991 4261412991 4261412991 4294967295 4294967295 4294967295 4294967295 4294967295 4294967295 4294967295)
+
+		#(4294967295 4294967295 4294967295 4294967295 4294967295 4294967295 4294967295 4294967295 4294967295 4294967295 4294967295 4294967295 4294967295 4294967295 4294967295 4294967295 4261412991 4261412991 4261412991 4261412991 4261412991 4261412991 4261412991 4261412991 4261412991 4294967295 4294967295 4294967295 4294967295 4294967295 4294967295 4294967295)
+
+		#(4294967295 4294967295 4294967295 4294967295 4294967295 4294967295 4294967295 4261412991 4261412991 4261412991 4261412991 4261412991 4261412991 4261412991 4261412991 4261412991 4294967295 4294967295 4294967295 4294967295 4294967295 4294967295 4294967295 4294967295 4294967295 4294967295 4294967295 4294967295 4294967295 4294967295 4294967295 4294967295)
+
+		#(4294967295 4294967295 4294967295 4294967295 4294967295 4294967295 4294967295 4294967295 4294967295 4294967295 4294967295 4294967295 4294967295 4294967295 4294967295 4294967295 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0)
+	).
+
+	^ results at: index! !
+
+!BitBltSimTest methodsFor: 'running-modes' stamp: 'tfel 3/17/2013 16:18'!
+runTest: index
+	"self runTestVisual: index" "to show something"
+	self runTestLarge: index "to test non-aligned stuff"
+	"self runTestDark: index" "to run without blitting primitive, against saved data"
+! !
+
+!BitBltSimTest methodsFor: 'running-modes' stamp: 'tfel 3/15/2013 14:37'!
+runTestDark: index
+	| s d rule | 
+	rule := index - 1.
+	s := self sourceForm.
+	d := self destForm.
+	(BitBlt
+		destForm: d
+		sourceForm: s
+		fillColor: nil
+		combinationRule: rule
+		destOrigin: 0 at 0
+		sourceOrigin: 0 at 0
+		extent: s extent
+		clipRect: (0 at 0 extent: d extent))
+		simulateCopyBits.
+	self assert: d bits asArray = (self bitsForTest: index).
+! !
+
+!BitBltSimTest methodsFor: 'running-modes' stamp: 'tfel 3/15/2013 14:30'!
+runTestLarge: index
+	| s d aBitBlt mask rule simD originPoint destOrigin | 
+	originPoint := path at: index.
+	rule := index - 1.
+	mask := nil.
+	s := Form extent: 32 at 32.
+	s fillWhite.
+	s fillBlack: (7 at 7 corner: 25 at 25).
+	d := Form extent: 500 at 500.
+	d fillWhite.
+	d fillBlack: (0 at 0 corner: 32 at 16).
+	destOrigin := originPoint + (s extent // (2 @ 1)).
+
+	simD := d deepCopy.
+	aBitBlt := BitBlt
+		destForm: simD
+		sourceForm: s
+		fillColor: mask
+		combinationRule: rule
+		destOrigin: destOrigin
+		sourceOrigin: 0 @ 0
+		extent: s extent
+		clipRect: simD computeBoundingBox.
+	aBitBlt simulateCopyBits.
+	
+	aBitBlt := BitBlt
+		destForm: d
+		sourceForm: s
+		fillColor: mask
+		combinationRule: rule
+		destOrigin: destOrigin
+		sourceOrigin: 0 @ 0
+		extent: s extent
+		clipRect: d computeBoundingBox.
+	aBitBlt copyBits.
+	self assert: [d bits = simD bits].
+! !
+
+!BitBltSimTest methodsFor: 'running-modes' stamp: 'tfel 3/15/2013 14:43'!
+runTestVisual: index
+	| s d aBitBlt mask rule simD originPoint destOrigin | 
+	originPoint := path at: index.
+	rule := index - 1.
+	mask := nil.
+	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).
+	destOrigin := 0 @ 0.
+
+	simD := d deepCopy.
+	aBitBlt := BitBlt
+		destForm: simD
+		sourceForm: s
+		fillColor: mask
+		combinationRule: rule
+		destOrigin: destOrigin
+		sourceOrigin: 0 @ 0
+		extent: s extent
+		clipRect: simD computeBoundingBox.
+	aBitBlt simulateCopyBits.
+	
+	aBitBlt := BitBlt
+		destForm: d
+		sourceForm: s
+		fillColor: mask
+		combinationRule: rule
+		destOrigin: destOrigin
+		sourceOrigin: 0 @ 0
+		extent: s extent
+		clipRect: d computeBoundingBox.
+	aBitBlt copyBits.
+
+	simD displayOn: Display at: originPoint + (s width @ 0) rule: Form over.
+	d displayOn: Display at: originPoint - (10 at 0) rule: Form over.
+	
+	d bits = simD bits
+		ifTrue: [index asString displayAt: originPoint - 20]
+		ifFalse: [(index asString, ' failed') displayAt: originPoint - 20. self assert: false].! !
+
+!BitBltSimTest methodsFor: 'initialize-release' stamp: 'tfel 3/15/2013 14:38'!
+initialize
+
+	super initialize.
+	"World restoreDisplay."
+	"(Form extent: 500 at 300 depth: 32)
+		fill: (0 at 0 extent: 500 at 300) fillColor: Color green muchDarker;
+		displayOn: Display at: 0 at 0 rule: Form over."! !
+
+!BitBltSimTest methodsFor: 'running' stamp: 'tfel 3/15/2013 11:38'!
+setUp
+	| pathClass |
+	(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]]].
+		! !
+
+
+!BitBltSimTest class methodsFor: 'as yet unclassified' stamp: 'tfel 3/17/2013 16:08'!
+runAllTestsBlind
+
+	1 to: 16 do: [:idx |
+		self new
+			setUp;
+			runTestDark: idx].! !
+
+TestCase subclass: #BitBltSimTest
+	instanceVariableNames: 'path'
+	classVariableNames: ''
+	poolDictionaries: ''
+	category: 'GraphicsTests-Primitives'!
+
+!BitBltSimTest reorganize!
+('sourceForm' destForm sourceForm)
+('testing' test1 test10 test11 test12 test13 test14 test15 test16 test2 test3 test4 test5 test6 test7 test8 test9)
+('test data' bitsForTest:)
+('running-modes' runTest: runTestDark: runTestLarge: runTestVisual:)
+('initialize-release' initialize)
+('running' setUp)
+!
+
+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 simInDebug'
+	classVariableNames: 'AllOnes RightMasks WordSize WordSize0'
+	poolDictionaries: ''
+	category: 'Graphics-Support'!
diff --git a/images/mini.image b/images/mini.image
index 4e0739b0aa769798ae904fee0eff0b0eac8c8368..a8cfbe28687d27aca4ab2d9dd0f37da338fd475d
GIT binary patch

[cut]

diff --git a/images/minibluebookdebug.image b/images/minibluebookdebug.image
new file mode 100644
index 0000000000000000000000000000000000000000..55870b1f6092dbfa3dcb4e4d0c46fec62b223bf2
GIT binary patch

[cut]

diff --git a/images/running-something-mini.image b/images/running-something-mini.image
index e87374dba659882613fccb6486bb1da78b5e7fde..ac12f8bf556e24ceb6046e03ef26d92e1e1201bf
GIT binary patch

[cut]

diff --git a/spyvm/constants.py b/spyvm/constants.py
--- a/spyvm/constants.py
+++ b/spyvm/constants.py
@@ -114,7 +114,7 @@
     "BlockClosure" : SO_BLOCKCLOSURE_CLASS,
     "Point" : SO_POINT_CLASS,
     "LargePositiveInteger" : SO_LARGEPOSITIVEINTEGER_CLASS,
-#    "Message" : SO_MESSAGE_CLASS,
+    "Message" : SO_MESSAGE_CLASS,
     "CompiledMethod" : SO_COMPILEDMETHOD_CLASS,
     "Semaphore" : SO_SEMAPHORE_CLASS,
     "Character" : SO_CHARACTER_CLASS,
@@ -134,6 +134,7 @@
     "special_selectors": SO_SPECIAL_SELECTORS_ARRAY,
     "smalltalkdict" : SO_SMALLTALK,
     "display" : SO_DISPLAY_OBJECT,
+    "doesNotUnderstand" : SO_DOES_NOT_UNDERSTAND,
     "interrupt_semaphore" : SO_USER_INTERRUPT_SEMAPHORE,
 }
 
diff --git a/spyvm/display.py b/spyvm/display.py
new file mode 100644
--- /dev/null
+++ b/spyvm/display.py
@@ -0,0 +1,41 @@
+from rpython.rlib.rarithmetic import r_uint
+from rpython.rtyper.lltypesystem import lltype, rffi
+
+from rsdl import RSDL, RSDL_helper
+
+
+class SDLDisplay(object):
+    _attrs_ = ["screen", "width", "height", "depth", "surface", "has_surface"]
+
+    def __init__(self):
+        assert RSDL.Init(RSDL.INIT_VIDEO) >= 0
+        self.has_surface = False
+
+    def set_video_mode(self, w, h, d):
+        assert w > 0 and h > 0
+        assert d in [1, 2, 4, 8, 16, 32]
+        self.width = w
+        self.height = h
+        self.depth = d
+        self.screen = RSDL.SetVideoMode(w, h, 32, 0)
+        assert self.screen
+        # self.fillwhite()
+
+    def set_pixelbuffer(self, pixelbuffer):
+        if self.has_surface:
+            RSDL.FreeSurface(self.surface)
+        pitch = 4 * self.width
+        rmask, gmask, bmask, amask = r_uint(0x000000FF), r_uint(0x0000FF00), r_uint(0x00FF0000), r_uint(0xFF000000)
+        self.surface = RSDL.CreateRGBSurfaceFrom(pixelbuffer, self.width, self.height, 32, pitch,
+                                                 rmask, gmask, bmask, amask)
+        self.has_surface = True
+
+    def fillwhite(self):
+        fmt = self.screen.c_format
+        color = RSDL.MapRGB(fmt, 255, 255, 255)
+        RSDL.FillRect(self.screen, lltype.nullptr(RSDL.Rect), color)
+        RSDL.Flip(self.screen)
+
+    def blit(self):
+        RSDL.BlitSurface(self.surface, lltype.nullptr(RSDL.Rect), self.screen, lltype.nullptr(RSDL.Rect))
+        RSDL.Flip(self.screen)
diff --git a/spyvm/interpreter.py b/spyvm/interpreter.py
--- a/spyvm/interpreter.py
+++ b/spyvm/interpreter.py
@@ -1,5 +1,5 @@
 import py
-from spyvm.shadow import ContextPartShadow, MethodContextShadow, BlockContextShadow
+from spyvm.shadow import ContextPartShadow, MethodContextShadow, BlockContextShadow, MethodNotFound
 from spyvm import model, constants, primitives, conftest, wrapper
 from spyvm.tool.bitmanipulation import splitter
 
@@ -287,9 +287,23 @@
                 interp._last_indent, w_selector.as_string(), receiver,
                 [self.peek(argcount-1-i) for i in range(argcount)])
         assert argcount >= 0
-        s_method = receiverclassshadow.lookup(w_selector)
-        # XXX catch MethodNotFound here and send doesNotUnderstand:
-        # AK shouln't that be done in lookup itself, please check what spec says about DNU in case of super sends.
+        try:
+            s_method = receiverclassshadow.lookup(w_selector)
+        except MethodNotFound:
+            arguments = self.pop_and_return_n(argcount)
+            s_message_class = self.space.classtable["w_Message"].as_class_get_shadow(self.space)
+            w_message = s_message_class.new()
+            w_message.store(self.space, 0, w_selector)
+            w_message.store(self.space, 1, self.space.wrap_list(arguments))
+            try:
+                s_method = receiverclassshadow.lookup(self.space.objtable["w_doesNotUnderstand"])
+            except MethodNotFound:
+                print "Missing doesDoesNotUnderstand in hierarchy of %s" % receiverclassshadow.getname()
+                raise
+            s_frame = s_method.create_frame(self.space, receiver, [w_message], self)
+            self.pop()
+            return interp.stack_frame(s_frame)
+
         code = s_method.primitive()
         if code:
             # the primitive pushes the result (if any) onto the stack itself
diff --git a/spyvm/model.py b/spyvm/model.py
--- a/spyvm/model.py
+++ b/spyvm/model.py
@@ -2,9 +2,9 @@
 Squeak model.
 
     W_Object
-        W_SmallInteger        
-        W_Float
+        W_SmallInteger
         W_AbstractObjectWithIdentityHash
+            W_Float
             W_AbstractObjectWithClassReference
                 W_PointersObject 
                 W_BytesObject
@@ -21,7 +21,9 @@
 from rpython.rlib import rrandom, objectmodel, jit
 from rpython.rlib.rarithmetic import intmask, r_uint
 from rpython.tool.pairtype import extendabletype
-from rpython.rlib.objectmodel import instantiate
+from rpython.rlib.objectmodel import instantiate, compute_hash
+from rpython.rtyper.lltypesystem import lltype, rffi
+from rsdl import RSDL, RSDL_helper
 
 class W_Object(object):
     """Root of Squeak model, abstract."""
@@ -152,7 +154,33 @@
     def clone(self, space):
         return self
 
-class W_Float(W_Object):
+class W_AbstractObjectWithIdentityHash(W_Object):
+    """Object with explicit hash (ie all except small
+    ints and floats)."""
+    _attrs_ = ['hash']
+
+    #XXX maybe this is too extreme, but it's very random
+    hash_generator = rrandom.Random()
+    UNASSIGNED_HASH = sys.maxint
+
+    hash = UNASSIGNED_HASH # default value
+
+    def setchar(self, n0, character):
+        raise NotImplementedError()
+
+    def gethash(self):
+        if self.hash == self.UNASSIGNED_HASH:
+            self.hash = hash = intmask(self.hash_generator.genrand32()) // 2
+            return hash
+        return self.hash
+
+    def invariant(self):
+        return isinstance(self.hash, int)
+
+    def _become(self, w_other):
+        self.hash, w_other.hash = w_other.hash, self.hash
+
+class W_Float(W_AbstractObjectWithIdentityHash):
     """Boxed float value."""
     _attrs_ = ['value']
 
@@ -170,11 +198,15 @@
         return space.w_Float
 
     def gethash(self):
-        return 41    # XXX check this
+        return compute_hash(self.value)
 
     def invariant(self):
-        return self.value is not None        # XXX but later:
-        #return isinstance(self.value, float)
+        return isinstance(self.value, float)
+
+    def _become(self, w_other):
+        self.value, w_other.value = w_other.value, self.value
+        W_AbstractObjectWithIdentityHash._become(self, w_other)
+
     def __repr__(self):
         return "W_Float(%f)" % self.value
 
@@ -226,33 +258,6 @@
             r = ((r >> 32) << 32) | uint
         self.value = float_unpack(r, 8)
 
-
-class W_AbstractObjectWithIdentityHash(W_Object):
-    """Object with explicit hash (ie all except small
-    ints and floats)."""
-    _attrs_ = ['hash']
-
-    #XXX maybe this is too extreme, but it's very random
-    hash_generator = rrandom.Random()
-    UNASSIGNED_HASH = sys.maxint
-
-    hash = UNASSIGNED_HASH # default value
-
-    def setchar(self, n0, character):
-        raise NotImplementedError()
-
-    def gethash(self):
-        if self.hash == self.UNASSIGNED_HASH:
-            self.hash = hash = intmask(self.hash_generator.genrand32()) // 2
-            return hash
-        return self.hash
-
-    def invariant(self):
-        return isinstance(self.hash, int)
-
-    def _become(self, w_other):
-        self.hash, w_other.hash = w_other.hash, self.hash
-
 class W_AbstractObjectWithClassReference(W_AbstractObjectWithIdentityHash):
     """Objects with arbitrary class (ie not CompiledMethod, SmallInteger or
     Float)."""
@@ -523,6 +528,83 @@
         w_result.words = list(self.words)
         return w_result
 
+NATIVE_DEPTH = 32
+class W_DisplayBitmap(W_AbstractObjectWithClassReference):
+    _attrs_ = ['pixelbuffer', '_depth', '_realsize', 'display']
+    _immutable_fields_ = ['_depth', '_realsize', 'display']
+
+    def __init__(self, w_class, size, depth, display):
+        W_AbstractObjectWithClassReference.__init__(self, w_class)
+        assert depth == 1 # XXX: Only support B/W for now
+        bytelen = NATIVE_DEPTH / depth * size * 4
+        self.pixelbuffer = lltype.malloc(rffi.VOIDP.TO, bytelen, flavor='raw')
+        self._depth = depth
+        self._realsize = size
+        self.display = display
+
+    def __del__(self):
+        lltype.free(self.pixelbuffer, flavor='raw')
+
+    def at0(self, space, index0):
+        val = self.getword(index0)
+        return space.wrap_uint(val)
+
+    def atput0(self, space, index0, w_value):
+        word = space.unwrap_uint(w_value)
+        self.setword(index0, word)
+
+    # XXX: Only supports 1-bit to 32-bit conversion for now
+    @jit.unroll_safe
+    def getword(self, n):
+        pixel_per_word = NATIVE_DEPTH / self._depth
+        word = r_uint(0)
+        pos = n * pixel_per_word * 4
+        for i in xrange(32):
+            word <<= 1
+            red = self.pixelbuffer[pos]
+            if red == '\0': # Black
+                word |= r_uint(1)
+            pos += 4
+        return word
+
+    @jit.unroll_safe
+    def setword(self, n, word):
+        pixel_per_word = NATIVE_DEPTH / self._depth
+        pos = n * pixel_per_word * 4
+        mask = r_uint(1)
+        mask <<= 31
+        for i in xrange(32):
+            bit = mask & word
+            if bit == 0: # white
+                self.pixelbuffer[pos]     = '\xff'
+                self.pixelbuffer[pos + 1] = '\xff'
+                self.pixelbuffer[pos + 2] = '\xff'
+            else:
+                self.pixelbuffer[pos]     = '\0'
+                self.pixelbuffer[pos + 1] = '\0'
+                self.pixelbuffer[pos + 2] = '\0'
+            self.pixelbuffer[pos + 3] = '\xff'
+            mask >>= 1
+            pos += 4
+
+    def flush_to_screen(self):
+        self.display.blit()
+
+    def size(self):
+        return self._realsize
+
+    def invariant(self):
+        return False
+
+    def clone(self, space):
+        w_result = W_WordsObject(self.w_class, self._realsize)
+        n = 0
+        while n < self._realsize:
+            w_result.words[n] = self.getword(n)
+            n += 1
+        return w_result
+
+
 # XXX Shouldn't compiledmethod have class reference for subclassed compiled
 # methods?
 class W_CompiledMethod(W_AbstractObjectWithIdentityHash):
diff --git a/spyvm/objspace.py b/spyvm/objspace.py
--- a/spyvm/objspace.py
+++ b/spyvm/objspace.py
@@ -87,6 +87,7 @@
         define_cls("w_SmallInteger", "w_Integer")
         define_cls("w_LargePositiveInteger", "w_Integer", format=shadow.BYTES)
         define_cls("w_Float", "w_Number", format=shadow.BYTES)
+        define_cls("w_Message", "w_Object")
         define_cls("w_Collection", "w_Object")
         define_cls("w_SequenceableCollection", "w_Collection")
         define_cls("w_ArrayedCollection", "w_SequenceableCollection")
@@ -285,6 +286,7 @@
             closure.atput0(i0, copiedValues[i0])
         return w_closure
 
+
 def bootstrap_class(space, instsize, w_superclass=None, w_metaclass=None,
                     name='?', format=shadow.POINTERS, varsized=False):
     from spyvm import model
diff --git a/spyvm/primitives.py b/spyvm/primitives.py
--- a/spyvm/primitives.py
+++ b/spyvm/primitives.py
@@ -4,6 +4,7 @@
 import operator
 from spyvm import model, shadow
 from spyvm import constants
+from spyvm import display
 from spyvm.error import PrimitiveFailedError, \
     PrimitiveNotYetWrittenError
 from spyvm import wrapper
@@ -523,7 +524,7 @@
 INPUT_SEMAPHORE = 93
 GET_NEXT_EVENT = 94
 INPUT_WORD = 95
-OBSOLETE_INDEXED = 96
+BITBLT_COPY_BITS = 96 # OBSOLETE_INDEXED = 96
 SNAPSHOT = 97
 STORE_IMAGE_SEGMENT = 98
 LOAD_IMAGE_SEGMENT = 99
@@ -531,7 +532,7 @@
 BE_CURSOR = 101
 BE_DISPLAY = 102
 SCAN_CHARACTERS = 103
-# OBSOLETE_INDEXED = 104 # also 96
+OBSOLETE_INDEXED = 104 # also 96
 STRING_REPLACE = 105
 SCREEN_SIZE = 106
 MOUSE_BUTTONS = 107
@@ -543,6 +544,21 @@
 def func(interp, s_frame, w_rcvr):
     raise PrimitiveNotYetWrittenError()
 
+ at expose_primitive(BITBLT_COPY_BITS, unwrap_spec=[object])
+def func(interp, s_frame, w_rcvr):
+    if not isinstance(w_rcvr, model.W_PointersObject) or w_rcvr.size() < 15:
+        raise PrimitiveFailedError
+
+    interp.perform(w_rcvr, "simulateCopyBits")
+
+    w_dest_form = w_rcvr.fetch(interp.space, 0)
+    if w_dest_form.is_same_object(interp.space.objtable['w_display']):
+        w_bitmap = w_dest_form.fetch(interp.space, 0)
+        assert isinstance(w_bitmap, model.W_DisplayBitmap)
+        w_bitmap.flush_to_screen()
+
+    return w_rcvr
+
 @expose_primitive(BE_CURSOR, unwrap_spec=[object])
 def func(interp, s_frame, w_rcvr):
     # TODO: Use info from cursor object.
@@ -554,6 +570,39 @@
     if not isinstance(w_rcvr, model.W_PointersObject) or w_rcvr.size() < 4:
         raise PrimitiveFailedError
     # the fields required are bits (a pointer to a Bitmap), width, height, depth
+
+    # XXX: TODO get the initial image TODO: figure out whether we
+    # should decide the width an report it in the other SCREEN_SIZE
+    w_bitmap = w_rcvr.fetch(interp.space, 0)
+    width = interp.space.unwrap_int(w_rcvr.fetch(interp.space, 1))
+    height = interp.space.unwrap_int(w_rcvr.fetch(interp.space, 2))
+    depth = interp.space.unwrap_int(w_rcvr.fetch(interp.space, 3))
+
+    sdldisplay = None
+
+    w_prev_display = interp.space.objtable['w_display']
+    if w_prev_display:
+        w_prev_bitmap = w_prev_display.fetch(interp.space, 0)
+        if isinstance(w_prev_bitmap, model.W_DisplayBitmap):
+            sdldisplay = w_prev_bitmap.display
+
+    if isinstance(w_bitmap, model.W_DisplayBitmap):
+        assert (sdldisplay is None) or (sdldisplay is w_bitmap.display)
+        sdldisplay = w_bitmap.display
+        w_display_bitmap = w_bitmap
+    else:
+        assert isinstance(w_bitmap, model.W_WordsObject)
+        if not sdldisplay:
+            sdldisplay = display.SDLDisplay()
+        w_display_bitmap = model.W_DisplayBitmap(w_bitmap.getclass(interp.space), w_bitmap.size(), depth, sdldisplay)
+        for idx, word in enumerate(w_bitmap.words):
+            w_display_bitmap.setword(idx, word)
+        w_rcvr.store(interp.space, 0, w_display_bitmap)
+
+    sdldisplay.set_video_mode(width, height, depth)
+    sdldisplay.set_pixelbuffer(w_display_bitmap.pixelbuffer)
+    sdldisplay.blit()
+
     interp.space.objtable['w_display'] = w_rcvr
     return w_rcvr
 
@@ -658,6 +707,7 @@
 VALUE_UNINTERRUPTABLY = 123
 LOW_SPACE_SEMAPHORE = 124
 SIGNAL_AT_BYTES_LEFT = 125
+DEFER_UPDATES = 126
 DRAW_RECTANGLE = 127
 
 @expose_primitive(IMAGE_NAME)
@@ -680,8 +730,13 @@
     # dont know when the space runs out
     return w_reciver
 
+ at expose_primitive(DEFER_UPDATES, unwrap_spec=[object, object])
+def func(interp, s_frame, w_receiver, w_bool):
+    raise PrimitiveNotYetWrittenError()
+
 @expose_primitive(DRAW_RECTANGLE, unwrap_spec=[object, int, int, int, int])
 def func(interp, s_frame, w_rcvr, left, right, top, bottom):
+    # import pdb; pdb.set_trace()
     raise PrimitiveNotYetWrittenError()
 
 
@@ -1135,6 +1190,21 @@
 CTXT_SIZE = 212
 
 # ___________________________________________________________________________
+# Drawing
+
+FORCE_DISPLAY_UPDATE = 231
+
+ at expose_primitive(FORCE_DISPLAY_UPDATE, unwrap_spec=[object])
+def func(interp, s_frame, w_rcvr):
+    w_prev_display = interp.space.objtable['w_display']
+    assert w_prev_display
+    w_prev_bitmap = w_prev_display.fetch(interp.space, 0)
+    assert isinstance(w_prev_bitmap, model.W_DisplayBitmap)
+    w_prev_bitmap.flush_to_screen()
+    return w_rcvr
+
+
+# ___________________________________________________________________________
 # PrimitiveLoadInstVar
 #
 # These are some wacky bytecodes in squeak.  They are defined to do
diff --git a/spyvm/shadow.py b/spyvm/shadow.py
--- a/spyvm/shadow.py
+++ b/spyvm/shadow.py
@@ -72,7 +72,6 @@
 WEAK_POINTERS = 3
 COMPILED_METHOD = 4
 FLOAT = 5
-DISPLAY_SCREEN = 6
 
 class MethodNotFound(error.SmalltalkException):
     pass
@@ -790,8 +789,11 @@
         return 0
 
     def short_str(self):
-        return 'BlockContext of %s (%i)' % (self.w_method().get_identifier_string(),
-                    self.pc() + 1)
+        return 'BlockContext of %s (%s) [%i]' % (
+            self.w_method().get_identifier_string(),
+            self.w_receiver(),
+            self.pc() + 1
+        )
 
 class MethodContextShadow(ContextPartShadow):
     _attr_ = ['w_closure_or_nil', '_w_receiver', '__w_method']
@@ -937,7 +939,12 @@
 
     def short_str(self):
         block = '[] of' if self.is_closure_context() else ''
-        return '%s %s (%i)' % (block, self.w_method().get_identifier_string(), self.pc() + 1)
+        return '%s %s (%s) [%i]' % (
+            block,
+            self.w_method().get_identifier_string(),
+            self.w_receiver(),
+            self.pc() + 1
+        )
 
 class CompiledMethodShadow(object):
     _attr_ = ["_w_self", "bytecode",
@@ -1031,6 +1038,7 @@
 
     def update(self): pass
 
+
 class ObserveeShadow(AbstractShadow):
     _attr_ = ['dependent']
     def __init__(self, space, w_self):
diff --git a/spyvm/test/test_miniimage.py b/spyvm/test/test_miniimage.py
--- a/spyvm/test/test_miniimage.py
+++ b/spyvm/test/test_miniimage.py
@@ -47,9 +47,9 @@
 def test_read_header():
     reader = open_miniimage(space)
     reader.read_header()
-    assert reader.endofmemory == 655196
-    assert reader.oldbaseaddress == -1220960256
-    assert reader.specialobjectspointer == -1220832384
+    assert reader.endofmemory == 726592
+    assert reader.oldbaseaddress == -1221464064
+    assert reader.specialobjectspointer == -1221336216
 
 def test_read_all_header(): 
     reader = open_miniimage(space)
@@ -113,8 +113,8 @@
    
 def test_special_classes0():
     image = get_image()
-    w = image.special(constants.SO_BITMAP_CLASS)
-    assert str(w) == "Bitmap class" 
+    # w = image.special(constants.SO_BITMAP_CLASS)
+    # assert str(w) == "Bitmap class" 
     w = image.special(constants.SO_SMALLINTEGER_CLASS)
     assert str(w) == "SmallInteger class" 
     w = image.special(constants.SO_STRING_CLASS)
@@ -131,6 +131,8 @@
     assert str(w) == "Point class" 
     w = image.special(constants.SO_LARGEPOSITIVEINTEGER_CLASS)
     assert str(w) == "LargePositiveInteger class" 
+    w = image.special(constants.SO_MESSAGE_CLASS)
+    assert str(w) == "Message class" 
 
     # to be continued
 
@@ -154,7 +156,7 @@
     assert repr(space.w_true.shadow_of_my_class(space)) == "<ClassShadow True>"
     assert repr(space.w_false.shadow_of_my_class(space)) == "<ClassShadow False>"
 
-def test_special_classes0():
+def test_special_objects0():
     image = get_image()
     w = image.special(constants.SO_DOES_NOT_UNDERSTAND)
     assert str(w) == "doesNotUnderstand:"
@@ -348,3 +350,24 @@
     w_result = perform(interp.space.w_Float, "new")
     assert w_result is not None
     assert isinstance(w_result, model.W_Float)
+
+def test_doesNotUnderstand():
+    w_dnu = interp.space.objtable["w_doesNotUnderstand"]
+    assert isinstance(w_dnu, model.W_BytesObject)
+    assert w_dnu.as_string() == "doesNotUnderstand:"
+
+def test_run_doesNotUnderstand():
+    from spyvm.test import test_miniimage
+    setup_module(test_miniimage, filename='running-something-mini.image')
+    w_result = test_miniimage.interp.perform(test_miniimage.interp.space.wrap_int(0), "runningADNU")
+    assert isinstance(w_result, model.W_BytesObject)
+    assert w_result.as_string() == "foobarThis:doesNotExist:('pypy' 'heya' )"
+
+def test_Message():
+    w_message_cls = interp.space.w_Message
+    assert w_message_cls is interp.space.classtable["w_Message"]
+    assert isinstance(w_message_cls, model.W_PointersObject)
+    s_message_cls = w_message_cls.as_class_get_shadow(interp.space)
+    assert s_message_cls.getname() == "Message class"
+    w_message = s_message_cls.new()
+    assert isinstance(w_message, model.W_PointersObject)
diff --git a/spyvm/test/test_model.py b/spyvm/test/test_model.py
--- a/spyvm/test/test_model.py
+++ b/spyvm/test/test_model.py
@@ -260,3 +260,32 @@
             assert math.isnan(target.value)
         else:
             assert target.value == f
+
+def test_float_hash():
+    target = model.W_Float(1.1)
+    assert target.gethash() == model.W_Float(1.1).gethash()
+    target.store(space, 0, space.wrap_int(42))
+    assert target.gethash() != model.W_Float(1.1).gethash()
+
+def test_display_bitmap():
+    target = model.W_DisplayBitmap(space.w_Array, 100, 1, None)
+    target.setword(0, 0xFF00)
+    assert bin(target.getword(0)) == bin(0xFF00)
+    target.setword(0, 0x00FF00FF)
+    assert bin(target.getword(0)) == bin(0x00FF00FF)
+    target.setword(0, 0xFF00FF00)
+    assert bin(target.getword(0)) == bin(0xFF00FF00)
+    for i in xrange(32):
+        if (i + 1) % 4 == 0:
+            assert target.pixelbuffer[i] == "\xff"
+        else:
+            assert target.pixelbuffer[i] == "\x00"
+    for i in xrange(32, 64):
+        assert target.pixelbuffer[i] == "\xff"    
+    for i in xrange(64, 96):
+        if (i + 1) % 4 == 0:
+            assert target.pixelbuffer[i] == "\xff"
+        else:
+            assert target.pixelbuffer[i] == "\x00"
+    for i in xrange(96, 128):
+        assert target.pixelbuffer[i] == "\xff"    
diff --git a/spyvm/test/test_primitives.py b/spyvm/test/test_primitives.py
--- a/spyvm/test/test_primitives.py
+++ b/spyvm/test/test_primitives.py
@@ -3,7 +3,7 @@
 import math
 from spyvm.primitives import prim_table, PrimitiveFailedError
 from spyvm import model, shadow, interpreter
-from spyvm import constants, primitives, objspace, wrapper
+from spyvm import constants, primitives, objspace, wrapper, display
 
 from rpython.rlib.rfloat import INFINITY, NAN, isinf, isnan
 
@@ -610,6 +610,80 @@
     assert w_2.getclass(space) is space.w_Array
     assert w_1 is not w_2
 
+def test_primitive_be_display():
+    assert space.objtable["w_display"] is None
+    mock_display = model.W_PointersObject(space.w_Point, 4)
+    w_wordbmp = model.W_WordsObject(space.w_Array, 100)
+    mock_display.store(space, 0, w_wordbmp) # bitmap
+    mock_display.store(space, 1, space.wrap_int(32)) # width
+    mock_display.store(space, 2, space.wrap_int(10)) # height
+    mock_display.store(space, 3, space.wrap_int(1))  # depth
+    prim(primitives.BE_DISPLAY, [mock_display])
+    assert space.objtable["w_display"] is mock_display
+    w_bitmap = mock_display.fetch(space, 0)
+    assert w_bitmap is not w_wordbmp
+    assert isinstance(w_bitmap, model.W_DisplayBitmap)
+    sdldisplay = w_bitmap.display
+    assert isinstance(sdldisplay, display.SDLDisplay)
+
+    mock_display2 = model.W_PointersObject(space.w_Point, 4)
+    mock_display2.store(space, 0, model.W_WordsObject(space.w_Array, 100)) # bitmap
+    mock_display2.store(space, 1, space.wrap_int(32)) # width
+    mock_display2.store(space, 2, space.wrap_int(10)) # height
+    mock_display2.store(space, 3, space.wrap_int(1))  # depth
+    prim(primitives.BE_DISPLAY, [mock_display2])
+    assert space.objtable["w_display"] is mock_display2
+    w_bitmap2 = mock_display.fetch(space, 0)
+    assert isinstance(w_bitmap2, model.W_DisplayBitmap)
+    assert w_bitmap.display is w_bitmap2.display
+    assert sdldisplay.width == 32
+    assert sdldisplay.height == 10
+
+    prim(primitives.BE_DISPLAY, [mock_display])
+    assert space.objtable["w_display"] is mock_display
+    assert mock_display.fetch(space, 0) is w_bitmap
+
+def test_primitive_force_display_update(monkeypatch):
+    mock_display = model.W_PointersObject(space.w_Point, 4)
+    w_wordbmp = model.W_WordsObject(space.w_Array, 100)
+    mock_display.store(space, 0, w_wordbmp) # bitmap
+    mock_display.store(space, 1, space.wrap_int(32)) # width
+    mock_display.store(space, 2, space.wrap_int(10)) # height
+    mock_display.store(space, 3, space.wrap_int(1))  # depth
+    prim(primitives.BE_DISPLAY, [mock_display])
+
+    class DisplayFlush(Exception):
+        pass
+
+    def flush_to_screen_mock():
+        raise DisplayFlush
+
+    try:
+        monkeypatch.setattr(mock_display.fetch(space, 0), "flush_to_screen", flush_to_screen_mock)
+        with py.test.raises(DisplayFlush):
+            prim(primitives.FORCE_DISPLAY_UPDATE, [mock_display])
+    finally:
+        monkeypatch.undo()
+
+def test_bitblt_copy_bits(monkeypatch):
+    class CallCopyBitsSimulation(Exception):
+        pass
+
+    mock_bitblt = model.W_PointersObject(space.w_Point, 15)
+
+    def perform_mock(w_rcvr, string):
+        if w_rcvr is mock_bitblt and string == "simulateCopyBits":
+            raise CallCopyBitsSimulation
+
+    interp, w_frame, argument_count = mock([mock_bitblt], None)
+
+    try:
+        monkeypatch.setattr(interp, "perform", perform_mock)
+        with py.test.raises(CallCopyBitsSimulation):
+            prim_table[primitives.BITBLT_COPY_BITS](interp, w_frame.as_context_get_shadow(space), argument_count-1)
+    finally:
+        monkeypatch.undo()
+
 # Note:
 #   primitives.NEXT is unimplemented as it is a performance optimization
 #   primitives.NEXT_PUT is unimplemented as it is a performance optimization
@@ -619,4 +693,3 @@
 #   primitives.VALUE_WITH_ARGS is tested in test_interpreter
 #   primitives.OBJECT_AT is tested in test_interpreter
 #   primitives.OBJECT_AT_PUT is tested in test_interpreter
-


More information about the pypy-commit mailing list