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

commits at source.squeak.org commits at source.squeak.org
Wed Jun 6 16:34:53 UTC 2018


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

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

Name: VMMaker.oscog-eem.2403
Author: eem
Time: 6 June 2018, 9:33:56.162374 am
UUID: bf983b6e-5c95-423d-96aa-1324f824974c
Ancestors: VMMaker.oscog-eem.2402

BitBltPlugin: Move the checks for the dest and source forms being sufficiently large pointer objects into their respective validation routines.

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

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.
  	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 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>>loadBitBltFrom:warping: (in category 'interpreter interface') -----
  loadBitBltFrom: bbObj warping: aBool
  	"Load context from BitBlt instance.  Return false if anything is amiss"
  	"NOTE this should all be changed to minX/maxX coordinates for simpler clipping
  		-- once it works!!"
  	| ok |
  	<inline: false>
  	bitBltOop := bbObj.
  	isWarping := aBool.
  	bitBltIsReceiver := bbObj = (interpreterProxy stackValue: interpreterProxy methodArgumentCount).
  	numGCsOnInvocation := interpreterProxy statNumGCs.
  	combinationRule := interpreterProxy fetchInteger: BBRuleIndex ofObject: bitBltOop.
  	(interpreterProxy failed
  		or: [combinationRule < 0 or: [combinationRule > (OpTableSize - 2)]])
  		 ifTrue: [^false  "operation out of range"].
  	(combinationRule >= 16 and: [combinationRule <= 17])
  		 ifTrue: [^false  "fail for old simulated paint, erase modes"].
  	sourceForm := interpreterProxy fetchPointer: BBSourceFormIndex ofObject: bitBltOop.
  	noSource := self ignoreSourceOrHalftone: sourceForm.
  	halftoneForm := interpreterProxy fetchPointer: BBHalftoneFormIndex ofObject: bitBltOop.
  	noHalftone := self ignoreSourceOrHalftone: halftoneForm.
  
  	destForm := interpreterProxy fetchPointer: BBDestFormIndex ofObject: bbObj.
- 	((interpreterProxy isPointers: destForm) and: [(interpreterProxy slotSizeOf: destForm) >= 4])
- 		ifFalse: [^false].
  	ok := self loadBitBltDestForm.
  	ok ifFalse:[^false].
  
  	destX := self fetchIntOrFloat: BBDestXIndex ofObject: bitBltOop ifNil: 0.
  	destY := self fetchIntOrFloat: BBDestYIndex ofObject: bitBltOop ifNil: 0.
  	width := self fetchIntOrFloat: BBWidthIndex ofObject: bitBltOop ifNil: destWidth.
  	height := self fetchIntOrFloat: BBHeightIndex ofObject: bitBltOop ifNil: destHeight.
  	interpreterProxy failed ifTrue: [^false].
  
  	noSource
  		ifTrue:
  			[sourceX := sourceY := 0]
  		ifFalse: 
+ 			[ok := self loadBitBltSourceForm.
- 			[((interpreterProxy isPointers: sourceForm) and: [(interpreterProxy slotSizeOf: sourceForm) >= 4])
- 				ifFalse: [^false].
- 			ok := self loadBitBltSourceForm.
  			ok ifFalse:[^false].
  			ok := self loadColorMap.
  			ok ifFalse:[^false].
  			"Need the implicit setup here in case of 16<->32 bit conversions"
  			(cmFlags bitAnd: ColorMapNewStyle) = 0 ifTrue:[self setupColorMasks].
  			sourceX := self fetchIntOrFloat: BBSourceXIndex ofObject: bitBltOop ifNil: 0.
  			sourceY := self fetchIntOrFloat: BBSourceYIndex ofObject: bitBltOop ifNil: 0].
  
  	ok := self loadHalftoneForm.
  	ok ifFalse:[^false].
  	clipX := self fetchIntOrFloat: BBClipXIndex ofObject: bitBltOop ifNil: 0.
  	clipY := self fetchIntOrFloat: BBClipYIndex ofObject: bitBltOop ifNil: 0.
  	clipWidth := self fetchIntOrFloat: BBClipWidthIndex ofObject: bitBltOop ifNil: destWidth.
  	clipHeight := self fetchIntOrFloat: BBClipHeightIndex ofObject: bitBltOop ifNil: destHeight.
  	interpreterProxy failed ifTrue: [^ false  "non-integer value"].
  	clipX < 0 ifTrue: [clipWidth := clipWidth + clipX.  clipX := 0].
  	clipY < 0 ifTrue: [clipHeight := clipHeight + clipY.  clipY := 0].
  	clipX+clipWidth > destWidth ifTrue: [clipWidth := destWidth - clipX].
  	clipY+clipHeight > destHeight ifTrue: [clipHeight := destHeight - clipY].
  	numGCsOnInvocation ~= interpreterProxy statNumGCs ifTrue: "querySurface could be a callback in loadSourceFor: and loadDestForm:"
  		[interpreterProxy primitiveFailFor: PrimErrObjectMoved.
  		 ^false].
  	^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.
  	sourceDepth < 0 ifTrue:
  		[sourceDepth := 0 - sourceDepth].
+ 	"Ignore an integer bits handle for Display in which case
- 	"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 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!



More information about the Vm-dev mailing list