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

commits at source.squeak.org commits at source.squeak.org
Tue Nov 8 23:16:57 UTC 2022


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

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

Name: VMMaker.oscog-eem.3270
Author: eem
Time: 8 November 2022, 3:16:38.381899 pm
UUID: 2ed5e56f-f39f-4da9-9403-c83acc745010
Ancestors: VMMaker.oscog-eem.3269

Write ClipboardExtendedPlugin>>ioHasClipboardData:inFormat: in a supported form.

Do a better job eliminating redundant failed checks in SmartSyntaxInterpreterPlugin methods.

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

Item was changed:
  ----- Method: ClipboardExtendedPlugin>>ioHasClipboardData:inFormat: (in category 'io') -----
  ioHasClipboardData: clipboard inFormat: format
  	self primitive: 'ioHasClipboardDataInFormat' parameters: #(Unsigned Oop).
  	(interpreterProxy isIntegerObject: format) ifTrue:
+ 		[^(self
- 		[^interpreterProxy methodReturnBool:
- 			(self
  				sqPasteboard: clipboard asVoidPointer
+ 				hasDataInFormat: (interpreterProxy integerValueOf: format)) asBooleanObj].
- 				hasDataInFormat: (interpreterProxy integerValueOf: format))].
  	(interpreterProxy isBytes: format) ifTrue:
+ 		[^(self
- 		[^interpreterProxy methodReturnBool:
- 			(self
  				sqPasteboard: clipboard asVoidPointer
  				hasDataInFormat: (interpreterProxy firstIndexableField: format)
+ 				formatLength: (interpreterProxy byteSizeOf: format)) asBooleanObj].
- 				formatLength: (interpreterProxy byteSizeOf: format))].
  	interpreterProxy primitiveFailFor: PrimErrBadArgument!

Item was removed:
- ----- Method: SmartSyntaxPluginTMethod>>fixUpReturnOneStmt:on: (in category 'transforming') -----
- fixUpReturnOneStmt: stmt on: sStream
- 	| expr exprRetStmts "p t" |
- 	stmt isReturn ifFalse: [^sStream nextPut: stmt].
- 	expr := stmt expression.
- 	(expr isSend
- 	 and: [self resultSendAlwaysFails: expr]) ifTrue:
- 		["failure returns"
- 		 returnType = #sqInt
- 			ifTrue: [sStream nextPut: (TReturnNode new setExpression: expr)]
- 			ifFalse: [sStream nextPut: expr; nextPut: self nullReturnExpr].
- 		 ^nil].
- 	(expr isVariable and: ['nil' = expr name]) ifTrue:
- 		["^ nil -- this is never right unless automatically generated"
- 		 sStream nextPut: stmt.
- 		 ^nil].
- 	(expr isVariable and: ['self' = expr name]) ifTrue:
- 		["^ self"
- 		 fullArgs isEmpty ifFalse:
- 			[sStream nextPut: (self statementGuardedWithSuccess: (self popExpr: fullArgs size))].
- 		 sStream nextPut: self nullReturnExpr.
- 		 ^nil].
- 	(expr isVariable or: [expr isConstant]) ifTrue:
- 		["^ variable or ^ constant without guardchecking"
- 		sStream
- 			nextPut: (sStream isEmpty "No statements to cause failure, therefore no need for failure guard."
- 						ifTrue:
- 							[self pop: fullArgs size + 1 thenReturnExpr: expr]
- 						ifFalse:
- 							[self statementGuardedWithSuccess:
- 								(self pop: fullArgs size + 1 thenReturnExpr: expr)]);
- 			nextPut: self nullReturnExpr.
- 		 ^nil].
- 	"^ expr with necessary guard checking"
- 	"p := sStream position."
- 	exprRetStmts := Array streamContents:
- 		[:ersStream|
- 		 (self resultExpressionCanFail: expr)
- 			ifTrue:
- 				["t := 1."
- 				ersStream
- 					nextPut: (self assign: (self oopVariable: '_return_value') expression: expr);
- 					nextPut: (self statementGuardedWithSuccess: (self pop: fullArgs size + 1
- 																		thenReturnExpr: (self oopVariable: '_return_value')))]
- 			ifFalse:
- 				["t := 2."
- 				 ersStream nextPut: (self pop: fullArgs size + 1 thenReturnExpr: expr)]].
- 		sStream isEmpty "No statements to cause failure, therefore no need for an initial failure guard."
- 			ifTrue: [sStream nextPutAll: exprRetStmts]
- 			ifFalse:
- 				["t := t + 2."
- 				 sStream nextPut: (self statementGuardedWithSuccess: exprRetStmts)].
- 	sStream nextPut: self nullReturnExpr.
- 	"Them := Dictionary new"
- 	"(Them at: t ifAbsentPut: [Dictionary new])
- 		at: self selector
- 		put: (sStream originalContents copyFrom: p + 1 to: sStream position)"!

