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

commits at source.squeak.org commits at source.squeak.org
Thu May 31 03:42:53 UTC 2018


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

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

Name: VMMaker.oscog-eem.2398
Author: eem
Time: 30 May 2018, 8:42:12.26673 pm
UUID: 5065644b-1af9-4f57-a2d0-427fd5f0e20b
Ancestors: VMMaker.oscog-eem.2397

Have Slang serve is rather than we work-around Slang, in as much as Slang now outputs any ext5ern ... declaration, so we no longer need a fake temp var with associated crap to keep the compiler happy.

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

Item was changed:
  ----- Method: CogARMCompiler>>aeabiDivModFunctionAddr (in category 'ARM convenience instructions') -----
  aeabiDivModFunctionAddr
+ 	"Answer the address of the __aeabi_idivmod() call provided by the ARM low level libs to do an integer divide that returns the quo in R0 and rem in R1.
+ 	 A word on the somewhat strange usage of idivmod herein; we need a declaration for the _aeabi_idivmod helper function, despite the fact that in a simple C program test, you don't.
+ 	 To get that declaration we need a variable to hang it off; thus the non-existent var idivmod, and in simulation we need to simulate it, which is what aeabiDiv:Mod: does."
- "return the address of the __aeabi_idivmod() call provided by the ARM low level libs to do an integer divide that returns the quo in R0 and rem in R1.
- A word on the somewhat strange usage of idivmod herein; we need a declaration for the _aeabi_idivmod helper function, despite the fact that in a simple C program test, you don't. To get that declaration we need a variable to hang it off and said variable needs to be referred to in order to not get culled. Thus the temp var idivmod, the declaration for it that has nothing to do with it and the odd usage in the inSmalltalk: block."
- 	| idivmod |
  	<returnTypeC: #usqInt>
  	<var: #idivmod declareC: 'extern void __aeabi_idivmod(int dividend, int divisor)'>
  
