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

commits at source.squeak.org commits at source.squeak.org
Fri Jul 10 21:02:03 UTC 2015


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

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

Name: VMMaker.oscog-eem.1409
Author: eem
Time: 10 July 2015, 1:59:54.741 pm
UUID: 428ff402-b7ce-44c6-a95d-5db172a1e43f
Ancestors: VMMaker.oscog-eem.1408

Fix slangification of ThreadedFFIPlugin.  Eliminate a few warnings there-in.

Make type of tenuringIncrementalGC agree with sqVirtualMachine.h.

Provide a back dorr for the ARM division routines diuring simulation.

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

Item was added:
+ ----- Method: Cogit>>handleABICallOrJumpSimulationTrap:evaluable: (in category 'simulation only') -----
+ handleABICallOrJumpSimulationTrap: aProcessorSimulationTrap evaluable: evaluable
+ 	self assert: aProcessorSimulationTrap type = #call.
+ 	processor
+ 		simulateLeafCallOf: aProcessorSimulationTrap address
+ 		nextpc: aProcessorSimulationTrap nextpc
+ 		memory: coInterpreter memory.
+ 	self recordInstruction: {'(simulated call of '. aProcessorSimulationTrap address. '/'. evaluable selector. ')'}.
+ 	evaluable valueWithArguments: (processor
+ 										postCallArgumentsNumArgs: evaluable numArgs
+ 										in: coInterpreter memory).
+ 	self recordInstruction: {'(simulated return to '. processor retpcIn: coInterpreter memory. ')'}.
+ 	processor
+ 		smashCallerSavedRegistersWithValuesFrom: 16r80000000 by: objectMemory wordSize;
+ 		simulateLeafReturnIn: coInterpreter memory!

Item was changed:
  ----- Method: Cogit>>handleCallOrJumpSimulationTrap: (in category 'simulation only') -----
  handleCallOrJumpSimulationTrap: aProcessorSimulationTrap
  	<doNotGenerate>
  	| evaluable function result savedFramePointer savedStackPointer savedArgumentCount rpc |
  	evaluable := simulatedTrampolines at: aProcessorSimulationTrap address.
