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

commits at source.squeak.org commits at source.squeak.org
Wed Dec 4 20:55:18 UTC 2013


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

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

Name: VMMaker.oscog-eem.529
Author: eem
Time: 2 December 2013, 5:25:30.451 pm
UUID: 0a395bcc-3dda-4e68-ad96-437e32f03339
Ancestors: VMMaker.oscog-eem.528

Fix implicit typing of variables assigned the result of an <api>
method.

Refactor compactCompiledCode: to compactCompiledCode to get
the null header initialized correctly.

Replace the simulation code in asciiDirectoryDelimiter with
something that will work for both FileSystem and FileDirectory.

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

Item was added:
+ ----- Method: CCodeGenerator>>anyMethodNamed: (in category 'utilities') -----
+ anyMethodNamed: selector
+ 	"Answer any method in the code base (including api methods) with the given selector."
+ 
+ 	^methods
+ 		at: selector
+ 		ifAbsent:
+ 			[apiMethods ifNotNil:
+ 				[apiMethods
+ 					at: selector
+ 					ifAbsent: []]]!

Item was changed:
  ----- Method: CCodeGenerator>>inferTypesForImplicitlyTypedVariablesAndMethods (in category 'type inference') -----
  inferTypesForImplicitlyTypedVariablesAndMethods
  	"Infer the return tupe and the types of untyped variables.
  	 As far as variables go, for now we try only to infer variables
  	 assigned the result of #longLongAt:, but much more could be
  	 done here."
  
  	"Iterate over all methods, inferring #void return types, until we reach a fixed point."
+ 	| firstTime allMethods |
- 	| firstTime |
  	firstTime := true.
+ 	allMethods := apiMethods
+ 					ifNil: [methods]
+ 					ifNotNil: [(Set withAll: methods)
+ 								addAll: apiMethods;
+ 								yourself].
  	[| changedReturnType |
  	 changedReturnType := false.
+ 	 allMethods do:
- 	 methods do:
  		[:m|
  		 firstTime ifTrue:
  			[m removeFinalSelfReturnIn: self. "must preceed recordDeclarationsIn: because it may set returnType"
  			 m recordDeclarationsIn: self].
  		 m inferTypesForImplicitlyTypedVariablesIn: self.
  		 (m inferReturnTypeIn: self) ifTrue:
  			[changedReturnType := true]].
  	 firstTime := false.
  	 changedReturnType] whileTrue.
  
  	"Type all as-yet-untyped methods as the default"
  	methods do:
  		[:m|
  		m returnType ifNil:
  			[m returnType: (self implicitReturnTypeFor: m selector)]]!

