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

commits at source.squeak.org commits at source.squeak.org
Mon Jan 6 19:04:18 UTC 2014


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

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

Name: VMMaker.oscog-eem.576
Author: eem
Time: 6 January 2014, 11:00:08.082 am
UUID: f4b652dc-67bc-4cf3-8b62-74bcbcbf01cd
Ancestors: VMMaker.oscog-eem.575

Make primitive accessor depth code translatable.
Rename var:type:array: to arrayInitializerCalled:for:sizeString:type:.

Add the missing simulation code for primitive accessor depth to
CogVMSimulator.

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

Item was added:
+ ----- Method: CCodeGenerator>>arrayInitializerCalled:for:sizeString:type: (in category 'utilities') -----
+ arrayInitializerCalled: varName for: array sizeString: sizeStringOrNil type: cType
+ 	"array is a literal array or a CArray on some array."
+ 	| sequence lastLine |
+ 	sequence := array isCollection ifTrue: [array] ifFalse: [array object].
+ 	lastLine := 0.
+ 	^String streamContents:
+ 		[:s|
+ 		s	nextPutAll: cType;
+ 			space;
+ 			nextPutAll: varName;
+ 			nextPut: $[.
+ 		sizeStringOrNil ifNotNil: [s nextPutAll: sizeStringOrNil].
+ 		s nextPutAll: '] = '.
+ 		sequence isString
+ 			ifTrue: [s nextPutAll: (self cLiteralFor: sequence)]
+ 			ifFalse:
+ 				[s nextPut: ${; crtab: 2.
+ 				sequence
+ 					do: [:element| s nextPutAll: (self cLiteralFor: element)]
+ 					separatedBy:
+ 						[s nextPut: $,.
+ 						 (s position - lastLine) > 76
+ 							ifTrue: [s crtab: 2. lastLine := s position]
+ 							ifFalse: [s space]].
+ 				s crtab; nextPut: $}]]!

Item was removed:
- ----- Method: CCodeGenerator>>arrayInitializerCalled:for:type: (in category 'utilities') -----
- arrayInitializerCalled: varName for: array type: cType
- 	"array is a literal array or a CArray on some array."
- 	| sequence lastLine |
- 	sequence := array isCollection ifTrue: [array] ifFalse: [array object].
- 	lastLine := 0.
- 	^String streamContents:
- 		[:s|
- 		s	nextPutAll: cType;
- 			space;
- 			nextPutAll: varName;
- 			nextPutAll: '[] = '.
- 		sequence isString
- 			ifTrue: [s nextPutAll: (self cLiteralFor: sequence)]
- 			ifFalse:
- 				[s nextPut: ${; crtab: 2.
- 				sequence
- 					do: [:element| s nextPutAll: (self cLiteralFor: element)]
- 					separatedBy:
- 						[s nextPut: $,.
- 						 (s position - lastLine) > 76
- 							ifTrue: [s crtab: 2. lastLine := s position]
- 							ifFalse: [s space]].
- 				s crtab; nextPut: $}].
- 		s cr]!

Item was changed:
  ----- Method: CCodeGenerator>>var:type:array: (in category 'public') -----
  var: varName type: cType array: array
  	"Use this in preference to #var:declareC: when possible. This produces a C
  	 statment of the form
  		int * fooArray[]={1,2,3}
  	 See also #var:type: for simple var decls" 
  	self
  		var: varName
+ 		declareC: (self arrayInitializerCalled: varName for: array sizeString: nil type: cType)!
- 		declareC: (self arrayInitializerCalled: varName for: array type: cType)!

Item was added:
+ ----- Method: CCodeGenerator>>var:type:sizeString:array: (in category 'public') -----
+ var: varName type: cType sizeString: sizeString array: array
+ 	"Use this in preference to #var:declareC: when possible. This produces a C
+ 	 statment of the form
+ 		int * fooArray[3 /* Foo */]={1,2,3}
+ 	 See also #var:type: for simple var decls" 
+ 	self
+ 		var: varName
+ 		declareC: (self arrayInitializerCalled: varName for: array sizeString: sizeString type: cType)!

Item was added:
+ ----- Method: CogVMSimulator>>ioLoadFunction:From:AccessorDepthInto: (in category 'plugin support') -----
+ ioLoadFunction: functionString From: pluginString AccessorDepthInto: accessorDepthPtr
+ 	"Load and return the requested function from a module.
+ 	 Assign the accessor depth through accessorDepthPtr.
+ 	 N.B. The actual code lives in platforms/Cross/vm/sqNamedPrims.h"
+ 	| firstTime plugin fnSymbol |
+ 	firstTime := false.
+ 	fnSymbol := functionString asSymbol.
+ 	transcript
+ 		cr;
+ 		show: '(', byteCount printString, ') Looking for ', functionString, ' in ',
+ 				(pluginString isEmpty ifTrue:['vm'] ifFalse:[pluginString]).
+ 	functionString = breakSelector ifTrue: [self halt: breakSelector].
+ 	plugin := pluginList 
+ 				detect: [:any| any key = pluginString asString]
+ 				ifNone:
+ 					[firstTime := true.
+ 					 self loadNewPlugin: pluginString].
+ 	plugin ifNil:
+ 		[firstTime ifTrue: [transcript cr; show: 'Failed ... primitive not in plugin'].
+ 		 ^0].
+ 	plugin := plugin value.
+ 	mappedPluginEntries doWithIndex:
+ 		[:pluginAndName :index|
+ 		 ((pluginAndName at: 1) == plugin 
+ 		  and:[(pluginAndName at: 2) == fnSymbol]) ifTrue:
+ 			[firstTime ifTrue: [transcript cr; show: ' ... okay'].
+ 			 accessorDepthPtr at: 0 put: (pluginAndName at: 4).
+ 			 ^index]].
+ 	firstTime ifTrue: [transcript cr; show: 'Failed ... primitive not in plugin'].
+ 	^0!

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.
- 		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 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: TAssignmentNode>>emitLiteralArrayDeclarationOn:level:generator: (in category 'C code generation') -----
  emitLiteralArrayDeclarationOn: aStream level: level generator: aCCodeGen
  	| type |
  	type := expression args last value.
  	self assert: type last = $*.
  	aStream
  		crtab: level;
  		nextPutAll: '{ static ';
+ 		nextPutAll: (aCCodeGen
+ 						arrayInitializerCalled: 'aLiteralArray'
+ 						for: expression args first value
+ 						sizeString: nil
+ 						type: type allButLast) withBlanksTrimmed;
- 		nextPutAll: (aCCodeGen arrayInitializerCalled: 'aLiteralArray' for: expression args first value type: type allButLast) withBlanksTrimmed;
  		nextPut: $;;
  		crtab: level + 1;
  		nextPutAll: variable name;
  		nextPutAll: ' = aLiteralArray;';
  		crtab: level;
  		nextPut: $};
  		cr!



More information about the Vm-dev mailing list