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

commits at source.squeak.org commits at source.squeak.org
Thu Jun 15 23:52:15 UTC 2017


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

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

Name: VMMaker.oscog-eem.2243
Author: eem
Time: 15 June 2017, 4:51:21.305055 pm
UUID: 2f909507-a192-4a51-8bff-786bc61737a5
Ancestors: VMMaker.oscog-eem.2242

StackInterpreter:
Make statTenures, statAverageLivePagesWhenMapping & statMaxPageCountWhenMapping (parameters 11, 68 & 69) writable to allow easier profiling.  Allow parameters expecting a float (statTenures, Sista CogCodeThreshold & statAverageLivePagesWhenMapping: 17, 55, 68) to take an int.

Slang:
Fix a bug in inferTypesForImplicitlyTypedVariablesIn:.  We cannot derive types from variables assigned to until all assignments are typed.  So exclude variables assigned from as-yet-untyped methods.  The old code would simply ignore the types from  as-yet-untyped methods, hence leaving the variable with a chosen-at-random, unmerged type.

This fixes a number of cases.  But there's still the weirdness that the return type of mapEndFor: in cogitX64SysV.c is correct (usqInt) but incorrect (sqInt) in cogitX64WIN64.c.  Luckily this is benign, but still should be fixed asap.

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

Item was changed:
  ----- Method: CogStackPages>>statAverageLivePagesWhenMapping (in category 'statistics') -----
  statAverageLivePagesWhenMapping
  	<returnTypeC: #double>
+ 	^statNumMaps = 0
+ 		ifTrue: [0.0]
+ 		ifFalse: [statPageCountWhenMappingSum asFloat / statNumMaps]!
- 	^statPageCountWhenMappingSum asFloat / statNumMaps!

Item was added:
+ ----- Method: CogStackPages>>statAverageLivePagesWhenMapping: (in category 'statistics') -----
+ statAverageLivePagesWhenMapping: aFloat
+ 	<var: #aFloat type: #double>
+ 	aFloat == 0.0
+ 		ifTrue: [statPageCountWhenMappingSum := statNumMaps := 0]
+ 		ifFalse: [coInterpreter primitiveFailFor: PrimErrBadArgument]!

Item was added:
+ ----- Method: CogStackPages>>statMaxPageCountWhenMapping: (in category 'statistics') -----
+ statMaxPageCountWhenMapping: num
+ 	statMaxPageCountWhenMapping := num!

Item was added:
+ ----- Method: ObjectMemory>>statTenures: (in category 'accessing') -----
+ statTenures: aValue
+ 	statTenures := aValue!

Item was added:
+ ----- Method: SpurGenerationScavenger>>statTenures: (in category 'accessing') -----
+ statTenures: aValue
+ 	statTenures := aValue!

Item was added:
+ ----- Method: SpurMemoryManager>>statTenures: (in category 'accessing') -----
+ statTenures: aValue
+ 	<doNotGenerate>
+ 	scavenger statTenures: aValue!

Item was added:
+ ----- Method: StackInterpreterPrimitives>>noInlineLoadFloatOrIntFrom: (in category 'primitive support') -----
+ noInlineLoadFloatOrIntFrom: floatOrInt
+ 	<inline: #never>
+ 	^objectMemory loadFloatOrIntFrom: floatOrInt!

Item was changed:
  ----- Method: StackInterpreterPrimitives>>primitiveVMParameter (in category 'system control primitives') -----
(excessive size, no diff calculated)

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 mustBeSigned newDeclarations effectiveNodes |
- 	| alreadyExplicitlyTypedOrNotToBeTyped asYetUntyped effectiveNodes |
  	aCodeGen maybeBreakForTestToInline: selector in: self.
  	alreadyExplicitlyTypedOrNotToBeTyped := declarations keys asSet.
  	asYetUntyped := locals copyWithoutAll: alreadyExplicitlyTypedOrNotToBeTyped.
+ 	mustBeSigned := Set new.
+ 	newDeclarations := Dictionary new.
  	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]]]]) ifTrue:
+ 			[mustBeSigned add: var.
+ 			 effectiveNodes at: var put: { #signed. node }, (effectiveNodes at: var ifAbsent: [#()])].
- 		 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: "Further, if the type derives from an as-yet-untyped method, we must defer."
+ 					[alreadyExplicitlyTypedOrNotToBeTyped add: var.
+ 					 (node expression isSend
+ 					 and: [(aCodeGen methodNamed: node expression selector) notNil]) ifTrue:
+ 						[newDeclarations removeKey: var ifAbsent: nil]]
- 				ifNil: [alreadyExplicitlyTypedOrNotToBeTyped add: var] 
  				ifNotNil: "Merge simple types (but *don't* merge untyped vars); complex types must be defined by the programmer."
  					[(aCodeGen isSimpleType: type) ifTrue:
  						[(asYetUntyped includes: var)
+ 							ifTrue: [newDeclarations at: var put: type, ' ', var. asYetUntyped remove: var]
- 							ifTrue: [declarations at: var put: type, ' ', var. asYetUntyped remove: var]
  							ifFalse:
+ 								[aCodeGen mergeTypeOf: var in: newDeclarations with: type method: self].
+ 						 effectiveNodes at: var put: { newDeclarations at: var. node }, (effectiveNodes at: var ifAbsent: [#()])]]]].
+ 	mustBeSigned do:
+ 		[:var|
+ 		 (newDeclarations at: var ifAbsent: nil) ifNotNil:
+ 			[:decl| | type |
+ 			 type := aCodeGen extractTypeFor: var fromDeclaration: decl.
+ 			 type first == $u ifTrue:
+ 				[newDeclarations at: var put: (aCodeGen signedTypeForIntegralType: type), ' ', var]]].
+ 	newDeclarations keysAndValuesDo:
+ 		[:var :decl| declarations at: var put: decl].
- 								[aCodeGen mergeTypeOf: var in: declarations with: type method: self].
- 						 effectiveNodes at: var put: { declarations at: var. node }, (effectiveNodes at: var ifAbsent: [#()])]]]].
  	^effectiveNodes!



More information about the Vm-dev mailing list