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

commits at source.squeak.org commits at source.squeak.org
Wed Jul 19 18:00:57 UTC 2017


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

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

Name: VMMaker.oscog-eem.2255
Author: eem
Time: 19 July 2017, 10:59:59.730933 am
UUID: 496474d7-fcb8-4a80-9e16-19f6b510bcc0
Ancestors: VMMaker.oscog-eem.2254

Rewrite remaining pop:;push: users in primiotives to use pop:thenPush:

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

Item was changed:
  ----- Method: CroquetPlugin>>primitiveOrthoNormInverseMatrix (in category 'transforms') -----
  primitiveOrthoNormInverseMatrix
  	| srcOop dstOop src dst x y z rx ry rz |
  	<export: true>
+ 	<var: #src type: #'float *'>
+ 	<var: #dst type: #'float *'>
+ 	<var: #x type: #double>
+ 	<var: #y type: #double>
+ 	<var: #z type: #double>
+ 	<var: #rx type: #double>
+ 	<var: #ry type: #double>
+ 	<var: #rz type: #double>
- 	<var: #src declareC:'float *src'>
- 	<var: #dst declareC:'float *dst'>
- 	<var: #x declareC:'double x'>
- 	<var: #y declareC:'double y'>
- 	<var: #z declareC:'double z'>
- 	<var: #rx declareC:'double rx'>
- 	<var: #ry declareC:'double ry'>
- 	<var: #rz declareC:'double rz'>
  
  	interpreterProxy methodArgumentCount = 0
  		ifFalse:[^interpreterProxy primitiveFail].
  	srcOop := interpreterProxy stackObjectValue: 0.
  	interpreterProxy failed ifTrue:[^nil].
  	((interpreterProxy isWords: srcOop) and:[(interpreterProxy slotSizeOf: srcOop) = 16])
  		ifFalse:[^interpreterProxy primitiveFail].
  	dstOop := interpreterProxy clone: srcOop.
  	"reload srcOop in case of GC"
  	srcOop := interpreterProxy stackObjectValue: 0.
  	src := interpreterProxy firstIndexableField: srcOop.
  	dst := interpreterProxy firstIndexableField: dstOop.
  
  	"Transpose upper 3x3 matrix"
  	"dst at: 0 put: (src at: 0)."	dst at: 1 put: (src at: 4). 	dst at: 2 put: (src at: 8). 
  	dst at: 4 put: (src at: 1). 	"dst at: 5 put: (src at: 5)."	dst at: 6 put: (src at: 9). 
  	dst at: 8 put: (src at: 2). 	dst at: 9 put: (src at: 6). 	"dst at: 10 put: (src at: 10)."
  
  	"Compute inverse translation vector"
  	x := src at: 3.
  	y := src at: 7.
  	z := src at: 11.
  	rx := (x * (dst at: 0)) + (y * (dst at: 1)) + (z * (dst at: 2)).
  	ry := (x * (dst at: 4)) + (y * (dst at: 5)) + (z * (dst at: 6)).
  	rz := (x * (dst at: 8)) + (y * (dst at: 9)) + (z * (dst at: 10)).
  
