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

commits at source.squeak.org commits at source.squeak.org
Mon Mar 30 14:16:35 UTC 2015


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

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

Name: VMMaker-tfel.360
Author: tfel
Time: 30 March 2015, 4:15:59.572 pm
UUID: 490a4aa1-e8dd-d541-85dc-4d1bde376a8c
Ancestors: VMMaker-dtl.359, VMMaker-tfel.359

Merge simulation fixes and optimizations for Balloon and BitBlt. Relevant changes only the simulation classes, the generated code should be unaffected.

=============== Diff against VMMaker-dtl.359 ===============

Item was added:
+ ----- Method: BalloonEngine>>simulateBalloonPrimitive:args: (in category '*VMMaker-InterpreterSimulation') -----
+ simulateBalloonPrimitive: aString args: args
+ 	^ Smalltalk at: #BalloonEngineSimulation ifPresent: [:be |
+ 			be simulatePrimitive: aString receiver: self args: args]!

Item was added:
+ ----- Method: BalloonEngineSimulation class>>simulatePrimitive:receiver:args: (in category 'simulation') -----
+ simulatePrimitive: aString receiver: rcvr args: args
+ 
+ 	| proxy bb |
+ 	proxy := InterpreterProxy new.
+ 	proxy synthesizeStackFor: rcvr with: args.
+ 	bb := self simulatorClass new.
+ 	bb setInterpreter: proxy.
+ 	bb initialiseModule.
+ 	"rendering state is loaded in the primitive implementations"
+ 	[bb perform: aString asSymbol] on: Exception do: [:ex |
+ 		proxy success: false].
+ 	^ 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.
- 		self cCode: '' inSmalltalk:
- 			[self assert: cmLookupTable unitSize = 4].
  	] 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 changed:
  BitBltSimulation subclass: #BitBltSimulator
  	instanceVariableNames: ''
  	classVariableNames: ''
  	poolDictionaries: ''
  	category: 'VMMaker-InterpreterSimulation'!
+ BitBltSimulator class
+ 	instanceVariableNames: 'opTable maskTable warpBitShiftTable ditherMatrix4x4 ditherThresholds16 ditherValues16 dither8Lookup isInitialised'!
  
  !BitBltSimulator commentStamp: 'tpr 5/5/2003 12:22' prior: 0!
  Provide bitblt support for the vm simulator!
+ BitBltSimulator class
+ 	instanceVariableNames: 'opTable maskTable warpBitShiftTable ditherMatrix4x4 ditherThresholds16 ditherValues16 dither8Lookup isInitialised'!

Item was added:
+ ----- Method: BitBltSimulator class>>dither8Lookup (in category 'accessing') -----
+ dither8Lookup
+ 
+ 	^ dither8Lookup!

Item was added:
+ ----- Method: BitBltSimulator class>>ditherMatrix4x4 (in category 'accessing') -----
+ ditherMatrix4x4
+ 
+ 	^ ditherMatrix4x4!

Item was added:
+ ----- Method: BitBltSimulator class>>ditherThresholds16 (in category 'accessing') -----
+ ditherThresholds16
+ 
+ 	^ ditherThresholds16!

Item was added:
+ ----- Method: BitBltSimulator class>>ditherValues16 (in category 'accessing') -----
+ ditherValues16
+ 
+ 	^ ditherValues16!

Item was added:
+ ----- Method: BitBltSimulator class>>initialize (in category 'class initialization') -----
+ initialize
+ 	"self initialize"
+ 	super initialize.
+ 	isInitialised := false.
+ !

Item was added:
+ ----- Method: BitBltSimulator class>>isInitialised (in category 'accessing') -----
+ isInitialised
+ 
+ 	^ isInitialised!

Item was added:
+ ----- Method: BitBltSimulator class>>maskTable (in category 'accessing') -----
+ maskTable
+ 
+ 	^ maskTable!

Item was added:
+ ----- Method: BitBltSimulator class>>setInitialised (in category 'accessing') -----
+ setInitialised
+ 
+ 	isInitialised := true.!

Item was added:
+ ----- Method: BitBltSimulator class>>warpBitShiftTable (in category 'accessing') -----
+ warpBitShiftTable
+ 
+ 	^ warpBitShiftTable!

Item was added:
+ ----- Method: BitBltSimulator>>halftoneAt: (in category 'simulation') -----
+ halftoneAt: idx
+ 
+ 	^ (halftoneBase + (idx \\ halftoneHeight * 4)) long32At: 0!

Item was added:
+ ----- Method: BitBltSimulator>>initialiseModule (in category 'initialize-release') -----
+ initialiseModule
+ 
+ 	self class isInitialised ifFalse: [| ivars |
+ 		ivars := #(opTable maskTable warpBitShiftTable ditherMatrix4x4 ditherThresholds16 ditherValues16 dither8Lookup).
+ 		super initialiseModule.
+ 		ivars do: [:symbol | self class instVarNamed: symbol put: (self instVarNamed: symbol)].
+ 		self class setInitialised].
+ 	opTable := self class opTable.
+ 	maskTable := self class maskTable.
+ 	warpBitShiftTable := self class warpBitShiftTable.
+ 	ditherMatrix4x4 := self class ditherMatrix4x4.
+ 	ditherThresholds16 := self class ditherThresholds16.
+ 	ditherValues16 := self class ditherValues16.
+ 	dither8Lookup := self class dither8Lookup.
+ !

Item was changed:
  ----- Method: BitBltSimulator>>initializeDitherTables (in category 'simulation') -----
  initializeDitherTables
  	ditherMatrix4x4 := CArrayAccessor on:
  		#(	0	8	2	10
  			12	4	14	6
  			3	11	1	9
  			15	7	13	5).
  	ditherThresholds16 := CArrayAccessor on:#(0 2 4 6 8 10 12 14 16).
  	ditherValues16 := CArrayAccessor on: 
  		#(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).
+ 	dither8Lookup := CArrayAccessor on: (Array new: 4096).!
- 	dither8Lookup := CArrayAccessor on: (Array new: 4096).
- 	self initDither8Lookup.!

Item was added:
+ ----- Method: InterpreterProxy>>synthesizeStackFor:with: (in category 'initialize') -----
+ synthesizeStackFor: receiver with: args
+ 	<doNotGenerate>
+ 	self push: receiver.
+ 	argumentCount := args size.
+ 	1 to: argumentCount do: [:i | self push: (args at: i)].!



More information about the Vm-dev mailing list