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

commits at source.squeak.org commits at source.squeak.org
Thu Jan 23 08:28:11 UTC 2020


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

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

Name: VMMaker.oscog-eem.2672
Author: eem
Time: 23 January 2020, 12:27:52.451046 am
UUID: 335f401c-b41b-48dc-b7be-2d33156978af
Ancestors: VMMaker.oscog-eem.2671

Slang/Cogit:
Declare the ceTryLockVMOwner & ceUnlockVMOwner routines as conditional on COGMTVM (as they should be).  Clean up the variable emission code to handle this kind of (ugly) hack more cleanly.  Fixes a regression introduced by VMMaker.oscog-eem.2671 where these variables would be mis-declared as sqInts in COGMTVM=0 compiles.

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

Item was changed:
  ----- Method: CCodeGenerator>>emitCVariablesOn: (in category 'C code generator') -----
  emitCVariablesOn: aStream 
  	"Store the global variable declarations on the given stream."
  
  	aStream cr; nextPutAll: '/*** Variables ***/'; cr.
  	(self sortStrings: variables) do:
+ 		[:var | | varString |
+ 		(self variableDeclarationStringsForVariable: (varString := var asString)) do:
+ 			[:declArg| | decl |		
+ 			(decl := declArg) first == $#
+ 				ifTrue:
+ 					[aStream nextPutAll: decl; cr]
+ 				ifFalse:
+ 					[self isGeneratingPluginCode
+ 						ifTrue:
+ 							[varString = 'interpreterProxy'
+ 								ifTrue: "quite special..."
+ 									[self preDeclareInterpreterProxyOn: aStream]
+ 								ifFalse: [(decl beginsWith: 'static') ifFalse:
+ 											[aStream nextPutAll: 'static ']]]
+ 						ifFalse:
+ 							[(vmClass mustBeGlobal: varString)
+ 								ifTrue:
+ 									[(decl beginsWith: 'static ') ifTrue:
+ 										[decl := decl allButFirst: 7]]
+ 								ifFalse:
+ 									[(decl beginsWith: 'static') ifFalse:
+ 										[aStream nextPutAll: 'static ']]].
+ 					aStream
+ 						nextPutAll: decl;
+ 						nextPut: $;;
+ 						cr]]].
- 		[:var | | varString decl |
- 		varString := var asString.
- 		decl := variableDeclarations at: varString ifAbsent: ['sqInt ' , varString].
- 		decl first == $# "support cgen var: #bytecodeSetSelector declareC: '#define bytecodeSetSelector 0' hack"
- 			ifTrue:
- 				[aStream nextPutAll: decl; cr]
- 			ifFalse:
- 				[self isGeneratingPluginCode
- 					ifTrue:
- 						[varString = 'interpreterProxy'
- 							ifTrue: "quite special..."
- 								[self preDeclareInterpreterProxyOn: aStream]
- 							ifFalse: [(decl beginsWith: 'static') ifFalse:
- 										[aStream nextPutAll: 'static ']]]
- 					ifFalse:
- 						[(vmClass mustBeGlobal: varString)
- 							ifTrue:
- 								[(decl beginsWith: 'static ') ifTrue:
- 									[decl := decl allButFirst: 7]]
- 							ifFalse:
- 								[(decl beginsWith: 'static') ifFalse:
- 									[aStream nextPutAll: 'static ']]].
- 				aStream
- 					nextPutAll: decl;
- 					nextPut: $;;
- 					cr]].
  	aStream cr!

Item was changed:
  ----- Method: CCodeGenerator>>emitGlobalCVariablesOn: (in category 'C code generator') -----
  emitGlobalCVariablesOn: aStream
+ 	"Store the global (exported) variable declarations on the given stream."
- 	"Store the global variable declarations on the given stream."
  
  	aStream cr; nextPutAll: '/*** Global Variables ***/'; cr.
  	
  	(self sortStrings: (variables select: [:v| vmClass mustBeGlobal: v])) do:
