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

commits at source.squeak.org commits at source.squeak.org
Thu Mar 6 20:12:01 UTC 2014


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

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

Name: VMMaker.oscog-eem.629
Author: eem
Time: 6 March 2014, 12:08:18.196 pm
UUID: b5baf46e-f728-459f-954f-c1c4aeb2abb4
Ancestors: VMMaker.oscog-eem.628

Revamp primitiveVMParameter to avoid overflow in values such as
total heap size.  Make statProcessSwitch, statIOProcessEvents,
statForceInterruptCheck, statCheckForEvents, statStackOverflow
& statStackPageDivorce 64-bit to avoid wrapping.
Make sure that positive64BitIntegerFor: will not cause a GC just as
positive32BitIntegerFor: doesn't.

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

Item was added:
+ ----- Method: NewObjectMemory>>bytesPerSlot (in category 'accessing') -----
+ bytesPerSlot
+ 	^self bytesPerOop!

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].
  	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
+ 								"these are high-frequency enough that tehy're overflowing quite quickly on modern hardware"
+ 								statProcessSwitch statIOProcessEvents statForceInterruptCheck
+ 								statCheckForEvents statStackOverflow statStackPageDivorce)
- 								longRunningPrimitiveStartUsecs longRunningPrimitiveStopUsecs)
  		in: aCCodeGenerator.
  	aCCodeGenerator var: #nextProfileTick type: #sqLong!

Item was changed:
  ----- Method: StackInterpreter>>positive32BitIntegerFor: (in category 'primitive support') -----
  positive32BitIntegerFor: integerValue
  	| newLargeInteger |
+ 	"N.B. will *not* cause a GC.
+ 		integerValue is interpreted as POSITIVE, e.g. as the result of Bitmap>at:."
- 	"Note - integerValue is interpreted as POSITIVE, eg, as the result of Bitmap>at:, or integer>bitAnd:."
  	(integerValue >= 0
  	 and: [objectMemory isIntegerValue: integerValue]) ifTrue:
  		[^objectMemory integerObjectOf: integerValue].
  
  	newLargeInteger := objectMemory
  							eeInstantiateSmallClassIndex: ClassLargePositiveIntegerCompactIndex
  							format: (objectMemory byteFormatForNumBytes: 4)
  							numSlots: 1.
  	objectMemory
  		storeByte: 3 ofObject: newLargeInteger withValue: (integerValue >> 24 bitAnd: 16rFF);
  		storeByte: 2 ofObject: newLargeInteger withValue: (integerValue >> 16 bitAnd: 16rFF);
  		storeByte: 1 ofObject: newLargeInteger withValue: (integerValue >>   8 bitAnd: 16rFF);
  		storeByte: 0 ofObject: newLargeInteger withValue: (integerValue ">> 0" bitAnd: 16rFF).
  	^newLargeInteger!

Item was changed:
  ----- Method: StackInterpreter>>positive64BitIntegerFor: (in category 'primitive support') -----
  positive64BitIntegerFor: integerValue
- 
- 	| newLargeInteger value highWord sz |
- 	"Note - integerValue is interpreted as POSITIVE, eg, as the result of
- 		Bitmap>at:, or integer>bitAnd:."
  	<var: 'integerValue' type: 'sqLong'>
+ 	| newLargeInteger highWord sz |
+ 	"N.B. will *not* cause a GC.
+ 		integerValue is interpreted as POSITIVE, e.g. as the result of Bitmap>at:."
+ 	highWord := self cCode: 'integerValue >> 32' inSmalltalk: [integerValue >> 32]. "shift is coerced to usqInt otherwise"
-  
- 	(self sizeof: integerValue) = 4 ifTrue: [^self positive32BitIntegerFor: integerValue].
- 
- 
- 	highWord := self cCode: 'integerValue >> 32'. "shift is coerced to usqInt otherwise"
  	highWord = 0 ifTrue:[^self positive32BitIntegerFor: integerValue].
  	sz := 5.
  	(highWord := highWord >> 8) = 0 ifFalse:[sz := sz + 1].
  	(highWord := highWord >> 8) = 0 ifFalse:[sz := sz + 1].
  	(highWord := highWord >> 8) = 0 ifFalse:[sz := sz + 1].
+ 	newLargeInteger := objectMemory
+ 							eeInstantiateSmallClassIndex: ClassLargePositiveIntegerCompactIndex
+ 							format: (objectMemory byteFormatForNumBytes: sz)
+ 							numSlots: 8 / objectMemory bytesPerSlot.
+ 	objectMemory
+ 		storeByte: 7 ofObject: newLargeInteger withValue: (integerValue >> 56 bitAnd: 16rFF);
+ 		storeByte: 6 ofObject: newLargeInteger withValue: (integerValue >> 48 bitAnd: 16rFF);
+ 		storeByte: 5 ofObject: newLargeInteger withValue: (integerValue >> 40 bitAnd: 16rFF);
+ 		storeByte: 4 ofObject: newLargeInteger withValue: (integerValue >> 32 bitAnd: 16rFF);
+ 		storeByte: 3 ofObject: newLargeInteger withValue: (integerValue >> 24 bitAnd: 16rFF);
+ 		storeByte: 2 ofObject: newLargeInteger withValue: (integerValue >> 16 bitAnd: 16rFF);
+ 		storeByte: 1 ofObject: newLargeInteger withValue: (integerValue >>   8 bitAnd: 16rFF);
+ 		storeByte: 0 ofObject: newLargeInteger withValue: (integerValue ">> 0" bitAnd: 16rFF).
+ 	^newLargeInteger
- 	newLargeInteger := objectMemory instantiateClass: (objectMemory splObj: ClassLargePositiveInteger) indexableSize:  sz.
- 	0 to: sz-1 do: [:i |
- 		value := self cCode: '(integerValue >> (i * 8)) & 255'.
- 		objectMemory storeByte: i ofObject: newLargeInteger withValue: value].
- 	^ newLargeInteger
  !

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



More information about the Vm-dev mailing list