[Vm-dev] VM Maker: VMMaker.oscog-nice.1839.mcz

commits at source.squeak.org commits at source.squeak.org
Sun Apr 24 13:00:10 UTC 2016


Nicolas Cellier uploaded a new version of VMMaker to project VM Maker:
http://source.squeak.org/VMMaker/VMMaker.oscog-nice.1839.mcz

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

Name: VMMaker.oscog-nice.1839
Author: nice
Time: 24 April 2016, 2:57:19.464 pm
UUID: 9f8b7677-00f1-4c43-bae8-2ab899cf0de4
Ancestors: VMMaker.oscog-nice.1838

Unify type inference used to #inferReturnTypeFromReturnsIn: with that based on AST.

That means many more type inference for message sends (returnTypeForSend:in:). Ideally any message generated specially thru initializeCTranslationDictionary should have a corresponding entry in returnTypeForSend:in:, because type inference cannot apply to special tricks applied by CCodeGenerator.

There is still possible ambiguity related to different types in different path (if else/ ()?: ). This was the whole point of #addTypesFor:to:in:. IMO we cannot resolve automatically and maybe the best will be to raise a Warning, optionnally ignore it and let expert user manually fix it..

Now that type inference is a bit more thorough, release type restrictions in #isFunctional in order to obtain much more aggressive inlining.

With those, a gain of 10% is possible on the LargeIntegersPlugin dominated bench:
[ArbitraryPrecisionFloatTest suite run] timeToRun.

=============== Diff against VMMaker.oscog-nice.1838 ===============

Item was changed:
  ----- Method: CCodeGenerator>>returnTypeForSend:in: (in category 'type inference') -----
  returnTypeForSend: sendNode in: aTMethod
  	"Answer the return type for a send.  Absent sends default to #sqInt.