+ 		[:var | | varString |
+ 		(self variableDeclarationStringsForVariable: (varString := var asString)) do:
+ 			[:decl|
+ 			decl first == $#
+ 				ifTrue:
+ 					[aStream nextPutAll: decl; cr]
+ 				ifFalse:
+ 					[(decl includesSubstring: ' private ') ifFalse: "work-around hack to prevent localization of variables only referenced once."
+ 						[(decl beginsWith: 'static') ifFalse: [aStream nextPutAll: 'VM_EXPORT '].
+ 						aStream
+ 							nextPutAll:
+ 								((decl includes: $=)
+ 									ifTrue: [decl copyFrom: 1 to: (decl indexOf: $=) - 1]
+ 									ifFalse: [decl]);
+ 							nextPut: $;;
+ 							cr]]]].
- 		[:var | | varString decl |
- 		varString := var asString.
- 		decl := variableDeclarations at: varString ifAbsent: ['sqInt ' , varString].
- 		decl first == $# "support cgen var: #bytecodeSetSelector declareC: '#define bytecodeSetSelector 0' hack"
- 			ifTrue:
- 				[aStream nextPutAll: decl; cr]
- 			ifFalse:
- 				[(decl includesSubstring: ' private ') ifFalse: "work-around hack to prevent localization of variables only referenced once."
- 					[(decl beginsWith: 'static') ifFalse: [aStream nextPutAll: 'VM_EXPORT '].
- 					(decl includes: $=) ifTrue:
- 						[decl := decl copyFrom: 1 to: (decl indexOf: $=) - 1].
- 					aStream
- 						nextPutAll: decl;
- 						nextPut: $;;
- 						cr]]].
  	aStream cr!

