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

commits at source.squeak.org commits at source.squeak.org
Mon Mar 13 20:20:24 UTC 2017


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

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

Name: VMMaker.oscog-eem.2148
Author: eem
Time: 13 March 2017, 1:19:30.469259 pm
UUID: 7f6e1475-0975-451e-8d17-b827aa97c1eb
Ancestors: VMMaker.oscog-dtl.2147

Slang:
Fix serious bug with inlining expressions such as
	context := ignoreContext
		ifTrue: [objectMemory nilObject ]
		ifFalse: [self ensureFrameIsMarried: localFP SP: localSP + (numCopiedArg * objectMemory bytesPerOop)].
where the exitVar (context) is lost and ensureFrameIsMarried:SP: is inlined missing the implicit assignment to context in the first ifTrue:.

Fix bug with type inference for #-.  The difference between two unsigned values is signed.

Fix bug with inferring return types of methods that return unsigned typed variables and positive integer constants.  Don't interpret the type of an integer constant as #sqInt if the method also returns an unsigned.  So defer considering the non-negative integer return values unless no other return type information can be found.

VMMaker:
Add a SpurStackSistaVM configuration (in which the above inlining expressions bug was found).  This is not one of the ones under version control.

=============== Diff against VMMaker.oscog-dtl.2147 ===============

Item was changed:
  ----- Method: CCodeGenerator>>harmonizeReturnTypesIn: (in category 'type inference') -----
  harmonizeReturnTypesIn: aSetOfTypes
+ 	"Eliminate signed/unsigned conflicts in aSetOfTypes. Non-negative integers can be either
+ 	 signed or unsigned. Ignore them unless there are no types, in which case default to sqInt."
+ 	| constantIntegers sqs usqs |
+ 	constantIntegers := aSetOfTypes select: [:element| element isInteger].
+ 	aSetOfTypes removeAll: constantIntegers.
+ 	"N.B. Because of LP64 vs LLP64 issues do *not* rename #long to #sqInt or #'unsigned long' to #usqInt"
+ 	#(char short int #'long long' #'unsigned char' #'unsigned short' #'unsigned int' #'unsigned long long')
+ 		with: #(sqInt sqInt sqInt sqLong usqInt usqInt usqInt usqLong)
- 	"Eliminate signed/unsigned conflicts in aSetOfTypes"
- 	| sqs usqs |
- 	#(char short int #'unsigned char' #'unsigned short' #'unsigned int' #'unsigned long')
- 		with: #(sqInt sqInt sqInt #usqInt #usqInt #usqInt #usqInt)
  		do: [:type :replacement|
  			(aSetOfTypes includes: type) ifTrue:
  				[aSetOfTypes remove: type; add: replacement]].
  	sqs := aSetOfTypes select: [:t| t beginsWith: 'sq'].
  	usqs := aSetOfTypes select: [:t| t beginsWith: 'usq'].
  	^(sqs size + usqs size = aSetOfTypes size
  	   and: [sqs notEmpty
  	   and: [sqs allSatisfy: [:t| usqs includes: 'u', t]]])
  		ifTrue: [sqs]