+ 	 The inferred type should match as closely as possible the C type of
+ 	 generated expessions so that inlining would not change the expression."
- 	 The bitwise operators answer unsigned versions of their argument types, at least in gcc
- 	 although this author can't find that in the C99 spec.  If you can find this, please let me know."
  	| sel methodOrNil |
  	methodOrNil := self anyMethodNamed: (sel := sendNode selector).
  	(methodOrNil notNil and: [methodOrNil returnType notNil]) ifTrue:
  		[^self baseTypeForType: methodOrNil returnType].
  	^kernelReturnTypes
  		at: sel
  		ifAbsent:
  			[sel
  				caseOf: {
+ 				[#negated]				->	[self promoteArithmeticTypes: (self typeFor: sendNode receiver in: aTMethod) and: #int].
  				[#+]					->	[self typeForArithmetic: sendNode in: aTMethod].
  				[#-]						->	[self typeForArithmetic: sendNode in: aTMethod].
  				[#*]					->	[self typeForArithmetic: sendNode in: aTMethod].
  				[#/]						->	[self typeForArithmetic: sendNode in: aTMethod].
+ 				[#//]					->	[self typeForArithmetic: sendNode in: aTMethod].
+ 				[#\\]					->	[self typeForArithmetic: sendNode in: aTMethod].
+ 				[#>>]					->	[self typeForArithmetic: sendNode in: aTMethod].
+ 				[#<<]					->	[self
+ 												promoteArithmeticTypes: (self unsignedTypeForIntegralType: (self typeFor: sendNode receiver in: aTMethod))
+ 												and: (self typeFor: sendNode args first in: aTMethod)].
+ 				[#rem:]					->	[self typeForArithmetic: sendNode in: aTMethod].
+ 				[#quo:]					->	[self typeForArithmetic: sendNode in: aTMethod].
  				[#addressOf:]			->	[(self typeFor: sendNode receiver in: aTMethod)
  												ifNil: [#sqInt]
  												ifNotNil: [:type| type, (type last isLetter ifTrue: [' *'] ifFalse: ['*'])]].
  				[#at:]					->	[self typeForDereference: sendNode in: aTMethod].
  				[#bitAnd:]				->	[self typeForArithmetic: sendNode in: aTMethod].
  				[#bitOr:]				->	[self typeForArithmetic: sendNode in: aTMethod].
  				[#bitXor:]				->	[self typeForArithmetic: sendNode in: aTMethod].
+ 				[#bitClear:]				->	[self typeForArithmetic: sendNode in: aTMethod].
+ 				[#bitInvert32]			->	[#'unsigned int'].
+ 				[#bitInvert64]			->	[self promoteArithmeticTypes: (self typeFor: sendNode receiver in: aTMethod) and: #int].
+ 				[#byteSwap32]			->	[#'unsigned int'].
+ 				[#byteSwap64]			->	[#'unsigned long long'].
+ 				[#byteSwapped32IfBigEndian:]	->	[#'unsigned int'].
+ 				[#byteSwapped64IfBigEndian:]	->	[#'unsigned long long'].
+ 				[#=]					->	[#int].
+ 				[#~=]					->	[#int].
+ 				[#==]					->	[#int].
+ 				[#~~]					->	[#int].
+ 				[#<]					->	[#int].
+ 				[#<=]					->	[#int].
+ 				[#>]					->	[#int].
+ 				[#>=]					->	[#int].
+ 				[#between:and:]		->	[#int].
+ 				[#anyMask:]				->	[#int].
+ 				[#allMask:]				->	[#int].
+ 				[#noMask:]				->	[#int].
+ 				[#isNil]					->	[#int].
+ 				[#notNil]				->	[#int].
+ 				[#&]					->	[#int].
+ 				[#|]						->	[#int].
+ 				[#not]					->	[#int].
  				[#asFloat]				->	[#double].
  				[#atan]					->	[#double].
  				[#exp]					->	[#double].
  				[#log]					->	[#double].
  				[#sin]					->	[#double].
  				[#sqrt]					->	[#double].
  				[#asLong]				->	[#long].
+ 				[#asInteger]			->	[#sqInt].
  				[#asUnsignedInteger]	->	[#usqInt].
  				[#asUnsignedLong]		->	[#'unsigned long'].
  				[#asVoidPointer]		->	[#'void *'].
  				[#signedIntToLong]		->	[#usqInt]. "c.f. generateSignedIntToLong:on:indent:"
  				[#signedIntToShort]	->	[#usqInt]. "c.f. generateSignedIntToShort:on:indent:"
  				[#cCoerce:to:]			->	[sendNode args last value].
  				[#cCoerceSimple:to:]	->	[sendNode args last value].
+ 				[#sizeof:]				->	[#'unsigned long']. "Technically it's a size_t but it matches unsigned long on target architectures so far..."
  				[#ifTrue:ifFalse:]		->	[self typeForConditional: sendNode in: aTMethod].
  				[#ifFalse:ifTrue:]		->	[self typeForConditional: sendNode in: aTMethod].
  				[#ifTrue:]				->	[self typeForConditional: sendNode in: aTMethod].
  				[#ifFalse:]				->	[self typeForConditional: sendNode in: aTMethod] }
  				otherwise: "If there /is/ a method for sel but its retrn type is as yet unknown we /mustn't/ default it.
  							We can only default unbound selectors."
  					[methodOrNil ifNotNil: [nil] ifNil: [#sqInt]]]!

Item was added:
+ ----- Method: CCodeGenerator>>unsignedTypeForIntegralType: (in category 'type inference') -----
+ unsignedTypeForIntegralType: aCTypeString
+ 	^aCTypeString first = $u
+ 		ifTrue: [aCTypeString]
+ 		ifFalse:
+ 			[(aCTypeString beginsWith: 'sq')
+ 				ifTrue: ['u' , aCTypeString]
+ 				ifFalse: ['unsigned ' , aCTypeString]]!

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.
- 	"Add the value tupes 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)]].
+ 		(expr typeOrNilFrom: aCodeGen in: self)
+ 			ifNil: [^(aCodeGen methodNamed: expr selector) notNil and: [expr selector ~~ selector]]
+ 			ifNotNil:
+ 				[:type |
+ 				typeSet add: type.
+ 				^false].].
- 		 (#(= ~= == ~~ < > <= >= anyMask: allMask: noMask:) includes: expr selector) ifTrue:
- 			[typeSet add: #sqInt. ^false].
- 		 (#(+ - * / // \\ rem: quo: bitAnd: bitClear: bitOr: bitXor: bitShift:) includes: expr selector) ifTrue:
- 			[| types |
- 			 types := Set new.
- 			 self addTypesFor: expr receiver to: types in: aCodeGen.
- 			 (types size = 1 and: [types anyOne last = $*]) ifTrue: "pointer arithmetic"
- 				[typeSet add: types anyOne. ^false].
- 			 self addTypesFor: expr args first to: types in: aCodeGen.
- 			 types := aCodeGen harmonizeReturnTypesIn: types.
- 			 types size = 2 ifTrue:
- 				[(types includes: #double) ifTrue:
- 					[typeSet add: #double. ^false].
- 				 (types includes: #float) ifTrue:
- 					[typeSet add: #float. ^false].
- 				^false]. "don't know; leave unspecified."
- 			types notEmpty ifTrue:
- 				[typeSet add: types anyOne].
- 			^false].
- 		"Abort only for untyped methods that will be typed, but don't be phased by recursion."
- 		 ^(aCodeGen returnTypeForSend: expr in: self)
- 			ifNotNil: [:type| typeSet add: type. false]
- 			ifNil: [(aCodeGen methodNamed: expr selector) notNil and: [expr selector ~~ selector]]].
  	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 typeOrNilFrom: aCodeGen in: self)
+ 			ifNotNil: [:type | typeSet add: type]]..
- 		[| val |
- 		 val := expr value.
- 		 val isInteger ifTrue:
- 			[typeSet add: ((val >= 0 ifTrue: [val] ifFalse: [-1 - val]) highBit <= 32
- 									ifTrue: [#sqInt]
- 									ifFalse: [#sqLong])].
- 		 (#(nil true false) includes: val) ifTrue:
- 			[typeSet add: #sqInt].
- 		 val isFloat ifTrue:
- 			[typeSet add: #float]].
  	^false!

Item was changed:
  ----- Method: TMethod>>isFunctional (in category 'inlining') -----
  isFunctional
  	"Answer true if the receiver is a functional method. That is, if it
  	 consists of a single return statement of an expression that contains
  	 no other returns.
  
  	 Answer false for methods with return types other than the simple
  	 integer types to work around bugs in the inliner."
  
  	parseTree statements isEmpty ifTrue:
  		[^false].
  	parseTree statements last isReturn ifFalse:
  		[^false].
  	parseTree statements size = 1 ifFalse:
  		[(parseTree statements size = 2
  		  and: [parseTree statements first isSend
  		  and: [parseTree statements first selector == #flag:]]) ifFalse:
  			[^false]].
  	parseTree statements last expression nodesDo:
  		[ :n | n isReturn ifTrue: [^false]].
+ 	^#(int #'unsigned int' #long #'unsigned long' #'long long' #'unsigned long long'
+ 		sqInt usqInt sqLong usqLong
+ 		#'int *' #'unsigned int *' #'sqInt *' #'usqInt *' #'sqLong *' #'usqLong *' #'CogMethod *' #'char *') includes: returnType!
- 	^#(sqInt usqInt sqLong usqLong #'sqInt *' #'CogMethod *' #'char *') includes: returnType!



More information about the Vm-dev mailing list