Item was added:
+ ----- Method: CCodeGenerator>>variableDeclarationStringsForVariable: (in category 'C translation support') -----
+ variableDeclarationStringsForVariable: variableNameString
+ 	"We (have to?) abuse declarations for optionality using #if C preprocessor forms.
+ 	 This is ugly, but difficult to avoid.  This routine answers either a single string declaration
+ 	 for a variable declared without one of these hacks, or returns the declaration split up into lines."
+ 	| declString |
+ 	declString := variableDeclarations at: variableNameString ifAbsent: [^{'sqInt ', variableNameString}].
+ 	^(declString includes: $#)
+ 		ifTrue: [declString findTokens: Character cr]
+ 		ifFalse: [{declString}]!

Item was changed:
  ----- Method: CCodeGeneratorGlobalStructure>>emitCVariablesOn: (in category 'C code generator') -----
  emitCVariablesOn: aStream
  	"Store the global variable declarations on the given stream.
  	 Break logic into vars for structure and vars for non-structure."
  	| structure nonstruct |
  
  	structure := WriteStream on: (String new: 32768).
  	nonstruct := WriteStream on: (String new: 32768).
  	aStream nextPutAll: '/*** Variables ***/'; cr.
  	structure
  		nextPutAll: '#if SQ_USE_GLOBAL_STRUCT'; cr;
  		nextPutAll: '# define _iss /* define in-struct static as void */'; cr;
  		nextPutAll: 'static struct foo {'; cr;
  		nextPutAll: '#else'; cr;
  		nextPutAll: '# define _iss static'; cr;
  		nextPutAll: '#endif'; cr.
  	self buildSortedVariablesCollection do:
+ 		[ :var | | varString inStruct target |
- 		[ :var | | decl varString inStruct target |
  		target := (inStruct := self placeInStructure: (varString := var asString)) 
  					ifTrue: [structure]
  					ifFalse: [nonstruct].
+ 		(self variableDeclarationStringsForVariable: varString) do:
+ 			[:decl|
+ 			 decl first == $#
+ 				ifTrue:
+ 					[target nextPutAll: decl; cr]
+ 				ifFalse:
+ 					[self isGeneratingPluginCode
+ 						ifTrue:
+ 							[varString = 'interpreterProxy'
+ 								ifTrue: "quite special..."
+ 									[self preDeclareInterpreterProxyOn: target]
+ 								ifFalse: [target nextPutAll: 'static ']]
+ 						ifFalse:
+ 							[(vmClass mustBeGlobal: varString) ifFalse:
+ 								[target nextPutAll: (inStruct ifTrue: ['_iss '] ifFalse: ['static '])]].
+ 					target nextPutAll: decl; nextPut: $;; cr]]].
- 		decl := variableDeclarations at: varString ifAbsent: ['sqInt ' , varString].
- 		decl first == $# "support cgen var: #bytecodeSetSelector declareC: '#define bytecodeSetSelector 0' hack"
- 			ifTrue:
- 				[target nextPutAll: decl; cr]
- 			ifFalse:
- 				[self isGeneratingPluginCode
- 					ifTrue:
- 						[varString = 'interpreterProxy'
- 							ifTrue: "quite special..."
- 								[self preDeclareInterpreterProxyOn: target]
- 							ifFalse: [target nextPutAll: 'static ']]
- 					ifFalse:
- 						[(vmClass mustBeGlobal: varString) ifFalse:
- 							[target nextPutAll: (inStruct ifTrue: ['_iss '] ifFalse: ['static '])]].
- 				target nextPutAll: decl; nextPut: $;; cr]].
  	structure
  		nextPutAll: '#undef _iss'; cr;
  		nextPutAll: '#if SQ_USE_GLOBAL_STRUCT'; cr;
  		nextPutAll: ' } fum;'; cr;
  		nextPutAll: ' #if SQ_USE_GLOBAL_STRUCT_REG';cr;
  		nextPutAll: '# define DECL_MAYBE_SQ_GLOBAL_STRUCT /* using a global reg pointer */'; cr;
  		nextPutAll: '# define DECL_MAYBE_VOLATILE_SQ_GLOBAL_STRUCT /* using a global reg pointer */'; cr;
  		nextPutAll:'#else';cr;
  		nextPutAll: '# define DECL_MAYBE_SQ_GLOBAL_STRUCT register struct foo * foo = &fum;'; cr;
  		nextPutAll: '# define DECL_MAYBE_VOLATILE_SQ_GLOBAL_STRUCT volatile register struct foo * foo = &fum;'; cr;
  		nextPutAll: '#endif';cr;
  		nextPutAll: '# define GIV(interpreterInstVar) (foo->interpreterInstVar)'; cr;
  		nextPutAll: '#else'; cr;
  		nextPutAll: '# define DECL_MAYBE_SQ_GLOBAL_STRUCT /* oh, no mr bill!! */'; cr;
  		nextPutAll: '# define DECL_MAYBE_VOLATILE_SQ_GLOBAL_STRUCT /* oh no, mr bill!! */'; cr;
  		nextPutAll: '# define GIV(interpreterInstVar) interpreterInstVar'; cr;
  		nextPutAll: '#endif'; cr.
  
  	"if the machine needs the fum structure defining locally, do it now; global register users don't need that, but DO need some batshit insane C macro fudging in order to convert the define of USE_GLOBAL_STRUCT_REG into a simple string to use in the asm clause below. Sigh."
  	structure
  		nextPutAll: '#if SQ_USE_GLOBAL_STRUCT'; cr;
  		nextPutAll: '#if SQ_USE_GLOBAL_STRUCT_REG';cr;
  		nextPutAll: '#define fooxstr(s) foostr(s)'; cr;
  		nextPutAll: '#define foostr(s)  #s'; cr;
  		nextPutAll: 'register struct foo * foo asm(fooxstr(USE_GLOBAL_STRUCT_REG));'; cr;
  		nextPutAll: '#else'; cr;
  		nextPutAll: 'static struct foo * foo = &fum;'; cr;
  		nextPutAll: '#endif'; cr;
  		nextPutAll: '#endif'; cr.
  
  	aStream
  		nextPutAll: structure contents;
  		nextPutAll: nonstruct contents;
  		cr!

Item was changed:
  ----- Method: Cogit class>>declareCVarsIn: (in category 'translation') -----
  declareCVarsIn: aCCodeGenerator
  	#(	'coInterpreter' 'objectMemory' 'methodZone' 'objectRepresentation'
  		'cogBlockMethodSurrogateClass' 'cogMethodSurrogateClass' 'nsSendCacheSurrogateClass'
  		'threadManager' 'processor' 'lastNInstructions' 'simulatedAddresses'
  		'simulatedTrampolines' 'simulatedVariableGetters' 'simulatedVariableSetters'
  		'processorFrameValid' 'printRegisters' 'printInstructions' 'clickConfirm' 'singleStep') do:
  			[:simulationVariableNotNeededForRealVM|
  			aCCodeGenerator removeVariable: simulationVariableNotNeededForRealVM].
  	NewspeakVM ifFalse:
  		[#(	'selfSendTrampolines' 'dynamicSuperSendTrampolines'
  			'implicitReceiverSendTrampolines' 'outerSendTrampolines'
  			'ceEnclosingObjectTrampoline' 'numIRCs' 'indexOfIRC' 'theIRCs') do:
  				[:variableNotNeededInNormalVM|
  				aCCodeGenerator removeVariable: variableNotNeededInNormalVM]].
  	aCCodeGenerator removeConstant: #COGMTVM. "this should be defined at compile time"
  	aCCodeGenerator
  		addHeaderFile:'<stddef.h>'; "for e.g. offsetof"
  		addHeaderFile:'"sqCogStackAlignment.h"';
  		addHeaderFile:'"dispdbg.h"'; "must precede cointerp.h & cogit.h otherwise NoDbgRegParms gets screwed up"
  		addHeaderFile:'"cogmethod.h"'.
  	NewspeakVM ifTrue:
  		[aCCodeGenerator addHeaderFile:'"nssendcache.h"'].
  	aCCodeGenerator
  		addHeaderFile:'#if COGMTVM';
  		addHeaderFile:'"cointerpmt.h"';
  		addHeaderFile:'#else';
  		addHeaderFile:'"cointerp.h"';
  		addHeaderFile:'#endif';
  		addHeaderFile:'"cogit.h"'.
  	aCCodeGenerator
  		var: #ceGetFP
  			declareC: 'usqIntptr_t (*ceGetFP)(void)';
  		var: #ceGetSP
  			declareC: 'usqIntptr_t (*ceGetSP)(void)';
  		var: #ceCaptureCStackPointers
  			declareC: 'void (*ceCaptureCStackPointers)(void)';
  		var: #ceEnterCogCodePopReceiverReg
  			declareC: 'void (*ceEnterCogCodePopReceiverReg)(void)';
  		var: #realCEEnterCogCodePopReceiverReg
  			declareC: 'void (*realCEEnterCogCodePopReceiverReg)(void)';
  		var: #ceCallCogCodePopReceiverReg
  			declareC: 'void (*ceCallCogCodePopReceiverReg)(void)';
  		var: #realCECallCogCodePopReceiverReg
  			declareC: 'void (*realCECallCogCodePopReceiverReg)(void)';
  		var: #ceCallCogCodePopReceiverAndClassRegs
  			declareC: 'void (*ceCallCogCodePopReceiverAndClassRegs)(void)';
  		var: #realCECallCogCodePopReceiverAndClassRegs
  			declareC: 'void (*realCECallCogCodePopReceiverAndClassRegs)(void)';
  		var: #postCompileHook
  			declareC: 'void (*postCompileHook)(CogMethod *)';
  		var: #openPICList declareC: 'CogMethod *openPICList = 0';
  		var: #maxMethodBefore type: #'CogBlockMethod *';
  		var: 'enumeratingCogMethod' type: #'CogMethod *'.
  	