+ 		ifFalse: [(aSetOfTypes isEmpty and: [constantIntegers notEmpty])
+ 					ifTrue: [Set with: #sqInt]
+ 					ifFalse: [aSetOfTypes]]!
- 		ifFalse: [aSetOfTypes]!

Item was changed:
  ----- Method: CCodeGenerator>>typeForArithmetic:in: (in category 'type inference') -----
  typeForArithmetic: sendNode in: aTMethod
  	"Answer the return type for an arithmetic sendThis is so that the inliner can still
  	 inline simple expressions.  Deal with pointer arithmetic, floating point arithmetic
  	 and promotion."
+ 	| rcvrType argType arg promotedType |
- 	| rcvrType argType |
  	rcvrType := self typeFor: sendNode receiver in: aTMethod.
+ 	argType := self typeFor: (arg := sendNode args first) in: aTMethod.
- 	argType := self typeFor: sendNode args first in: aTMethod.
  	"deal with pointer arithmetic"
+ 	((rcvrType notNil and: [rcvrType last == $*]) or: [argType notNil and: [argType last == $*]]) ifTrue:
- 	((rcvrType notNil and: [rcvrType last = $*]) or: [argType notNil and: [argType last = $*]]) ifTrue:
  		[(rcvrType isNil or: [argType isNil]) ifTrue:
  			[^nil].
+ 		 (rcvrType last == $* and: [argType last == $*]) ifTrue:
- 		 (rcvrType last = $* and: [argType last = $*]) ifTrue:
  			[sendNode selector == #- ifTrue:
  				[^#int].
  			 self error: 'invalid pointer arithmetic'].
+ 		 ^rcvrType last == $*
- 		 ^rcvrType last = $*
  			ifTrue: [rcvrType]
  			ifFalse: [argType]].
+ 	promotedType := self promoteArithmeticTypes: rcvrType and: argType.
+ 	"We have to be very careful with subtraction.  The difference between two unsigned types is signed.
+ 	 But we don't want unsigned - constant to be signed.  We almost always want this to stay unsigned."
+ 	^(sendNode selector == #- and: [promotedType first == $u and: [(arg isConstant and: [arg value isInteger]) not]])
+ 		ifTrue: [promotedType allButFirst: ((promotedType beginsWith: 'unsigned') ifTrue: [9] ifFalse: [1])]
+ 		ifFalse: [promotedType]!
- 	^self promoteArithmeticTypes: rcvrType and: argType!

Item was changed:
  ----- Method: TMethod>>addTypesFor:to:in: (in category 'type inference') -----
  addTypesFor: node to: typeSet in: aCodeGen
  	"Add the value types for the node to typeSet.
  	 Answer if any type was derived from an as-yet-untyped method, which allows us to abort
  	 inferReturnTypeFromReturnsIn: if the return type depends on a yet-to-be-typed method."
  	| expr |
  	expr := node.
  	[expr isAssignment or: [expr isStmtList]] whileTrue:
  		[expr isAssignment ifTrue:
  			[expr := expr variable].
  		 expr isStmtList ifTrue:
  			[expr := expr statements last]].
  	expr isSend ifTrue:
  		[(#(ifTrue: ifFalse: ifTrue:ifFalse: ifFalse:ifTrue:) includes: expr selector) ifTrue:
  			[^expr args
  				inject: false
  				into: [:asYetUntyped :block|
  					asYetUntyped | (self addTypesFor: block to: typeSet in: aCodeGen)]].
  		(aCodeGen returnTypeForSend: expr in: self ifNil: nil)
  			ifNil: [^(aCodeGen methodNamed: expr selector) notNil and: [expr selector ~~ selector]]
  			ifNotNil:
  				[:type |
  				typeSet add: type.
  				^false].].
  	expr isVariable ifTrue:
  		[(aCodeGen typeOfVariable: expr name)
  			ifNotNil: [:type| typeSet add: type]
  			ifNil: [typeSet add: (expr name = 'self'
  										ifTrue: [#void]
  										ifFalse: [#sqInt])]].
  	expr isConstant ifTrue:
+ 		[(expr value isInteger and: [expr value >= 0]) "cannot determine if signed or unsigned yet..."
+ 			ifTrue: [typeSet add: expr value]
+ 			ifFalse:
+ 				[(expr typeOrNilFrom: aCodeGen in: self) ifNotNil:
+ 					[:type | typeSet add: type]]].
- 		[(expr typeOrNilFrom: aCodeGen in: self) ifNotNil:
- 			[:type | typeSet add: type]]..
  	^false!

Item was changed:
  ----- Method: TMethod>>inferTypesForImplicitlyTypedVariablesIn: (in category 'type inference') -----
  inferTypesForImplicitlyTypedVariablesIn: aCodeGen
  	"infer types for untyped variables from assignments and arithmetic uses.
  	 For debugging answer a Dictionary from var to the nodes that determined types
  	 This for debugging:
  		(self copy inferTypesForImplicitlyTypedVariablesIn: aCodeGen)"
+ 	| alreadyExplicitlyTypedOrNotToBeTyped asYetUntyped effectiveNodes |
- 	| alreadyExplicitlyTypedOrNotToBeTyped effectiveNodes |
  	aCodeGen maybeBreakForTestToInline: selector in: self.
  	alreadyExplicitlyTypedOrNotToBeTyped := declarations keys asSet.
+ 	asYetUntyped := locals copyWithoutAll: alreadyExplicitlyTypedOrNotToBeTyped.
  	effectiveNodes := Dictionary new. "this for debugging"
  	parseTree nodesDo:
  		[:node| | type var |
  		"If there is something of the form i >= 0, then i should be signed, not unsigned."
  		(node isSend
  		 and: [(locals includes: (var := node receiver variableNameOrNil))
  		 and: [(alreadyExplicitlyTypedOrNotToBeTyped includes: var) not "don't be fooled by inferred unsigned types"
  		 and: [(#(<= < >= >) includes: node selector)
  		 and: [node args first isConstant
  		 and: [node args first value = 0
  		 and: [(type := self typeFor: var in: aCodeGen) notNil
  		 and: [type first == $u]]]]]]]) ifTrue:
  			[self declarationAt: var put: (aCodeGen signedTypeForIntegralType: type), ' ', var.
  			 effectiveNodes at: var put: { declarations at: var. node }].
  		"if an assignment to an untyped local of a known type, set the local's type to that type.
  		 Only observe known sends (methods in the current set) and typed local variables."
  		(node isAssignment
  		 and: [(locals includes: (var := node variable name))
  		 and: [(alreadyExplicitlyTypedOrNotToBeTyped includes: var) not]]) ifTrue: "don't be fooled by previously inferred types"
  		 	[type := node expression isSend
  						ifTrue: [aCodeGen returnTypeForSend: node expression in: self ifNil: nil]
  						ifFalse: [self typeFor: node expression in: aCodeGen].
  			 type "If untyped, then cannot type the variable yet. A subsequent assignment may assign a subtype of what this type ends up being"
  				ifNil: [alreadyExplicitlyTypedOrNotToBeTyped add: var] 
+ 				ifNotNil: "Merge simple types (but *don't* merge untyped vars); complex types must be defined by the programmer."
- 				ifNotNil: "Merge simple types; complex types must be defined by the programmer."
  					[(aCodeGen isSimpleType: type) ifTrue:
+ 						[(asYetUntyped includes: var)
+ 							ifTrue: [declarations at: var put: type, ' ', var. asYetUntyped remove: var]
+ 							ifFalse:
+ 								[aCodeGen mergeTypeOf: var in: declarations with: type method: self].
- 						[aCodeGen mergeTypeOf: var in: declarations with: type method: self.
  						 effectiveNodes at: var put: { declarations at: var. node }, (effectiveNodes at: var ifAbsent: [#()])]]]].
  	^effectiveNodes!

Item was changed:
  ----- Method: TMethod>>tryToInlineMethodStatementsIn:statementListsInto: (in category 'inlining') -----
  tryToInlineMethodStatementsIn: aCodeGen statementListsInto: aBlock
  	"Expand any (complete) inline methods sent by this method as top-level statements.
  	 Answer if anything was inlined."
  
  	| stmtLists didSomething newStatements returningNodes |
  	didSomething := false.
  	returningNodes := Set new.
+ 	stmtLists := self statementsListsForInliningIn: aCodeGen.
+ 	"stmtLists may include expressions that are used for value but the exitVar is distant because its in an ifTrue:ifTrue:,
+ 	 e.g. in
+ 			context := ignoreContext
+ 							ifTrue: [objectMemory nilObject ]
+ 							ifFalse: [self ensureFrameIsMarried: localFP SP: localSP + (numCopiedArg * objectMemory bytesPerOop)].
+ 	ensureFrameIsMarried:SP: *does* have an exitVar, context, but it is the exitVar for the ifTrue:ifFalse:.  So
+ 	inlineCodeOrNilForStatement:returningNodes:in: should not consider inlining these in its last phrase where exitVar is nil."
  	parseTree nodesDo:
  		[:node|
  		node isReturn ifTrue:
  			[returningNodes add: node expression.
  			 node expression isConditionalSend ifTrue:
+ 				[returningNodes addAll: (node expression args collect: [:stmtList| stmtList statements last])]].
+ 		node isAssignment ifTrue:
+ 			[node expression nodesDo:
+ 				[:assignmentSubNode|
+ 				(stmtLists includes: assignmentSubNode) ifTrue:
+ 					[stmtLists remove: assignmentSubNode]]]].
+ 	
- 				[returningNodes addAll: (node expression args collect: [:stmtList| stmtList statements last])]]].
- 	stmtLists := self statementsListsForInliningIn: aCodeGen.
  	stmtLists do:
  		[:stmtList|
  		newStatements := OrderedCollection new: stmtList statements size.
  		stmtList statements do:
  			[:stmt|
  			(self inlineCodeOrNilForStatement: stmt returningNodes: returningNodes in: aCodeGen)
  				ifNil: [newStatements addLast: stmt]
  				ifNotNil: [:inlinedStmts|
  					didSomething := true.
  					newStatements addAllLast: inlinedStmts]].
  		stmtList setStatements: newStatements asArray].
  
  	"This is a hack; forgive me. The inlining above tends to keep return statements in statement lists.
  	 In the case of returning ifs we don't want the returns in case the returning if is generated as an expression."
  	returningNodes do:
  		[:returningNode|
  		 (returningNode isConditionalSend
  		  and: [returningNode args anySatisfy: [:alternativeNode| alternativeNode endsWithReturn]]) ifTrue:
  			[returningNode args withIndexDo:
  				[:alternativeNode :index|
  				 alternativeNode endsWithReturn ifTrue:
  					[returningNode args at: index put: alternativeNode copyWithoutReturn]]]].
  
  	aBlock value: stmtLists.
  
  	^didSomething!

Item was added:
+ ----- Method: VMMaker class>>generateSqueakSpurStackSistaVM (in category 'configurations') -----
+ generateSqueakSpurStackSistaVM
+ 	"No primitives since we can use those for the Cog VM"
+ 	^VMMaker
+ 		generate: StackInterpreter
+ 		with: #(SistaVM true
+ 				ObjectMemory Spur32BitMemoryManager
+ 				FailImbalancedPrimitives false
+ 				MULTIPLEBYTECODESETS true
+ 				bytecodeTableInitializer initializeBytecodeTableForSqueakV3PlusClosuresSistaV1Hybrid)
+ 		to: (FileDirectory default pathFromURI: self sourceTree, '/spursistastacksrc')
+ 		platformDir: (FileDirectory default pathFromURI: self sourceTree, '/platforms')
+ 		including:#()!



More information about the Vm-dev mailing list