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

commits at source.squeak.org commits at source.squeak.org
Mon Jan 6 21:58:19 UTC 2014


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

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

Name: VMMaker.oscog-eem.577
Author: eem
Time: 6 January 2014, 1:53:51.172 pm
UUID: 8788f091-6817-480e-9bda-13ae360eeeb7
Ancestors: VMMaker.oscog-eem.576

Clean-up accessorDepth code for SqueakV3 VMs.
Don't include accessor depth in SqueakV3 vm's named primitives.
Do a better job of dead code removal with and: and or: chains.
Don't generate primitiveAccessorDepthTable in SqueakV3 VMs.
Copy the hasSpurMemoryManagerAPI methods to the class-side.

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

Item was changed:
  ----- Method: CCodeGenerator>>emitExportsNamed:pluginName:on: (in category 'C code generator') -----
  emitExportsNamed: exportsNamePrefix pluginName: pluginName on: aStream
  	"Store all the exported primitives in the form used by the internal named prim system."
+ 	| nilVMClass excludeDepth |
- 	| nilVMClass |
  	(nilVMClass := vmClass isNil) ifTrue:
  		[vmClass := StackInterpreter].
+ 	"Don't include the depth in the vm's named primitives if the vm is non-Spur."
+ 	excludeDepth := exportsNamePrefix = 'vm'
+ 					  and: [pluginName isEmpty
+ 					  and: [vmClass objectMemoryClass hasSpurMemoryManagerAPI not]].
  	aStream cr; cr; nextPutAll: 'void* '; nextPutAll: exportsNamePrefix; nextPutAll: '_exports[][3] = {'.
  	(self sortStrings: self exportedPrimitiveNames) do:
  		[:primName|
+ 		 aStream cr; tab;
+ 			nextPutAll: '{"'; 
- 		 aStream cr;
- 			nextPutAll:'	{"'; 
  			nextPutAll: pluginName; 
  			nextPutAll: '", "'; 
  			nextPutAll: primName.
+ 		 excludeDepth ifFalse:
+ 			[(self accessorDepthForSelector: primName asSymbol) ifNotNil:
+ 				[:depth| "store the accessor depth in a hidden byte immediately after the primName"
+ 				self assert: depth < 128.
+ 				aStream
+ 					nextPutAll: '\000\';
+ 					nextPutAll: ((depth bitAnd: 255) printStringBase: 8 nDigits: 3)]].
- 		 (self accessorDepthForSelector: primName asSymbol) ifNotNil:
- 			[:depth| "store the accessor depth in a hidden byte immediately after the primName"
- 			self assert: depth < 128.
- 			aStream
- 				nextPutAll: '\000\';
- 				nextPutAll: ((depth bitAnd: 255) printStringBase: 8 nDigits: 3)].
  		 aStream
+ 			nextPutAll: '", (void*)'; 
- 			nextPutAll:'", (void*)'; 
  			nextPutAll: primName;
+ 			nextPutAll: '},'].
+ 	aStream cr; tab; nextPutAll: '{NULL, NULL, NULL}'; cr; nextPutAll: '};'; cr.
- 			nextPutAll:'},'].
- 	aStream cr; tab; nextPutAll:'{NULL, NULL, NULL}'; cr; nextPutAll: '};'; cr.
  	nilVMClass ifTrue:
  		[vmClass := nil]!