Item was added:
+ ----- Method: SmartSyntaxPluginTMethod>>fixUpReturnOneStmt:previous:on: (in category 'transforming') -----
+ fixUpReturnOneStmt: stmt previous: previousStmtOrNil on: sStream
+ 	| expr exprRetStmts "p t" |
+ 	stmt isReturn ifFalse: [^sStream nextPut: stmt].
+ 	expr := stmt expression.
+ 	(self resultExpressionAlwaysFails: expr) ifTrue:
+ 		["failure returns"
+ 		 returnType = #sqInt
+ 			ifTrue: [sStream nextPut: (TReturnNode new setExpression: expr)]
+ 			ifFalse: [sStream nextPut: expr; nextPut: self nullReturnExpr].
+ 		 ^nil].
+ 	(expr isVariable and: ['nil' = expr name]) ifTrue:
+ 		["^ nil -- this is never right unless automatically generated"
+ 		 sStream nextPut: stmt.
+ 		 ^nil].
+ 	(expr isVariable and: ['self' = expr name]) ifTrue:
+ 		["^ self"
+ 		 (previousStmtOrNil notNil
+ 		  and: [self resultExpressionAlwaysFails: previousStmtOrNil]) ifFalse:
+ 			 [fullArgs isEmpty ifFalse:
+ 				[sStream nextPut: (self statementGuardedWithSuccess: (self popExpr: fullArgs size))]].
+ 		 sStream nextPut: self nullReturnExpr.
+ 		 ^nil].
+ 	(expr isVariable or: [expr isConstant]) ifTrue:
+ 		["^ variable or ^ constant without guardchecking"
+ 		sStream
+ 			nextPut: (sStream isEmpty "No statements to cause failure, therefore no need for failure guard."
+ 						ifTrue:
+ 							[self pop: fullArgs size + 1 thenReturnExpr: expr]
+ 						ifFalse:
+ 							[self statementGuardedWithSuccess:
+ 								(self pop: fullArgs size + 1 thenReturnExpr: expr)]);
+ 			nextPut: self nullReturnExpr.
+ 		 ^nil].
+ 	"^ expr with necessary guard checking"
+ 	"p := sStream position."
+ 	exprRetStmts := Array streamContents:
+ 		[:ersStream|
+ 		 (self resultExpressionCanFail: expr)
+ 			ifTrue:
+ 				["t := 1."
+ 				ersStream
+ 					nextPut: (self assign: (self oopVariable: '_return_value') expression: expr);
+ 					nextPut: (self statementGuardedWithSuccess: (self pop: fullArgs size + 1
+ 																		thenReturnExpr: (self oopVariable: '_return_value')))]
+ 			ifFalse:
+ 				["t := 2."
+ 				 ersStream nextPut: (self pop: fullArgs size + 1 thenReturnExpr: expr)]].
+ 		sStream isEmpty "No statements to cause failure, therefore no need for an initial failure guard."
+ 			ifTrue: [sStream nextPutAll: exprRetStmts]
+ 			ifFalse:
+ 				["t := t + 2."
+ 				 sStream nextPut: (self statementGuardedWithSuccess: exprRetStmts)].
+ 	sStream nextPut: self nullReturnExpr.
+ 	"Them := Dictionary new"
+ 	"(Them at: t ifAbsentPut: [Dictionary new])
+ 		at: self selector
+ 		put: (sStream originalContents copyFrom: p + 1 to: sStream position)"!

Item was changed:
  ----- Method: SmartSyntaxPluginTMethod>>fixUpReturns (in category 'transforming') -----
  fixUpReturns
  	"Replace each return statement in this method with (a) the given postlog, (b) code to pop the receiver and the given number of arguments, and (c) code to push the integer result and return."
  	self endsWithMethodReturnExpression ifTrue:
  		[parseTree statements last isSend ifFalse:
  			[parseTree setStatements: parseTree statements allButLast]].
  	parseTree nodesDo:
  		[:node |
  		node isStmtList ifTrue:
  			[node setStatements: (Array streamContents:
+ 				[:sStream | | prevStmt |
- 				[:sStream |
  				 node statements do: 
+ 					[:stmt |
+ 					 self fixUpReturnOneStmt: stmt previous: prevStmt on: sStream.
+ 					 prevStmt := stmt]])]]!
- 					[:stmt | self fixUpReturnOneStmt: stmt on: sStream]])]]!

Item was added:
+ ----- Method: SmartSyntaxPluginTMethod>>resultExpressionAlwaysFails: (in category 'private') -----
+ resultExpressionAlwaysFails: aTParseNode
+ 	^aTParseNode isSend
+ 	  and: [(#(primitiveFail primitiveFailFor: primitiveFailForFFIException:at: primitiveFailForOSError:) includes: aTParseNode selector)
+ 			or: [aTParseNode selector == #success:
+ 				 and: [aTParseNode args first isConstant
+ 				 and: [aTParseNode args first value == false]]]]!

Item was changed:
  ----- Method: SmartSyntaxPluginTMethod>>resultExpressionCanFail: (in category 'private') -----
+ resultExpressionCanFail: aTParseNode
- resultExpressionCanFail: aTSendNode
  	"Neither asSmallIntegerObj nor asBooleanObj nor asPositiveIntegerObj can fail.
  	 asPositiveIntegerObj maps to positive32BitIntegerFor: which uses
  	 eeInstantiateSmallClassIndex:format:numSlots: which does not GC and does not fail."
+ 	aTParseNode isSend ifFalse:
+ 		[^true].
+ 	(#(asSmallIntegerObj asPositiveIntegerObj asBooleanObj nilObject trueObject falseObject) includes: aTParseNode selector) ifTrue:
+ 		[^false].
+ 	(aTParseNode selector == #asOop:
+ 	and: [aTParseNode args first isVariable
+ 	and: [#('SmallInteger' 'Boolean') includes: aTParseNode args first  name]]) ifTrue:
+ 		[^false].
+ 	^true!
- 	^(#(asSmallIntegerObj asPositiveIntegerObj asBooleanObj nilObject trueObject falseObject) includes: aTSendNode selector) not!

Item was removed:
- ----- Method: SmartSyntaxPluginTMethod>>resultSendAlwaysFails: (in category 'private') -----
- resultSendAlwaysFails: aTSendNode
- 	^(#(primitiveFail primitiveFailFor: primitiveFailForFFIException:at: primitiveFailForOSError:) includes: aTSendNode selector)
- 		or: [aTSendNode selector == #success:
- 			 and: [aTSendNode args first isConstant
- 			 and: [aTSendNode args first value == false]]]!



More information about the Vm-dev mailing list