Item was added:
+ ----- Method: CogMethodZone>>compactCompiledCode (in category 'compaction') -----
+ compactCompiledCode
+ 	| objectHeaderValue source dest bytes |
+ 	<var: #source type: #'CogMethod *'>
+ 	<var: #dest type: #'CogMethod *'>
+ 	objectHeaderValue := objectMemory nullHeaderForMachineCodeMethod.
+ 	source := coInterpreter cCoerceSimple: baseAddress to: #'CogMethod *'.
+ 	openPICList := nil.
+ 	methodCount := 0.
+ 	self cppIf: NewspeakVM ifTrue: [unpairedMethodList := nil].
+ 	[source < self limitZony
+ 	 and: [source cmType ~= CMFree]] whileTrue:
+ 		[self assert: (cogit cogMethodDoesntLookKosher: source) = 0.
+ 		 source objectHeader: objectHeaderValue.
+ 		 source cmUsageCount > 0 ifTrue:
+ 			[source cmUsageCount: source cmUsageCount // 2].
+ 		 self cppIf: NewspeakVM ifTrue:
+ 				[(source cmType = CMMethod
+ 				  and: [(coInterpreter rawHeaderOf: source methodObject) asInteger ~= source asInteger]) ifTrue:
+ 					[source nextMethod: unpairedMethodList.
+ 					 unpairedMethodList := source]].
+ 		 source cmType = CMOpenPIC ifTrue:
+ 			[source nextOpenPIC: openPICList asUnsignedInteger.
+ 			 openPICList := source].
+ 		 methodCount := methodCount + 1.
+ 		 source := self methodAfter: source].
+ 	source >= self limitZony ifTrue:
+ 		[^self halt: 'no free methods; cannot compact.'].
+ 	dest := source.
+ 	[source < self limitZony] whileTrue:
+ 		[self assert: (cogit maybeFreeCogMethodDoesntLookKosher: source) = 0.
+ 		 bytes := source blockSize.
+ 		 source cmType ~= CMFree ifTrue:
+ 			[methodCount := methodCount + 1.
+ 			 objectMemory mem: dest mo: source ve: bytes.
+ 			 dest objectHeader: objectHeaderValue.
+ 			 dest cmType = CMMethod
+ 				ifTrue:
+ 					["For non-Newspeak there should be a one-to-one mapping between bytecoded and
+ 					  cog methods.  For Newspeak not necessarily, but only for anonymous accessors."
+ 					"Only update the original method's header if it is referring to this CogMethod."
+ 					 (coInterpreter rawHeaderOf: dest methodObject) asInteger = source asInteger
+ 						ifTrue: [coInterpreter rawHeaderOf: dest methodObject put: dest asInteger]
+ 						ifFalse:
+ 							[self assert: (cogit noAssertMethodClassAssociationOf: dest methodObject) = objectMemory nilObject.
+ 							 self cppIf: NewspeakVM
+ 								ifTrue: [dest nextMethod: unpairedMethodList.
+ 										unpairedMethodList := dest]]]
+ 				ifFalse:
+ 					[dest cmType = CMOpenPIC ifTrue:
+ 						[dest nextOpenPIC: openPICList asUnsignedInteger.
+ 						 openPICList := dest]].
+ 			 dest cmUsageCount > 0 ifTrue:
+ 				[dest cmUsageCount: dest cmUsageCount // 2].
+ 			 dest := coInterpreter
+ 								cCoerceSimple: dest asUnsignedInteger + bytes
+ 								to: #'CogMethod *'].
+ 		 source := coInterpreter
+ 							cCoerceSimple: source asUnsignedInteger + bytes
+ 							to: #'CogMethod *'].
+ 	mzFreeStart := dest asUnsignedInteger.
+ 	methodBytesFreedSinceLastCompaction := 0!

Item was removed:
- ----- Method: CogMethodZone>>compactCompiledCode: (in category 'compaction') -----
- compactCompiledCode: objectHeaderValue
- 	| source dest bytes |
- 	<var: #source type: #'CogMethod *'>
- 	<var: #dest type: #'CogMethod *'>
- 	source := coInterpreter cCoerceSimple: baseAddress to: #'CogMethod *'.
- 	openPICList := nil.
- 	methodCount := 0.
- 	self cppIf: NewspeakVM ifTrue: [unpairedMethodList := nil].
- 	[source < self limitZony
- 	 and: [source cmType ~= CMFree]] whileTrue:
- 		[self assert: (cogit cogMethodDoesntLookKosher: source) = 0.
- 		 source objectHeader: objectHeaderValue.
- 		 source cmUsageCount > 0 ifTrue:
- 			[source cmUsageCount: source cmUsageCount // 2].
- 		 self cppIf: NewspeakVM ifTrue:
- 				[(source cmType = CMMethod
- 				  and: [(coInterpreter rawHeaderOf: source methodObject) asInteger ~= source asInteger]) ifTrue:
- 					[source nextMethod: unpairedMethodList.
- 					 unpairedMethodList := source]].
- 		 source cmType = CMOpenPIC ifTrue:
- 			[source nextOpenPIC: openPICList asUnsignedInteger.
- 			 openPICList := source].
- 		 methodCount := methodCount + 1.
- 		 source := self methodAfter: source].
- 	source >= self limitZony ifTrue:
- 		[^self halt: 'no free methods; cannot compact.'].
- 	dest := source.
- 	[source < self limitZony] whileTrue:
- 		[self assert: (cogit maybeFreeCogMethodDoesntLookKosher: source) = 0.
- 		 bytes := source blockSize.
- 		 source cmType ~= CMFree ifTrue:
- 			[methodCount := methodCount + 1.
- 			 objectMemory mem: dest mo: source ve: bytes.
- 			 dest objectHeader: objectHeaderValue.
- 			 dest cmType = CMMethod
- 				ifTrue:
- 					["For non-Newspeak there should be a one-to-one mapping between bytecoded and
- 					  cog methods.  For Newspeak not necessarily, but only for anonymous accessors."
- 					"Only update the original method's header if it is referring to this CogMethod."
- 					 (coInterpreter rawHeaderOf: dest methodObject) asInteger = source asInteger
- 						ifTrue: [coInterpreter rawHeaderOf: dest methodObject put: dest asInteger]
- 						ifFalse:
- 							[self assert: (cogit noAssertMethodClassAssociationOf: dest methodObject) = objectMemory nilObject.
- 							 self cppIf: NewspeakVM
- 								ifTrue: [dest nextMethod: unpairedMethodList.
- 										unpairedMethodList := dest]]]
- 				ifFalse:
- 					[dest cmType = CMOpenPIC ifTrue:
- 						[dest nextOpenPIC: openPICList asUnsignedInteger.
- 						 openPICList := dest]].
- 			 dest cmUsageCount > 0 ifTrue:
- 				[dest cmUsageCount: dest cmUsageCount // 2].
- 			 dest := coInterpreter
- 								cCoerceSimple: dest asUnsignedInteger + bytes
- 								to: #'CogMethod *'].
- 		 source := coInterpreter
- 							cCoerceSimple: source asUnsignedInteger + bytes
- 							to: #'CogMethod *'].
- 	mzFreeStart := dest asUnsignedInteger.
- 	methodBytesFreedSinceLastCompaction := 0!

Item was changed:
  ----- Method: Cogit>>compactCogCompiledCode (in category 'jit - api') -----
  compactCogCompiledCode
  	<api>
  	self assert: self noCogMethodsMaximallyMarked.
  	coInterpreter markActiveMethodsAndReferents.
  	methodZone freeOlderMethodsForCompaction.
  	self freePICsWithFreedTargets.
  	methodZone planCompaction.
  	coInterpreter updateStackZoneReferencesToCompiledCodePreCompaction.
  	self relocateMethodsPreCompaction.
+ 	methodZone compactCompiledCode.
- 	methodZone compactCompiledCode: objectMemory nullHeaderForMachineCodeMethod.
  	self assert: self allMethodsHaveCorrectHeader.
  	self assert: methodZone kosherYoungReferrers.
  	processor flushICacheFrom: methodZoneBase to: methodZone freeStart!

Item was changed:
  ----- Method: FilePlugin>>asciiDirectoryDelimiter (in category 'directory primitives') -----
  asciiDirectoryDelimiter
+ 	^ self
+ 		cCode: 'dir_Delimitor()'
+ 		inSmalltalk:
+ 			[(Smalltalk classNamed: #FileSystem)
+ 				ifNotNil: [:fileSystem| fileSystem disk delimiter asciiValue]
+ 				ifNil: [FileDirectory pathNameDelimiter asciiValue]]!
- 	^ self cCode: 'dir_Delimitor()' inSmalltalk: [FileDirectory pathNameDelimiter asciiValue]!

Item was changed:
  ----- Method: TMethod>>determineTypeFor:in: (in category 'C code generation') -----
  determineTypeFor: aNode in: aCodeGen
  	aNode isSend ifTrue:
  		[aNode selector == #addressOf: ifTrue:
  			[^(self determineTypeFor: aNode args first in: aCodeGen)
  				ifNil: [#sqInt]
  				ifNotNil: [:type| type, (type last isLetter ifTrue: [' *'] ifFalse: ['*'])]].
  		(aNode selector == #at:
  		 and: [aNode receiver isVariable]) ifTrue:
  			[(aCodeGen typeOfVariable: aNode receiver name) ifNotNil:
  				[:type|
  				^type last = $*
  					ifTrue: [aCodeGen
  								extractTypeFor: aNode receiver name
  								fromDeclaration: type allButLast]
  					ifFalse: [type]]].
+ 		^(aCodeGen anyMethodNamed: aNode selector)
- 		^(aCodeGen methodNamed: aNode selector)
  			ifNil: [#sqInt]
  			ifNotNil: [:method| method returnType]].
  	aNode isAssignment ifTrue:
  		[^self determineTypeFor: aNode expression in: aCodeGen].
  	self error: 'don''t know how to extract return type from this kind of node'!

Item was changed:
  ----- Method: TMethod>>inferTypesForImplicitlyTypedVariablesIn: (in category 'type inference') -----
  inferTypesForImplicitlyTypedVariablesIn: aCodeGen
  	| explicitlyTyped |
  	explicitlyTyped := declarations keys asSet.
  	parseTree nodesDo:
  		[:node| | type var m |
  		"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: [(explicitlyTyped includes: var) not
  		 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:
  			[declarations at: var put: (declarations at: var) allButFirst].
  		"if an assignment of a known send, set the variable's type to the return type of the send."
  		(node isAssignment
  		 and: [(locals includes: (var := node variable name))
  		 and: [(declarations includesKey: var) not
  		 and: [node expression isSend
+ 		 and: [(m := aCodeGen anyMethodNamed: node expression selector) notNil]]]]) ifTrue:
- 		 and: [(m := aCodeGen methodNamed: node expression selector) notNil]]]]) ifTrue:
  			[(#(sqInt void nil) includes: m returnType) ifFalse:
  				["the $: is to map things like unsigned field : 3 to usqInt"
  				 declarations
  					at: var
  					put: ((m returnType includes: $:) ifTrue: [#usqInt] ifFalse: [m returnType]), ' ', var]]]!



More information about the Vm-dev mailing list