[Vm-dev] VM Maker: VMMaker-tfel.376.mcz

commits at source.squeak.org commits at source.squeak.org
Wed Feb 17 17:00:18 UTC 2016


Tim Felgentreff uploaded a new version of VMMaker to project VM Maker:
http://source.squeak.org/VMMaker/VMMaker-tfel.376.mcz

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

Name: VMMaker-tfel.376
Author: tfel
Time: 17 February 2016, 5:59:52.238339 pm
UUID: d69f8375-f4ff-497a-ad92-43a856afa1c1
Ancestors: VMMaker-dtl.375

Merge relevant Simulation changes from oscog

VMMaker.oscog-tfel.1683
  - Move BitBlt simulation methods into VMMaker, they can only be used if VMMaker is loaded, anyway, and they do not have any senders (besides a duplicated test that is also in VMMaker)
  - Avoid ENABLE_FAST_BLT binding lookup in BitBltSimulator, because that is not simulatable code

VMMaker.oscog-tfel.1682
  - fix BitBlt simulation to go through primitiveCopyBits primitive.

VMMaker.oscog-tfel.1677
  - Fix BitBltSimulation (for RSqueak on Spur)

=============== Diff against VMMaker-dtl.375 ===============

Item was added:
+ ----- Method: BitBlt>>copyBitsSimulated (in category '*VMMaker-Interpreter') -----
+ copyBitsSimulated
+ 	^ BitBltSimulation copyBitsFrom: self!

Item was added:
+ ----- Method: BitBlt>>copyBitsSimulated: (in category '*VMMaker-Interpreter') -----
+ copyBitsSimulated: alpha
+ 	^ BitBltSimulation copyBitsFrom: self!

Item was changed:
  ----- Method: BitBlt>>simulatePrimitive:args: (in category '*VMMaker-Interpreter') -----
  simulatePrimitive: aString args: args 
  	"simulate primitives in RSqueak"
  	aString = 'primitiveCopyBits'
+ 		ifTrue: [
+ 			args size = 1
+ 				ifTrue: [^ self copyBitsSimulated: (args at: 1)]
+ 				ifFalse: [^ self copyBitsSimulated]].
- 		ifTrue: [^ self copyBitsSimulated].
  	aString = 'primitiveWarpBits'
  		ifTrue: [^ self
  				warpBitsSimulated: (args at: 1)
  				sourceMap: (args at: 2)].
  	^ InterpreterProxy new primitiveFailFor: 255
  !

Item was changed:
  ----- Method: BitBltSimulation class>>copyBitsFrom: (in category 'system simulation') -----
  copyBitsFrom: aBitBlt
  	"Simulate the copyBits primitive"
  	| proxy bb |
  	proxy := InterpreterProxy new.
  	proxy loadStackFrom: thisContext sender home.
  	bb := self simulatorClass new.
  	bb initialiseModule.
  	bb setInterpreter: proxy.
  	proxy success: (bb loadBitBltFrom: aBitBlt).
+ 	bb primitiveCopyBits.
+ 	^ proxy stackValue: 0!
- 	bb copyBits.
- 	proxy failed ifFalse:[
- 		proxy showDisplayBits: aBitBlt destForm Left: bb affectedLeft Top: bb affectedTop Right: bb affectedRight Bottom: bb affectedBottom].
- 	^proxy stackValue: 0!