Item was changed:
  ----- Method: CCodeGenerator>>nilOrBooleanConstantReceiverOf: (in category 'utilities') -----
  nilOrBooleanConstantReceiverOf: aNode
  	"Answer nil or the boolean constant that is the receiver of the given message send.
  	 Used to suppress conditional code when the condition is a translation-time constant."
  
  	| val receiver argument |
  	generateDeadCode ifTrue:[^nil].
  	((self isConstantNode: aNode valueInto: [:v| val := v])
  	 and: [#(true false) includes: val]) ifTrue:
  		[^val].
  	aNode isSend ifTrue:
  		[((#(or: and:) includes: aNode selector)
  		 and: [aNode args last isStmtList
  		 and: [aNode args last statements size = 1]]) ifTrue:
  			[(self nilOrBooleanConstantReceiverOf: aNode receiver) ifNotNil:
  				[:rcvr|
+ 				((rcvr == false and: [aNode selector == #and:])
+ 				 or: [rcvr == true and: [aNode selector == #or:]]) ifTrue:
+ 					[^rcvr].
  				(self nilOrBooleanConstantReceiverOf: aNode args last statements first) ifNotNil:
  					[:arg|
  					^rcvr perform: aNode selector with: [arg]]]].
  		 ((#(= ~= < > <= >=) includes: aNode selector)
  		  and: [(self isConstantNode: aNode receiver valueInto: [:v| receiver := v])
  		  and: [receiver isInteger
  		  and: [(self isConstantNode: aNode args first valueInto: [:v| argument := v])
  		  and: [argument isInteger]]]]) ifTrue:
  			[^receiver perform: aNode selector with: argument]].
  	^nil!

Item was added:
+ ----- Method: ObjectMemory class>>hasSpurMemoryManagerAPI (in category 'api chacterization') -----
+ hasSpurMemoryManagerAPI
+ 	^false!

Item was added:
+ ----- Method: SpurMemoryManager class>>hasSpurMemoryManagerAPI (in category 'api characterization') -----
+ hasSpurMemoryManagerAPI
+ 	^true!

Item was changed:
  ----- Method: StackInterpreter class>>declareCVarsIn: (in category 'translation') -----
  declareCVarsIn: aCCodeGenerator
  	self class == thisContext methodClass ifFalse: [^self]. "Don't duplicate decls in subclasses"
  	aCCodeGenerator
  		addHeaderFile:'<stddef.h> /* for e.g. alloca */';
  		addHeaderFile:'<setjmp.h>';
  		addHeaderFile:'"vmCallback.h"';
  		addHeaderFile:'"sqMemoryFence.h"';
  		addHeaderFile:'"dispdbg.h"'.
  	self declareInterpreterVersionIn: aCCodeGenerator
  		defaultName: 'Stack'.
  	aCCodeGenerator
  		var: #interpreterProxy  type: #'struct VirtualMachine*'.
  	aCCodeGenerator
  		declareVar: #sendTrace type: 'volatile int';
  		declareVar: #byteCount type: 'unsigned long'.
  	"These need to be pointers or unsigned."
  	self declareC: #(instructionPointer method newMethod)
  		as: #usqInt
  		in: aCCodeGenerator.
  	"These are all pointers; char * because Slang has no support for C pointer arithmetic."
  	self declareC: #(localIP localSP localFP stackPointer framePointer stackLimit stackMemory)
  		as: #'char *'
  		in: aCCodeGenerator.
  	self declareC: #(stackPage overflowedPage)
  		as: #'StackPage *'
  		in: aCCodeGenerator.
  	aCCodeGenerator removeVariable: 'stackPages'.  "this is an implicit receiver in the translated code."
  	"This defines bytecodeSetSelector as 0 if MULTIPLEBYTECODESETS
  	 is not defined, for the benefit of the interpreter on slow machines."
  	aCCodeGenerator addConstantForBinding: (self bindingOf: #MULTIPLEBYTECODESETS).
  	MULTIPLEBYTECODESETS == false ifTrue:
  		[aCCodeGenerator
  			removeVariable: 'extA';
  			removeVariable: 'extB';
  			removeVariable: 'bytecodeSetSelector'].
  	aCCodeGenerator
  		var: #methodCache
  		declareC: 'long methodCache[MethodCacheSize + 1 /* ', (MethodCacheSize + 1) printString, ' */]'.
  	aCCodeGenerator
  		var: #atCache
  		declareC: 'sqInt atCache[AtCacheTotalSize + 1 /* ', (AtCacheTotalSize + 1) printString, ' */]'.
  	aCCodeGenerator
  		var: #primitiveTable
  		declareC: 'void (*primitiveTable[MaxPrimitiveIndex + 2 /* ', (MaxPrimitiveIndex + 2) printString, ' */])(void) = ', self primitiveTableString.
  	self primitiveTable do:
  		[:symbolOrNot|
  		(symbolOrNot isSymbol
  		 and: [symbolOrNot ~~ #primitiveFail]) ifTrue:
  			[(aCCodeGenerator methodNamed: symbolOrNot) ifNotNil:
  				[:tMethod| tMethod returnType: #void]]].
+ 	self objectMemoryClass hasSpurMemoryManagerAPI
+ 		ifTrue:
+ 			[aCCodeGenerator
+ 				var: #primitiveAccessorDepthTable
+ 				type: 'signed char'
+ 				sizeString: 'MaxPrimitiveIndex + 2 /* ', (MaxPrimitiveIndex + 2) printString, ' */'
+ 				array: self primitiveAccessorDepthTable]
+ 		ifFalse:
+ 			[aCCodeGenerator removeVariable: #primitiveAccessorDepthTable].
- 	self objectMemoryClass basicNew hasSpurMemoryManagerAPI ifTrue:
- 		[aCCodeGenerator
- 			var: #primitiveAccessorDepthTable
- 			type: 'signed char'
- 			sizeString: 'MaxPrimitiveIndex + 2 /* ', (MaxPrimitiveIndex + 2) printString, ' */'
- 			array: self primitiveAccessorDepthTable].
  	aCCodeGenerator
  		var: #primitiveFunctionPointer
  		declareC: 'void (*primitiveFunctionPointer)()'.
  	aCCodeGenerator
  		var: #externalPrimitiveTable
  		declareC: 'void (*externalPrimitiveTable[MaxExternalPrimitiveTableSize + 1 /* ', (MaxExternalPrimitiveTableSize + 1) printString, ' */])(void)'.
  	aCCodeGenerator var: #showSurfaceFn type: #'void *'.
  	aCCodeGenerator
  		var: #jmpBuf
  		declareC: 'jmp_buf jmpBuf[MaxJumpBuf + 1 /* ', (MaxJumpBuf + 1) printString, ' */]'.
  	aCCodeGenerator
  		var: #suspendedCallbacks
  		declareC: 'usqInt suspendedCallbacks[MaxJumpBuf + 1 /* ', (MaxJumpBuf + 1) printString, ' */]'.
  	aCCodeGenerator
  		var: #suspendedMethods
  		declareC: 'usqInt suspendedMethods[MaxJumpBuf + 1 /* ', (MaxJumpBuf + 1) printString, ' */]'.
  	aCCodeGenerator
  		var: #interruptCheckChain
  		declareC: 'void (*interruptCheckChain)(void) = 0'.
  	aCCodeGenerator
  		var: #breakSelector type: #'char *';
  		var: #breakSelectorLength
  		declareC: 'sqInt breakSelectorLength = -1'.
  
  	self declareCAsUSqLong: #(nextPollUsecs nextWakeupUsecs longRunningPrimitiveGCUsecs
  								longRunningPrimitiveStartUsecs longRunningPrimitiveStopUsecs)
  		in: aCCodeGenerator.
  	aCCodeGenerator var: #nextProfileTick type: #sqLong!

Item was changed:
  ----- Method: StackInterpreter>>checkForAndFollowForwardedPrimitiveState (in category 'primitive support') -----
  checkForAndFollowForwardedPrimitiveState
  	"In Spur a primitive may fail due to encountering a forwarder.
  	 On failure check the accessorDepth for the primitive and
  	 if non-negative scan the args to the depth, following any
+ 	 forwarders.  Answer if any are found so the prim can be retried."
+ 	<option: #SpurObjectMemory>
- 	 forwarders.  Answer if any are found so the prim can be retried.."
  	| primIndex accessorDepth found |
  	self assert: self successful not.
  	found := false.
  	primIndex := self primitiveIndexOf: newMethod.
  	self assert: (self
  					cCode:
  						[primitiveFunctionPointer = (self functionPointerFor: primIndex inClass: objectMemory nilObject)]
  					inSmalltalk:
  						[((primitiveFunctionPointer isInteger and: [primitiveFunctionPointer >= 1000])
  							ifTrue: [#primitiveExternalCall]
  							ifFalse: [primitiveFunctionPointer]) = (self functionPointerFor: primIndex inClass: objectMemory nilObject)]).
  	self assert: argumentCount = (self argumentCountOf: newMethod).
  	accessorDepth := (primIndex = 117 and: [primitiveFunctionPointer ~~ #primitiveExternalCall])
  							ifTrue: [self primitiveAccessorDepthForExternalPrimitiveMethod: newMethod]
  							ifFalse: [primitiveAccessorDepthTable at: primIndex].
  	accessorDepth < 0 ifTrue:
  		[^false].
  	0 to: argumentCount do:
  		[:index| | oop |
  		oop := self stackValue: index.
  		(objectMemory isNonImmediate: oop) ifTrue:
  			[(objectMemory isForwarded: oop) ifTrue:
  				[self assert: index < argumentCount. "receiver should have been caught at send time."
  				 found := true.
  				 oop := objectMemory followForwarded: oop.
  				 self stackValue: index put: oop].
  			((objectMemory hasPointerFields: oop)
  			 and: [objectMemory followForwardedObjectFields: oop toDepth: accessorDepth]) ifTrue:
  				[found := true]]].
  	^found!



More information about the Vm-dev mailing list