+ 	^self cCode: '(usqInt)__aeabi_idivmod' inSmalltalk:[#aeabiDiv:Mod:]!
- 	^self cCode: '(usqInt)__aeabi_idivmod' inSmalltalk:[idivmod := #aeabiDiv:Mod:]!

Item was changed:
  ----- Method: StackInterpreter>>ownVM: (in category 'vm scheduling') -----
  ownVM: threadIndexAndFlags
  	<api>
  	<inline: false>
  	"This is the entry-point for plugins and primitives that wish to reacquire the VM after having
  	 released it via disownVM or callbacks that want to acquire it without knowing their ownership
  	 status.  While this exists for the threaded FFI VM we use it to reset newMethod and the
  	 argumentCount after a callback.
  
  	 Answer the argumentCount encoded as a SmallInteger if the current thread is the VM thread.
  	 Answer -1 if the current thread is unknown to the VM and fails to take ownership."
- 	| amInVMThread |
  	<var: 'amInVMThread' declareC: 'extern sqInt amInVMThread(void)'>
- 	self cCode: [] inSmalltalk: [amInVMThread := 1. amInVMThread class].
  	self amInVMThread ifFalse:
  		[^-1].
  	self assert: primFailCode = 0.
  	self assert: ((objectMemory isOopCompiledMethod: newMethod)
  				and: [(self argumentCountOf: newMethod) = argumentCount]).
  	self push: newMethod.
  	^objectMemory integerObjectOf: argumentCount!

Item was changed:
  ----- Method: TMethod>>emitCLocalsOn:generator: (in category 'C code generation') -----
  emitCLocalsOn: aStream generator: aCodeGen
  	"Emit a C function header for this method onto the given stream."
  
+ 	| volatileVariables maybeExternFunctions |
- 	| volatileVariables |
  	volatileVariables := properties includesKey: #volatile.
  	self refersToGlobalStruct ifTrue:
  		[aStream
  			next: 3 put: Character space; "there's already an opening ${ on this line; see sender"
  			nextPutAll: (volatileVariables
  						ifTrue: ['DECL_MAYBE_VOLATILE_SQ_GLOBAL_STRUCT']
  						ifFalse: ['DECL_MAYBE_SQ_GLOBAL_STRUCT'])].
  	aStream cr.
+ 	maybeExternFunctions := (declarations select: [:decl| decl beginsWith: 'extern']) keys.
+ 	(locals isEmpty and: [maybeExternFunctions isEmpty]) ifFalse:
+ 		[(aCodeGen sortStrings: locals, maybeExternFunctions) do:
- 	locals isEmpty ifFalse:
- 		[(aCodeGen sortStrings: locals) do:
  			[ :var | | decl |
  			decl := self declarationAt: var.
  			(volatileVariables
  			 or: [(decl beginsWith: 'static')
  			 or: [(decl beginsWith: 'extern')
  			 or: [usedVariablesCache includes: var]]]) ifTrue:
  				[aStream next: 4 put: Character space.
  				 volatileVariables ifTrue:
  					[aStream nextPutAll: #volatile; space].
  				 aStream
  					nextPutAll: decl;
  					nextPut: $;;
  					cr]].
  		 aStream cr]!

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 |
- 	| myThreadIndex atomicType floatRet intRet loadFloatRegs |
  	<var: #floatRet type: #double>
  	<var: #intRet type: #usqLong>
  	<inline: true>
- 	self cCode: '' inSmalltalk: [loadFloatRegs := #used. loadFloatRegs class].
  	self maybeDisownVM: calloutState threadIndexInto: [:threadIndex| myThreadIndex := threadIndex].
  
  	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)].
  
  	(self allocaLiesSoSetSpBeforeCall or: [self mustAlignStack]) ifTrue:
  		[self setsp: calloutState argVector].
  
  	atomicType := self atomicTypeOf: calloutState ffiRetHeader.
  	(atomicType >> 1) = (FFITypeSingleFloat >> 1) ifTrue:
  		[atomicType = FFITypeSingleFloat
  			ifTrue:
  				[floatRet := self 
  					dispatchFunctionPointer: (self cCoerceSimple: procAddr to: 'float (*)(sqIntptr_t, sqIntptr_t, sqIntptr_t, sqIntptr_t)') 
  					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 (*)(sqIntptr_t, sqIntptr_t, sqIntptr_t, sqIntptr_t)') 
  					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 maybeOwnVM: calloutState threadIndex: myThreadIndex.
  
  		 ^interpreterProxy floatObjectOf: floatRet].
  
  	intRet := self 
  				dispatchFunctionPointer: (self cCoerceSimple: procAddr to: 'usqIntptr_t (*)(sqIntptr_t, sqIntptr_t, sqIntptr_t, sqIntptr_t)') 
  				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 maybeOwnVM: calloutState threadIndex: 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) ifTrue:
  			[^self ffiReturnPointer: intRet ofType: (self ffiReturnType: specOnStack) in: calloutState].
  		 ^self ffiReturnStruct: intRet ofType: (self ffiReturnType: specOnStack) in: calloutState].
  	
  	^self ffiCreateIntegralResultOop: intRet ofAtomicType: atomicType in: calloutState!

Item was changed:
  ----- Method: ThreadedX64SysVFFIPlugin>>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 |
- 	| myThreadIndex atomicType floatRet intRet loadFloatRegs |
  	<var: #floatRet type: #double>
  	<var: #intRet type: #SixteenByteReturn>
  	<inline: true>
- 	self cCode: '' inSmalltalk: [loadFloatRegs := #used. loadFloatRegs class].
  	self maybeDisownVM: calloutState threadIndexInto: [:threadIndex| myThreadIndex := threadIndex].
  
  	calloutState floatRegisterIndex > 0 ifTrue:
  		[self 
  			load: (calloutState floatRegisters at: 0)
  			Flo: (calloutState floatRegisters at: 1)
  			a: (calloutState floatRegisters at: 2)
  			t: (calloutState floatRegisters at: 3)
  			R: (calloutState floatRegisters at: 4)
  			e: (calloutState floatRegisters at: 5)
  			g: (calloutState floatRegisters at: 6)
  			s: (calloutState floatRegisters at: 7)].
  
  	(self allocaLiesSoSetSpBeforeCall or: [self mustAlignStack]) ifTrue:
  		[self setsp: calloutState argVector].
  
  	atomicType := self atomicTypeOf: calloutState ffiRetHeader.
  	(atomicType >> 1) = (FFITypeSingleFloat >> 1) ifTrue:
  		[atomicType = FFITypeSingleFloat
  			ifTrue:
  				[floatRet := self 
  					dispatchFunctionPointer: (self cCoerceSimple: procAddr to: 'float (*)(sqIntptr_t, sqIntptr_t, sqIntptr_t, sqIntptr_t, sqIntptr_t, sqIntptr_t)') 
  					with: (calloutState integerRegisters at: 0)
  					with: (calloutState integerRegisters at: 1)
  					with: (calloutState integerRegisters at: 2)
  					with: (calloutState integerRegisters at: 3)
  					with: (calloutState integerRegisters at: 4)
  					with: (calloutState integerRegisters at: 5)]
  			ifFalse: "atomicType = FFITypeDoubleFloat"
  				[floatRet := self 
  					dispatchFunctionPointer: (self cCoerceSimple: procAddr to: 'double (*)(sqIntptr_t, sqIntptr_t, sqIntptr_t, sqIntptr_t, sqIntptr_t, sqIntptr_t)') 
  					with: (calloutState integerRegisters at: 0)
  					with: (calloutState integerRegisters at: 1)
  					with: (calloutState integerRegisters at: 2)
  					with: (calloutState integerRegisters at: 3)
  					with: (calloutState integerRegisters at: 4)
  					with: (calloutState integerRegisters at: 5)].
  
  		 self maybeOwnVM: calloutState threadIndex: myThreadIndex.
  
  		 ^interpreterProxy floatObjectOf: floatRet].
  
  	intRet := self 
  				dispatchFunctionPointer: (self cCoerceSimple: procAddr to: 'SixteenByteReturn (*)(sqIntptr_t, sqIntptr_t, sqIntptr_t, sqIntptr_t, sqIntptr_t, sqIntptr_t)') 
  				with: (calloutState integerRegisters at: 0)
  				with: (calloutState integerRegisters at: 1)
  				with: (calloutState integerRegisters at: 2)
  				with: (calloutState integerRegisters at: 3)
  				with: (calloutState integerRegisters at: 4)
  				with: (calloutState integerRegisters at: 5).
  
  	self maybeOwnVM: calloutState threadIndex: 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) ifTrue:
  			[^self ffiReturnPointer: intRet a ofType: (self ffiReturnType: specOnStack) in: calloutState].
  		 ^self ffiReturnStruct: intRet ofType: (self ffiReturnType: specOnStack) in: calloutState].
  	
  	^self ffiCreateIntegralResultOop: intRet a ofAtomicType: atomicType in: calloutState!

Item was changed:
  ----- Method: ThreadedX64Win64FFIPlugin>>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)'>
  	"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 |