+ 	dst at: 3 put: (self cCoerce: 0.0-rx to: #float).
+ 	dst at: 7 put: (self cCoerce: 0.0-ry to: #float).
+ 	dst at: 11 put: (self cCoerce: 0.0-rz to: #float).
- 	dst at: 3 put: (self cCoerce: 0.0-rx to: 'float').
- 	dst at: 7 put: (self cCoerce: 0.0-ry to: 'float').
- 	dst at: 11 put: (self cCoerce: 0.0-rz to: 'float').
  
+ 	interpreterProxy pop: 1 thenPush: dstOop!
- 	interpreterProxy pop: 1.
- 	^interpreterProxy push: dstOop.
- !

Item was changed:
  ----- Method: InterpreterPrimitives>>primitiveGetLogDirectory (in category 'I/O primitives') -----
  primitiveGetLogDirectory
  	"Primitive. Answer the VM's current log directory"
  	| ptr sz stringOop |
  	<var: 'ptr' type: 'char*'>
  	<export: true>
  	ptr := self ioGetLogDirectory.
  	ptr == nil ifTrue:[^self success: false].
  	sz := self strlen: ptr.
  	stringOop := objectMemory instantiateClass: objectMemory classString indexableSize: sz.
  	0 to: sz-1 do:[:i| objectMemory storeByte: i ofObject: stringOop withValue: (ptr at: i)].
+ 	self pop: argumentCount+1 thenPush: stringOop!
- 	self pop: self methodArgumentCount+1.
- 	self push: stringOop.!

Item was changed:
  ----- Method: InterpreterPrimitives>>primitiveGetWindowLabel (in category 'I/O primitives') -----
  primitiveGetWindowLabel
  	"Primitive. Answer the OS window's label"
  	| ptr sz labelOop |
  	<var: 'ptr' type: 'char*'>
  	<export: true>
  	ptr := self ioGetWindowLabel.
  	ptr == nil ifTrue:[^self success: false].
  	sz := self strlen: ptr.
  	labelOop := objectMemory instantiateClass: objectMemory classString indexableSize: sz.
  	0 to: sz-1 do:[:i| objectMemory storeByte: i ofObject: labelOop withValue: (ptr at: i)].
+ 	self pop: argumentCount+1 thenPush: labelOop!
- 	self pop: self methodArgumentCount+1.
- 	self push: labelOop.!

Item was changed:
  ----- Method: InterpreterPrimitives>>primitiveImageName (in category 'other primitives') -----
  primitiveImageName
  	"When called with a single string argument, record the string as the current image file name. When called with zero arguments, return a string containing the current image file name."
  
  	| s sz sCRIfn okToRename |
  	<var: #sCRIfn type: 'void *'>
  	argumentCount = 1 ifTrue: [
  		"If the security plugin can be loaded, use it to check for rename permission.
  		If not, assume it's ok"
  		sCRIfn := self ioLoadFunction: 'secCanRenameImage' From: 'SecurityPlugin'.
  		sCRIfn ~= 0 ifTrue:
  			[okToRename := self cCode: '((sqInt (*)(void))sCRIfn)()'
  								inSmalltalk: [self dispatchMappedPluginEntry: sCRIfn].
  			okToRename ifFalse:
  				[^self primitiveFail]].
  		s := self stackTop.
  		self assertClassOf: s is: (objectMemory splObj: ClassByteString).
  		self successful ifTrue: [
  			sz := self stSizeOf: s.
  			self imageNamePut: (s + objectMemory baseHeaderSize) Length: sz.
  			self pop: 1.  "pop s, leave rcvr on stack"
  		].
  	] ifFalse: [
  		sz := self imageNameSize.
  		s := objectMemory instantiateClass: (objectMemory splObj: ClassByteString) indexableSize: sz.
  		self imageNameGet: (s + objectMemory baseHeaderSize) Length: sz.
+ 		self pop: 1 thenPush: s
- 		self pop: 1.  "rcvr"
- 		self push: s.
  	]!

Item was changed:
  ----- Method: InterpreterPrimitives>>primitiveScanCharacters (in category 'I/O primitives') -----
  primitiveScanCharacters
  	"The character scanner primitive."
  	| kernDelta stops sourceString scanStopIndex scanStartIndex rcvr scanDestX scanLastIndex scanXTable
  	  scanMap maxGlyph ascii stopReason glyphIndex sourceX sourceX2 nextDestX scanRightX nilOop |
  
  	self methodArgumentCount = 6
  		ifFalse: [^ self primitiveFail].
  
  	"Load the receiver and arguments"
  	kernDelta := self stackIntegerValue: 0.
  	stops := self stackValue: 1.
  	scanRightX := self stackIntegerValue: 2.
  	sourceString := self stackValue: 3.
  	scanStopIndex := self stackIntegerValue: 4.
  	scanStartIndex := self stackIntegerValue: 5.
  	rcvr := self stackValue: 6.
  	self successful ifFalse: [^ nil].
  	
  	"check argument type and range and rcvr"
  	((objectMemory isArray: stops)
  	 and: [(objectMemory slotSizeOf: stops) >= 258
  	 and: [(objectMemory isBytes: sourceString)
  	 and: [scanStartIndex > 0
  	 and: [scanStopIndex > 0
  	 and: [scanStopIndex <= (objectMemory byteSizeOf: sourceString)
  	 and: [(objectMemory isPointers: rcvr)
  	 and: [(objectMemory slotSizeOf: rcvr) >= 4]]]]]]])
  		ifFalse: [^ self primitiveFail].
  
  	"Check required rcvr instVars"
  	scanDestX := self fetchInteger: 0 ofObject: rcvr.
  	scanLastIndex := self fetchInteger: 1 ofObject: rcvr.
  	scanXTable := objectMemory fetchPointer: 2 ofObject: rcvr.
  	scanMap := objectMemory fetchPointer: 3 ofObject: rcvr.
  	((objectMemory isArray: scanXTable)
  	 and: [(objectMemory isArray: scanMap)
  	 and: [(objectMemory slotSizeOf: scanMap) = 256
+ 	 and: [self successful "for the fetchInteger:ofObject:'s above"]]]) ifFalse:
- 	 and: [self successful "for the fetchInteger:ofObject:'s abobve"]]]) ifFalse:
  		[^ self primitiveFail].
  	maxGlyph := (objectMemory slotSizeOf: scanXTable) - 2.
  
  	"Okay, here we go. We have eliminated nearly all failure 
  	conditions, to optimize the inner fetches."
  	scanLastIndex := scanStartIndex.
  	nilOop := objectMemory nilObject.
  	[scanLastIndex <= scanStopIndex]
  		whileTrue: [
  			"Known to be okay since scanStartIndex > 0 and scanStopIndex <= sourceString size"
  			ascii := objectMemory fetchByte: scanLastIndex - 1 ofObject: sourceString.
  			"Known to be okay since stops size >= 258"
  			(stopReason := objectMemory fetchPointer: ascii ofObject: stops) = nilOop
  				ifFalse: ["Store everything back and get out of here since some stop conditionn needs to be checked"
  					(objectMemory isIntegerValue: scanDestX) ifFalse: [^ self primitiveFail].
  					self storeInteger: 0 ofObject: rcvr withValue: scanDestX.
  					self storeInteger: 1 ofObject: rcvr withValue: scanLastIndex.
+ 					self pop: 7 "args+rcvr" thenPush: stopReason.
+ 					^nil].
- 					self pop: 7. "args+rcvr"
- 					^ self push: stopReason].
  			"Known to be okay since scanMap size = 256"
  			glyphIndex := self fetchInteger: ascii ofObject: scanMap.
  			"fail if the glyphIndex is out of range"
  			(self failed or: [glyphIndex < 0 	or: [glyphIndex > maxGlyph]]) ifTrue: [^ self primitiveFail].
  			sourceX := self fetchInteger: glyphIndex ofObject: scanXTable.
  			sourceX2 := self fetchInteger: glyphIndex + 1 ofObject: scanXTable.
  			"Above may fail if non-integer entries in scanXTable"
  			self failed ifTrue: [^ nil].
  			nextDestX := scanDestX + sourceX2 - sourceX.
  			nextDestX > scanRightX ifTrue:
  				["Store everything back and get out of here since we got to the right edge"
  				(objectMemory isIntegerValue: scanDestX) ifFalse: [^ self primitiveFail].
  				self storeInteger: 0 ofObject: rcvr withValue: scanDestX.
  				self storeInteger: 1 ofObject: rcvr withValue: scanLastIndex.
  				self pop: 7 "args+rcvr" thenPush: (objectMemory fetchPointer: CrossedX - 1 ofObject: stops).
  				^nil].
  			scanDestX := nextDestX + kernDelta.
  			scanLastIndex := scanLastIndex + 1].
  	(objectMemory isIntegerValue: scanDestX) ifFalse: [^ self primitiveFail].
  	self storeInteger: 0 ofObject: rcvr withValue: scanDestX.
  	self storeInteger: 1 ofObject: rcvr withValue: scanStopIndex.
  	self pop: 7 "args+rcvr" thenPush: (objectMemory fetchPointer: EndOfRun - 1 ofObject: stops)!



More information about the Vm-dev mailing list