+ 	function := evaluable isBlock
+ 					ifTrue: ['aBlock; probably some plugin primitive']
+ 					ifFalse:
+ 						[evaluable receiver == backEnd ifTrue:
+ 							[^self handleABICallOrJumpSimulationTrap: aProcessorSimulationTrap evaluable: evaluable].
+ 						 evaluable selector].
- 	function := evaluable
- 					isBlock ifTrue: ['aBlock; probably some plugin primitive']
- 					ifFalse: [evaluable selector].
  	function ~~ #ceBaseFrameReturn: ifTrue:
  		[coInterpreter assertValidExternalStackPointers].
  	(function beginsWith: 'ceShort') ifTrue:
  		[^self perform: function with: aProcessorSimulationTrap].
  	aProcessorSimulationTrap type = #call
  		ifTrue:
  			[processor
  				simulateCallOf: aProcessorSimulationTrap address
  				nextpc: aProcessorSimulationTrap nextpc
  				memory: coInterpreter memory.
  			self recordInstruction: {'(simulated call of '. aProcessorSimulationTrap address. '/'. function. ')'}]
  		ifFalse:
  			[processor
  				simulateJumpCallOf: aProcessorSimulationTrap address
  				memory: coInterpreter memory.
  			 self recordInstruction: {'(simulated jump to '. aProcessorSimulationTrap address. '/'. function. ')'}].
  	savedFramePointer := coInterpreter framePointer.
  	savedStackPointer := coInterpreter stackPointer.
  	savedArgumentCount := coInterpreter argumentCount.
  	result := ["self halt: evaluable selector."
  			   evaluable valueWithArguments: (processor
  												postCallArgumentsNumArgs: evaluable numArgs
  												in: coInterpreter memory)]
  				on: ReenterMachineCode
  				do: [:ex| ex return: ex returnValue].
  			
  	coInterpreter assertValidExternalStackPointers.
  	"Verify the stack layout assumption compileInterpreterPrimitive: makes, provided we've
  	 not called something that has built a frame, such as closure value or evaluate method, or
  	 switched frames, such as primitiveSignal, primitiveWait, primitiveResume, primitiveSuspend et al."
  	(function beginsWith: 'primitive') ifTrue:
  		[coInterpreter checkForLastObjectOverwrite.
  		 coInterpreter primFailCode = 0
  			ifTrue: [(#(	primitiveClosureValue primitiveClosureValueWithArgs primitiveClosureValueNoContextSwitch
  						primitiveSignal primitiveWait primitiveResume primitiveSuspend primitiveYield
  						primitiveExecuteMethodArgsArray primitiveExecuteMethod
  						primitivePerform primitivePerformWithArgs primitivePerformInSuperclass
  						primitiveTerminateTo primitiveStoreStackp primitiveDoPrimitiveWithArgs)
  							includes: function) ifFalse:
  						[self assert: savedFramePointer = coInterpreter framePointer.
  						 self assert: savedStackPointer + (savedArgumentCount * objectMemory wordSize)
  								= coInterpreter stackPointer]]
  			ifFalse:
  				[self assert: savedFramePointer = coInterpreter framePointer.
  				 self assert: savedStackPointer = coInterpreter stackPointer]].
  	result ~~ #continueNoReturn ifTrue:
  		[self recordInstruction: {'(simulated return to '. processor retpcIn: coInterpreter memory. ')'}.
  		 rpc := processor retpcIn: coInterpreter memory.
  		 self assert: (rpc >= codeBase and: [rpc < methodZone freeStart]).
  		 processor
  			smashCallerSavedRegistersWithValuesFrom: 16r80000000 by: objectMemory wordSize;
  			simulateReturnIn: coInterpreter memory].
  	self assert: (result isInteger "an oop result"
  			or: [result == coInterpreter
  			or: [result == objectMemory
  			or: [#(nil continue continueNoReturn) includes: result]]]).
  	processor cResultRegister: (result
  							ifNil: [0]
  							ifNotNil: [result isInteger
  										ifTrue: [result]
  										ifFalse: [16rF00BA222]])
  
  	"coInterpreter cr.
  	 processor sp + 32 to: processor sp - 32 by: -4 do:
  		[:sp|
  		 sp = processor sp
  			ifTrue: [coInterpreter print: 'sp->'; tab]
  			ifFalse: [coInterpreter printHex: sp].
  		 coInterpreter tab; printHex: (coInterpreter longAt: sp); cr]"!

Item was changed:
  ----- Method: InterpreterProxy>>tenuringIncrementalGC (in category 'other') -----
  tenuringIncrementalGC
+ 	<returnTypeC: #void>
- 	<returnTypeC: #sqInt>
  	Smalltalk forceTenuring; garbageCollectMost!

Item was changed:
  ----- Method: ThreadedARMFFIPlugin>>ffiCalloutTo:SpecOnStack:in: (in category 'callout support') -----
  ffiCalloutTo: procAddr SpecOnStack: specOnStack in: calloutState
  	<var: #procAddr type: #'void *'>
  	<var: #calloutState type: #'CalloutState *'>
  	<var: #loadFloatRegs declareC: 'extern void loadFloatRegs(double, double, double, double, double, double, double, double)'>
  	"Go out, call this guy and create the return value.  This *must* be inlined because of
  	 the alloca of the outgoing stack frame in ffiCall:WithFlags:NumArgs:Args:AndTypes:"
  	| myThreadIndex atomicType floatRet intRet loadFloatRegs oop |
  	<var: #floatRet type: #double>
  	<var: #intRet type: #usqLong>
  	<inline: true>
  	self cCode: '' inSmalltalk: [loadFloatRegs := #used. loadFloatRegs class].
  	self cppIf: COGMTVM ifTrue:
  	[(calloutState callFlags anyMask: FFICallFlagThreaded) ifTrue:
  		[myThreadIndex := interpreterProxy disownVM: 0]].
  
  	self registerArgsSlop + self cStackAlignment > 0 ifTrue:
  		[self setsp: calloutState argVector].
  
  	calloutState floatRegisterIndex > 0 ifTrue:
  		[self 
  			load: ((self cCoerceSimple: (self addressOf: (calloutState floatRegisters at: 0)) to: 'double *') at: 0)
  			Flo: ((self cCoerceSimple: (self addressOf: (calloutState floatRegisters at: 2)) to: 'double *') at: 0)
  			a: ((self cCoerceSimple: (self addressOf: (calloutState floatRegisters at: 4)) to: 'double *') at: 0)
  			t: ((self cCoerceSimple: (self addressOf: (calloutState floatRegisters at: 6)) to: 'double *') at: 0)
  			R: ((self cCoerceSimple: (self addressOf: (calloutState floatRegisters at: 8)) to: 'double *') at: 0)
  			e: ((self cCoerceSimple: (self addressOf: (calloutState floatRegisters at: 10)) to: 'double *') at: 0)
  			g: ((self cCoerceSimple: (self addressOf: (calloutState floatRegisters at: 12)) to: 'double *') at: 0)
  			s: ((self cCoerceSimple: (self addressOf: (calloutState floatRegisters at: 14)) to: 'double *') at: 0)].
  
  	atomicType := self atomicTypeOf: calloutState ffiRetHeader.
  	(atomicType >> 1) = (FFITypeSingleFloat > 1)
  		ifTrue:
  			[atomicType = FFITypeSingleFloat
  				ifTrue:
  					[floatRet := self 
  						dispatchFunctionPointer: (self cCoerceSimple: procAddr to: 'float (*)(int, int, int, int)') 
  						with: (calloutState integerRegisters at: 0)
  						with: (calloutState integerRegisters at: 1)
  						with: (calloutState integerRegisters at: 2)
  						with: (calloutState integerRegisters at: 3)]
  				ifFalse: "atomicType = FFITypeDoubleFloat"
  					[floatRet := self 
  						dispatchFunctionPointer: (self cCoerceSimple: procAddr to: 'double (*)(int, int, int, int)') 
  						with: (calloutState integerRegisters at: 0)
  						with: (calloutState integerRegisters at: 1)
  						with: (calloutState integerRegisters at: 2)
  						with: (calloutState integerRegisters at: 3)]]
  		ifFalse:
  			[intRet := self 
  				dispatchFunctionPointer: (self cCoerceSimple: procAddr to: 'usqLong (*)(int, int, int, int)') 
  				with: (calloutState integerRegisters at: 0)
  				with: (calloutState integerRegisters at: 1)
  				with: (calloutState integerRegisters at: 2)
  				with: (calloutState integerRegisters at: 3)].
  	"undo any callee argument pops because it may confuse stack management with the alloca."
  	(self isCalleePopsConvention: calloutState callFlags) ifTrue:
  		[self setsp: calloutState argVector].
  
  	self cppIf: COGMTVM ifTrue:
  	[(calloutState callFlags anyMask: FFICallFlagThreaded) ifTrue:
  		[interpreterProxy ownVM: myThreadIndex]].
  
  	(calloutState ffiRetHeader anyMask: FFIFlagPointer+FFIFlagStructure) ifTrue:
  		["Note: Order is important here since FFIFlagPointer + FFIFlagStructure is used to represent
  		 'typedef void* VoidPointer' and VoidPointer must be returned as pointer *not* as struct."
+ 		 (calloutState ffiRetHeader anyMask: FFIFlagPointer)
- 		^(calloutState ffiRetHeader anyMask: FFIFlagPointer)
  			ifTrue:
+ 				[oop := self ffiReturnPointer: intRet ofType: (self ffiReturnType: specOnStack) in: calloutState]
- 				[self ffiReturnPointer: intRet ofType: (self ffiReturnType: specOnStack) in: calloutState]
  			ifFalse:
+ 				[oop := self ffiReturnStruct: intRet ofType: (self ffiReturnType: specOnStack) in: calloutState].
+ 		 ^oop].
- 				[self ffiReturnStruct: intRet ofType: (self ffiReturnType: specOnStack) in: calloutState]].
  	
  	(atomicType >> 1) = (FFITypeSingleFloat > 1)
  		ifTrue:
  			[oop := interpreterProxy floatObjectOf: floatRet]
  		ifFalse:
  			[oop := self ffiCreateIntegralResultOop: intRet
  						ofAtomicType: atomicType
  						in: calloutState].
  	^interpreterProxy methodReturnValue: oop!

Item was changed:
  ----- Method: ThreadedARMFFIPlugin>>ffiPushPointer:in: (in category 'marshalling') -----
  ffiPushPointer: pointer in: calloutState
  	<var: #pointer type: #'void *'>
  	<var: #calloutState type: #'CalloutState *'>
  	<inline: true>
  	calloutState integerRegisterIndex < NumIntRegArgs
  		ifTrue:
+ 			[calloutState integerRegisters at: calloutState integerRegisterIndex put: pointer asInteger.
- 			[calloutState integerRegisters at: calloutState integerRegisterIndex put: pointer.
  			 calloutState integerRegisterIndex: calloutState integerRegisterIndex + 1]
  		ifFalse:
  			[calloutState currentArg + 4 > calloutState limit ifTrue:
  				[^FFIErrorCallFrameTooBig].
  			 interpreterProxy longAt: calloutState currentArg put: pointer.
  			 calloutState currentArg: calloutState currentArg + 4].
  	^0!

Item was changed:
  ----- Method: ThreadedFFIPlugin>>primitiveFFIAllocate (in category 'primitives') -----
  primitiveFFIAllocate
  	"Primitive. Allocate an object on the external heap."
  	| byteSize addr oop ptr |
  	<export: true>
  	<inline: false>
  	<var: #ptr type:'int *'>
  	byteSize := interpreterProxy stackIntegerValue: 0.
  	interpreterProxy failed ifTrue:[^nil].
  	addr := self ffiAlloc: byteSize.
  	addr = 0 ifTrue:[^interpreterProxy primitiveFail].
  	oop := interpreterProxy 
  			instantiateClass: interpreterProxy classExternalAddress 
  			indexableSize: 4.
  	ptr := interpreterProxy firstIndexableField: oop.
  	ptr at: 0 put: addr.
+ 	^interpreterProxy pop: 2 thenPush: oop!
- 	interpreterProxy pop: 2 thenPush: oop!

Item was changed:
  ----- Method: ThreadedFFIPlugin>>primitiveFFIDoubleAtPut (in category 'primitives') -----
  primitiveFFIDoubleAtPut
  	"Return a (signed or unsigned) n byte integer from the given byte offset."
  	| byteOffset rcvr addr floatValue floatOop |
  	<export: true>
  	<inline: false>
  	<var: #floatValue type:'double '>
  	floatOop := interpreterProxy stackValue: 0.
  	(interpreterProxy isIntegerObject: floatOop)
  		ifTrue:[floatValue := self cCoerce: (interpreterProxy integerValueOf: floatOop) to:'double']
  		ifFalse:[floatValue := self cCoerce: (interpreterProxy floatValueOf: floatOop) to:'double'].
  	byteOffset := interpreterProxy stackIntegerValue: 1.
  	rcvr := interpreterProxy stackObjectValue: 2.
  	interpreterProxy failed ifTrue:[^0].
  	addr := self ffiAddressOf: rcvr startingAt: byteOffset size: 8.
  	interpreterProxy failed ifTrue:[^0].
  	self cCode:'((int*)addr)[0] = ((int*)(&floatValue))[0]'.
  	self cCode:'((int*)addr)[1] = ((int*)(&floatValue))[1]'.
+ 	^interpreterProxy pop: 3 thenPush: floatOop!
- 	interpreterProxy pop: 3 thenPush: floatOop!

Item was changed:
  ----- Method: ThreadedFFIPlugin>>primitiveFFIFloatAtPut (in category 'primitives') -----
  primitiveFFIFloatAtPut
  	"Return a (signed or unsigned) n byte integer from the given byte offset."
  	| byteOffset rcvr addr floatValue floatOop |
  	<export: true>
  	<inline: false>
  	<var: #floatValue type:'float '>
  	floatOop := interpreterProxy stackValue: 0.
  	(interpreterProxy isIntegerObject: floatOop)
  		ifTrue:[floatValue := self cCoerce: (interpreterProxy integerValueOf: floatOop) to:'float']
  		ifFalse:[floatValue := self cCoerce: (interpreterProxy floatValueOf: floatOop) to:'float'].
  	byteOffset := interpreterProxy stackIntegerValue: 1.
  	rcvr := interpreterProxy stackObjectValue: 2.
  	interpreterProxy failed ifTrue:[^0].
  	addr := self ffiAddressOf: rcvr startingAt: byteOffset size: 4.
  	interpreterProxy failed ifTrue:[^0].
  	self cCode:'((int*)addr)[0] = ((int*)(&floatValue))[0]'.
+ 	^interpreterProxy pop: 3 thenPush: floatOop!
- 	interpreterProxy pop: 3 thenPush: floatOop!

Item was changed:
  ----- Method: ThreadedFFIPlugin>>primitiveFFIIntegerAt (in category 'primitives') -----
  primitiveFFIIntegerAt
  	"Return a (signed or unsigned) n byte integer from the given byte offset."
  	| isSigned byteSize byteOffset rcvr addr value mask |
  	<export: true>
  	<inline: false>
  	isSigned := interpreterProxy booleanValueOf: (interpreterProxy stackValue: 0).
  	byteSize := interpreterProxy stackIntegerValue: 1.
  	byteOffset := interpreterProxy stackIntegerValue: 2.
  	rcvr := interpreterProxy stackObjectValue: 3.
  	interpreterProxy failed ifTrue:[^0].
  	(byteOffset > 0 and:[byteSize = 1 or:[byteSize = 2 or:[byteSize = 4]]])
  		ifFalse:[^interpreterProxy primitiveFail].
  	addr := self ffiAddressOf: rcvr startingAt: byteOffset size: byteSize.
  	interpreterProxy failed ifTrue:[^0].
  	byteSize < 4 ifTrue:[
  		"short/byte"
  		byteSize = 1 
  			ifTrue:[value := interpreterProxy byteAt: addr]
  			ifFalse:[	value := self cCode: '*((unsigned short int *) addr)' 
  								inSmalltalk: [interpreterProxy shortAt: addr]].
  		isSigned ifTrue:["sign extend value"
  			mask := 1 << (byteSize * 8 - 1).
  			value := (value bitAnd: mask-1) - (value bitAnd: mask)].
  		"note: byte/short never exceed SmallInteger range"
  		value := interpreterProxy integerObjectOf: value.
  	] ifFalse:[
  		"general 32 bit integer"
  		value := interpreterProxy longAt: addr.
  		value := isSigned
  					ifTrue:[interpreterProxy signed32BitIntegerFor: value]
  					ifFalse:[interpreterProxy positive32BitIntegerFor: value].
  	].
+ 	^interpreterProxy pop: 4 thenPush: value!
- 	interpreterProxy pop: 4 thenPush: value!

Item was changed:
  ----- Method: ThreadedFFIPlugin>>primitiveFFIIntegerAtPut (in category 'primitives') -----
  primitiveFFIIntegerAtPut
  	"Store a (signed or unsigned) n byte integer at the given byte offset."
  	| isSigned byteSize byteOffset rcvr addr value max valueOop |
  	<export: true>
  	<inline: false>
  	isSigned := interpreterProxy booleanValueOf: (interpreterProxy stackValue: 0).
  	byteSize := interpreterProxy stackIntegerValue: 1.
  	valueOop := interpreterProxy stackValue: 2.
  	byteOffset := interpreterProxy stackIntegerValue: 3.
  	rcvr := interpreterProxy stackObjectValue: 4.
  	interpreterProxy failed ifTrue:[^0].
  	(byteOffset > 0 and:[byteSize = 1 or:[byteSize = 2 or:[byteSize = 4]]])
  		ifFalse:[^interpreterProxy primitiveFail].
  	addr := self ffiAddressOf: rcvr startingAt: byteOffset size: byteSize.
  	interpreterProxy failed ifTrue:[^0].
  	isSigned 
  		ifTrue:[value := interpreterProxy signed32BitValueOf: valueOop]
  		ifFalse:[value := interpreterProxy positive32BitValueOf: valueOop].
  	interpreterProxy failed ifTrue:[^0].
  	byteSize < 4 ifTrue:[
  		isSigned ifTrue:[
  			max := 1 << (8 * byteSize - 1).
  			value >= max ifTrue:[^interpreterProxy primitiveFail].
  			value < (0 - max) ifTrue:[^interpreterProxy primitiveFail].
  		] ifFalse:[
  			value >= (1 << (8*byteSize)) ifTrue:[^interpreterProxy primitiveFail].
  		].
  		"short/byte"
  		byteSize = 1 
  			ifTrue:[interpreterProxy byteAt: addr put: value]
  			ifFalse:[	self cCode: '*((short int *) addr) = value' 
  						inSmalltalk: [interpreterProxy shortAt: addr put: value]].
  	] ifFalse:[interpreterProxy longAt: addr put: value].
+ 	^interpreterProxy pop: 5 thenPush: valueOop!
- 	interpreterProxy pop: 5 thenPush: valueOop!

Item was changed:
  ----- Method: ThreadedIA32FFIPlugin>>ffiCalloutTo:SpecOnStack:in: (in category 'callout support') -----
  ffiCalloutTo: procAddr SpecOnStack: specOnStack in: calloutState
  	<var: #procAddr type: #'void *'>
  	<var: #calloutState type: #'CalloutState *'>
  	"Go out, call this guy and create the return value.  This *must* be inlined because of
  	 the alloca of the outgoing stack frame in ffiCall:WithFlags:NumArgs:Args:AndTypes:"
  	| myThreadIndex atomicType floatRet intRet oop |
  	<var: #floatRet type: #double>
  	<var: #intRet type: #usqLong>
  	<inline: true>
  	self cppIf: COGMTVM ifTrue:
  	[(calloutState callFlags anyMask: FFICallFlagThreaded) ifTrue:
  		[myThreadIndex := interpreterProxy disownVM: 0]].
  
  	self registerArgsSlop + self cStackAlignment > 0 ifTrue:
  		[self setsp: calloutState argVector].
  
  	atomicType := self atomicTypeOf: calloutState ffiRetHeader.
  	(atomicType >> 1) = (FFITypeSingleFloat > 1)
  		ifTrue:
  			[floatRet := self dispatchFunctionPointer: (self cCoerceSimple: procAddr to: 'double (*)()')]
  		ifFalse:
  			[intRet := self dispatchFunctionPointer: (self cCoerceSimple: procAddr to: 'usqLong (*)()')].
  	"undo any callee argument pops because it may confuse stack management with the alloca."
  	(self isCalleePopsConvention: calloutState callFlags) ifTrue:
  		[self setsp: calloutState argVector].
  
  	self cppIf: COGMTVM ifTrue:
  	[(calloutState callFlags anyMask: FFICallFlagThreaded) ifTrue:
  		[interpreterProxy ownVM: myThreadIndex]].
  
  	(calloutState ffiRetHeader anyMask: FFIFlagPointer+FFIFlagStructure) ifTrue:
  		["Note: Order is important here since FFIFlagPointer + FFIFlagStructure is used to represent
  		 'typedef void* VoidPointer' and VoidPointer must be returned as pointer *not* as struct."
+ 		 (calloutState ffiRetHeader anyMask: FFIFlagPointer)
- 		^(calloutState ffiRetHeader anyMask: FFIFlagPointer)
  			ifTrue:
+ 				[oop := self ffiReturnPointer: intRet ofType: (self ffiReturnType: specOnStack) in: calloutState]
- 				[self ffiReturnPointer: intRet ofType: (self ffiReturnType: specOnStack) in: calloutState]
  			ifFalse:
+ 				[oop := self ffiReturnStruct: intRet ofType: (self ffiReturnType: specOnStack) in: calloutState].
+ 		 ^oop].
- 				[self ffiReturnStruct: intRet ofType: (self ffiReturnType: specOnStack) in: calloutState]].
  	
  	(atomicType >> 1) = (FFITypeSingleFloat > 1)
  		ifTrue:
  			[oop := interpreterProxy floatObjectOf: floatRet]
  		ifFalse:
  			[oop := self ffiCreateIntegralResultOop: intRet
  						ofAtomicType: atomicType
  						in: calloutState].
  	^interpreterProxy methodReturnValue: oop!



More information about the Vm-dev mailing list