- 	| myThreadIndex atomicType floatRet intRet loadFloatRegs |
  	<var: #floatRet type: #double>
  	<var: #intRet type: #usqLong>
  	<inline: true>
- 	self cCode: '' inSmalltalk: [loadFloatRegs := #used. loadFloatRegs class].
  	self maybeDisownVM: calloutState threadIndexInto: [:threadIndex| myThreadIndex := threadIndex].
  
  	calloutState floatRegisterSignature > 0 ifTrue:
  		[self 
  			load: (calloutState floatRegisters at: 0)
  			Flo: (calloutState floatRegisters at: 1)
  			at: (calloutState floatRegisters at: 2)
  			Re: (calloutState floatRegisters at: 3)
  			gs: (calloutState floatRegisters at: 4)].
  
  	(self allocaLiesSoSetSpBeforeCall or: [self mustAlignStack]) ifTrue:
  		[self setsp: calloutState argVector].
  
  	atomicType := self atomicTypeOf: calloutState ffiRetHeader.
  	(atomicType >> 1) = (FFITypeSingleFloat >> 1) ifTrue:
  		[atomicType = FFITypeSingleFloat
  			ifTrue:
  				[floatRet := self 
  					dispatchFunctionPointer: (self cCoerceSimple: procAddr to: 'float (*)(sqIntptr_t, sqIntptr_t, sqIntptr_t, sqIntptr_t)') 
  					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 (*)(sqIntptr_t, sqIntptr_t, sqIntptr_t, sqIntptr_t)') 
  					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 maybeOwnVM: calloutState threadIndex: myThreadIndex.
  
  		 ^interpreterProxy floatObjectOf: floatRet].
  
  	intRet := self 
  				dispatchFunctionPointer: (self cCoerceSimple: procAddr to: 'usqIntptr_t (*)(sqIntptr_t, sqIntptr_t, sqIntptr_t, sqIntptr_t)') 
  				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 maybeOwnVM: calloutState threadIndex: 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) ifTrue:
  			[^self ffiReturnPointer: intRet ofType: (self ffiReturnType: specOnStack) in: calloutState].
  		 ^self ffiReturnStruct: intRet ofType: (self ffiReturnType: specOnStack) in: calloutState].
  	
  	^self ffiCreateIntegralResultOop: intRet ofAtomicType: atomicType in: calloutState!



More information about the Vm-dev mailing list