Item was changed:
  ----- Method: BitBltSimulation>>loadColorMap (in category 'interpreter interface') -----
  loadColorMap
  	"ColorMap, if not nil, must be longWords, and 
  	2^N long, where N = sourceDepth for 1, 2, 4, 8 bits, 
  	or N = 9, 12, or 15 (3, 4, 5 bits per color) for 16 or 32 bits."
  	| cmSize oldStyle oop cmOop |
  	<inline: true>
  	cmFlags := cmMask := cmBitsPerColor := 0.
  	cmShiftTable := nil.
  	cmMaskTable := nil.
  	cmLookupTable := nil.
  	cmOop := interpreterProxy fetchPointer: BBColorMapIndex ofObject: bitBltOop.
  	cmOop = interpreterProxy nilObject ifTrue:[^true].
  	cmFlags := ColorMapPresent. "even if identity or somesuch - may be cleared later"
  	oldStyle := false.
  	(interpreterProxy isWords: cmOop) ifTrue:[
  		"This is an old-style color map (indexed only, with implicit RGBA conversion)"
  		cmSize := interpreterProxy slotSizeOf: cmOop.
  		cmLookupTable := interpreterProxy firstIndexableField: cmOop.
  		oldStyle := true.
  	] ifFalse: [
  		"A new-style color map (fully qualified)"
  		((interpreterProxy isPointers: cmOop) 
  			and:[(interpreterProxy slotSizeOf: cmOop) >= 3]) ifFalse:[^false].
  		cmShiftTable := self loadColorMapShiftOrMaskFrom:
  			(interpreterProxy fetchPointer: 0 ofObject: cmOop).
  		cmMaskTable := self loadColorMapShiftOrMaskFrom:
  			(interpreterProxy fetchPointer: 1 ofObject: cmOop).
  		oop := interpreterProxy fetchPointer: 2 ofObject: cmOop.
  		oop = interpreterProxy nilObject 
  			ifTrue:[cmSize := 0]
  			ifFalse:[(interpreterProxy isWords: oop) ifFalse:[^false].
  					cmSize := (interpreterProxy slotSizeOf: oop).
  					cmLookupTable := interpreterProxy firstIndexableField: oop].
  		cmFlags := cmFlags bitOr: ColorMapNewStyle.
  		self cCode: '' inSmalltalk:
+ 			[].
- 			[self assert: cmShiftTable unitSize = 4.
- 			 self assert: cmMaskTable unitSize = 4.
- 			 self assert: cmLookupTable unitSize = 4].
  	].
  	(cmSize bitAnd: cmSize - 1) = 0 ifFalse:[^false].
  	cmMask := cmSize - 1.
  	cmBitsPerColor := 0.
  	cmSize = 512 ifTrue: [cmBitsPerColor := 3].
  	cmSize = 4096 ifTrue: [cmBitsPerColor := 4].
  	cmSize = 32768 ifTrue: [cmBitsPerColor := 5].
  	cmSize = 0
  		ifTrue:[cmLookupTable := nil. cmMask := 0]
  		ifFalse:[cmFlags := cmFlags bitOr: ColorMapIndexedPart].
  	oldStyle "needs implicit conversion"
  		ifTrue:[	self setupColorMasks].
  	"Check if colorMap is just identity mapping for RGBA parts"
  	(self isIdentityMap: cmShiftTable with: cmMaskTable)
  		ifTrue:[ cmMaskTable := nil. cmShiftTable := nil ]
  		ifFalse:[ cmFlags := cmFlags bitOr: ColorMapFixedPart].
  	^true!

Item was added:
+ ----- Method: BitBltSimulator>>cppIf:ifTrue:ifFalse: (in category 'translation support') -----
+ cppIf: conditionBlockOrSymbolValue ifTrue: trueExpressionOrBlock ifFalse: falseExpressionOrBlockOrNil
+ 	"The simulator does not have fast blt defines"
+ 	^ conditionBlockOrSymbolValue = #'ENABLE_FAST_BLT'
+ 		ifTrue: falseExpressionOrBlockOrNil
+ 		ifFalse: [super
+ 					cppIf: conditionBlockOrSymbolValue
+ 					ifTrue: trueExpressionOrBlock
+ 					ifFalse: falseExpressionOrBlockOrNil]!

Item was changed:
  TParseNode subclass: #TCaseStmtNode
  	instanceVariableNames: 'expression firsts lasts cases'
  	classVariableNames: ''
  	poolDictionaries: ''
  	category: 'VMMaker-Translation to C'!
+ 
+ !TCaseStmtNode commentStamp: '<historical>' prior: 0!
+ I implement the main dispatch case statements for bytecode and primitive dispatch.  See TMethod classPool associationAt: #CaseStatements!

Item was added:
+ ----- Method: WarpBlt>>warpBitsSimulated (in category '*VMMaker-Interpreter-system simulation') -----
+ warpBitsSimulated
+ 	"Simulate WarpBlt"
+ 
+ 	cellSize < 1 ifTrue: [ ^self error: 'cellSize must be >= 1' ].
+ 
+ 	self warpBitsSimulated: cellSize
+ 		sourceMap: (sourceForm colormapIfNeededForDepth: 32).
+ !

Item was added:
+ ----- Method: WarpBlt>>warpBitsSimulated:sourceMap: (in category '*VMMaker-Interpreter-system simulation') -----
+ warpBitsSimulated: n sourceMap: sourceMap
+ 	"Simulate WarpBlt"
+ 	^ BitBltSimulation warpBitsFrom: self!



More information about the Vm-dev mailing list