+ 	aCCodeGenerator
+ 		var: #ceTryLockVMOwner
+ 			declareC: '#if COGMTVM\usqIntptr_t (*ceTryLockVMOwner)(void)' withCRs;
+ 		var: #ceUnlockVMOwner
+ 			declareC: 'void (*ceUnlockVMOwner)(void)\#endif /* COGMTVM */' withCRs.
+ 
- 	COGMTVM ifTrue:
- 		[aCCodeGenerator
- 			var: #ceUnlockVMOwner
- 				declareC: 'void (*ceUnlockVMOwner)(void)';
- 			var: #ceTryLockVMOwner
- 				declareC: 'usqIntptr_t (*ceTryLockVMOwner)(void)'].
  	CogCompilerClass basicNew numCheckLZCNTOpcodes > 0 ifTrue:
  		[aCCodeGenerator
  			var: #ceCheckLZCNTFunction
  				declareC: 'static usqIntptr_t (*ceCheckLZCNTFunction)(void)'].
  	CogCompilerClass basicNew numCheckFeaturesOpcodes > 0 ifTrue:
  		[aCCodeGenerator
  			var: #ceCheckFeaturesFunction
  				declareC: 'static usqIntptr_t (*ceCheckFeaturesFunction)(void)'].
  	CogCompilerClass basicNew numICacheFlushOpcodes > 0 ifTrue:
  		[aCCodeGenerator
  			var: #ceFlushICache
  				declareC: 'static void (*ceFlushICache)(usqIntptr_t from, usqIntptr_t to)'].
  
  	aCCodeGenerator
  		declareVar: 'aMethodLabel' type: #'AbstractInstruction'; "Has to come lexicographically before backEnd & methodLabel"
  		var: #backEnd declareC: 'AbstractInstruction * const backEnd = &aMethodLabel';
  		var: #methodLabel declareC: 'AbstractInstruction * const methodLabel = &aMethodLabel'.
  	self declareC: #(abstractOpcodes stackCheckLabel
  					blockEntryLabel blockEntryNoContextSwitch
  					stackOverflowCall sendMiss
  					entry noCheckEntry selfSendEntry dynSuperEntry
  					fullBlockNoContextSwitchEntry fullBlockEntry
  					picMNUAbort picInterpretAbort  endCPICCase0 endCPICCase1 cPICEndOfCodeLabel)
  			as: #'AbstractInstruction *'
  				in: aCCodeGenerator.
  	aCCodeGenerator
  		declareVar: #blockStarts type: #'BlockStart *';
  		declareVar: #fixups type: #'BytecodeFixup *'.
  	aCCodeGenerator
  		var: #ordinarySendTrampolines
  			declareC: 'sqInt ordinarySendTrampolines[NumSendTrampolines]';
  		var: #superSendTrampolines
  			declareC: 'sqInt superSendTrampolines[NumSendTrampolines]'.
  	BytecodeSetHasDirectedSuperSend ifTrue:
  		[aCCodeGenerator
  			var: #directedSuperSendTrampolines
  				declareC: 'sqInt directedSuperSendTrampolines[NumSendTrampolines]';
  			var: #directedSuperBindingSendTrampolines
  				declareC: 'sqInt directedSuperBindingSendTrampolines[NumSendTrampolines]'].
  	NewspeakVM ifTrue:
  		[aCCodeGenerator
  			var: #selfSendTrampolines
  				declareC: 'sqInt selfSendTrampolines[NumSendTrampolines]';
  			var: #dynamicSuperSendTrampolines
  				declareC: 'sqInt dynamicSuperSendTrampolines[NumSendTrampolines]';
  			var: #implicitReceiverSendTrampolines
  				declareC: 'sqInt implicitReceiverSendTrampolines[NumSendTrampolines]';
  			var: #outerSendTrampolines
  				declareC: 'sqInt outerSendTrampolines[NumSendTrampolines]'].
  	aCCodeGenerator
  		var: #trampolineAddresses
  			declareC: 'static char *trampolineAddresses[NumTrampolines*2]';
  		var: #objectReferencesInRuntime
  			declareC: 'static usqInt objectReferencesInRuntime[NumObjRefsInRuntime+1]';
  		var: #labelCounter
  			type: #int;
  		var: #traceFlags
  			declareC: 'int traceFlags = 8 /* prim trace log on by default */';
  		var: #cStackAlignment
  			declareC: 'const int cStackAlignment = STACK_ALIGN_BYTES'.
  	aCCodeGenerator
  		declareVar: #minValidCallAddress type: #'usqIntptr_t';
  		declareVar: #debugPrimCallStackOffset type: #'usqIntptr_t'.
  	aCCodeGenerator vmClass generatorTable ifNotNil:
  		[:bytecodeGenTable|
  		aCCodeGenerator
  			var: #generatorTable
  				declareC: 'static BytecodeDescriptor generatorTable[', bytecodeGenTable size printString, ']',
  							(self tableInitializerFor: bytecodeGenTable
  								in: aCCodeGenerator)].
  	"In C the abstract opcode names clash with the Smalltak generator syntactic sugar.
  	 Most of the syntactic sugar is inlined, but alas some remains.  Rename the syntactic
  	 sugar to avoid the clash."
  	(self organization listAtCategoryNamed: #'abstract instructions') do:
  		[:s|
  		aCCodeGenerator addSelectorTranslation: s to: 'g', (aCCodeGenerator cFunctionNameFor: s)].
  	aCCodeGenerator addSelectorTranslation: #halt: to: 'haltmsg'!



More information about the Vm-dev mailing list