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

commits at source.squeak.org commits at source.squeak.org
Mon Feb 3 23:26:32 UTC 2020


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

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

Name: VMMaker.oscog-eem.2699
Author: eem
Time: 3 February 2020, 3:26:15.630866 pm
UUID: dc6180ae-b25f-4ece-9834-af9793616fbf
Ancestors: VMMaker.oscog-eem.2698

Cogit:
Fix a regression in generateCaptureCStackPointers: (TempReg is used and TempReg is a caller-saced reg, so if TempReg is used to save VarBaseReg, VarBaseReg will get corrupted.

Make sure VarBase is different from stackPointerAddress so that assembler decoration is not confusing.

As a displacement activity from implementing the range of cache flusing required for the dual mapped code zone, sort variables by size so that they occupy a little less space.

The reenterInterpreter does *not* need to be exported.

Nuke unused Cogit Lowcode vars when not generating a LowcodeVM.

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

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 segregateByGroupingSizeAndVisibility: (self sortStrings: variables)) do:
- 	(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]]].
  	aStream cr!

Item was added:
+ ----- Method: CCodeGenerator>>hasVariable: (in category 'utilities') -----
+ hasVariable: variableName
+ 	^variables includes: variableName!

Item was added:
+ ----- Method: CCodeGenerator>>segregateByGroupingSizeAndVisibility: (in category 'utilities') -----
+ segregateByGroupingSizeAndVisibility: variables
+ 	"Sort variables by grouping (clusteredVariables first), by size (pointer & integer
+ 	 vars sorted from defaultWordSize to bytes), and finally by size, public last.  The
+ 	 intent is to group smaller variables together for better locality (because we can)."
+ 	| clusteredVariableNames streams defaultStream defaultWordSize groupedBySize privateStream publicStream |
+ 	clusteredVariableNames := ([vmClass clusteredVariableNames]
+ 									on: MessageNotUnderstood
+ 									do: [:ex| #()]).
+ 	streams := (1 to: 8) collect: [:i| i isPowerOfTwo ifTrue: [(Array new: variables size // 2) writeStream]].
+ 	defaultStream := (Array new: variables size // 2) writeStream.
+ 	defaultWordSize := vmClass ifNotNil: [vmClass objectMemoryClass wordSize] ifNil: 8. "We now live in a 64-bit"
+ 	variables do:
+ 		[:varName| | type |
+ 		(clusteredVariableNames includes: varName) ifFalse:
+ 			[type := variableDeclarations
+ 						at: varName
+ 						ifPresent: [:decl| self extractTypeFor: varName fromDeclaration: decl]
+ 						ifAbsent: [#sqInt].
+ 			 ((self isSimpleType: type)
+ 				ifTrue: [streams at: ((self isPointerCType: type)
+ 										ifTrue: [defaultWordSize]
+ 										ifFalse: [self sizeOfIntegralCType: type])]
+ 				ifFalse: [defaultStream])
+ 					nextPut: varName]].
+ 	groupedBySize := Array new: variables size streamContents:
+ 						[:varStream|
+ 						varStream
+ 							nextPutAll: clusteredVariableNames;
+ 							nextPutAll: (streams at: defaultWordSize) contents;
+ 							nextPutAll: (streams at: (defaultWordSize = 8 ifTrue: [4] ifFalse: [8])) contents;
+ 							nextPutAll: (streams at: 2) contents;
+ 							nextPutAll: (streams at: 1) contents;
+ 							nextPutAll: defaultStream contents].
+ 	publicStream := (Array new: variables size // 2) writeStream.
+ 	privateStream := (Array new: variables size // 2) writeStream.
+ 	groupedBySize do:
+ 		[:varName|
+ 		(((self mustBeGlobal: varName) or: [clusteredVariableNames includes: varName])
+ 			ifTrue: [publicStream]
+ 			ifFalse: [privateStream]) nextPut: varName].
+ 	^privateStream contents, publicStream contents!

Item was changed:
  ----- Method: CCodeGeneratorGlobalStructure>>buildSortedVariablesCollection (in category 'C code generator') -----
  buildSortedVariablesCollection
  	"Build sorted vars, end result will be sorted collection based on static usage, 
  	perhaps cache lines will like this!!"
  
  	| globalNames |
  	globalNames := Bag new: globalVariableUsage size.
  	globalVariableUsage keysAndValuesDo:
  		[:k :v | | count |
  		count := 0.
  		v do:
  			[:methodName|
  			(methods at: methodName ifAbsent: []) ifNotNil:
  				[:method|
  				 method parseTree nodesDo:
  					[:n|
  					(n isVariable
  					 and: [n name hasEqualElements: k]) ifTrue:
  						[count := count + 1]]]].
  		globalNames
  			add: k		"move arrays (e.g. methodCache) to end of struct"
  			withOccurrences: (((variableDeclarations at: k ifAbsent: ['']) includes: $[)
  								ifTrue: [count]
  								ifFalse: [count + 1000])].
  	variableDeclarations keysDo:
  		[:e | globalNames add: e withOccurrences: 0].
  	variables do:
  		[:e | globalNames add: e withOccurrences: 0].
- 	"Allow vmClass to specify some number of names that should be emitted first in a specific order.
- 	 This is for the Cogit's use of VarBaseRegister."
- 	([vmClass clusteredVariableNames]
- 		on: MessageNotUnderstood
- 		do: [:ex| nil]) ifNotNil:
- 			[:clusteredVariableNames|
- 			clusteredVariableNames with: (clusteredVariableNames size - 1 * 10000 + 1000000 to: 1000000 by: -10000) do:
- 				[:variable :occurrences|
- 				 (globalNames includes: variable) ifTrue:
- 					[globalNames
- 						remove: variable;
- 						add: variable withOccurrences: occurrences]]].
  	^(globalNames sortedElements asSortedCollection:
  		[:a1 :a2| a1 value > a2 value or: [a1 value = a2 value and: [a1 key <= a2 key]]]) collect:
  			[:ea| ea key]!

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 segregateByGroupingSizeAndVisibility: self buildSortedVariablesCollection) do:
- 	self buildSortedVariablesCollection do:
  		[ :var | | 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]]].
  	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
+ 	| backEnd |
+ 	backEnd := CogCompilerClass basicNew.
  	#(	'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.
  
+ 	backEnd numCheckLZCNTOpcodes > 0 ifTrue:
- 	CogCompilerClass basicNew numCheckLZCNTOpcodes > 0 ifTrue:
  		[aCCodeGenerator
  			var: #ceCheckLZCNTFunction
  				declareC: 'static usqIntptr_t (*ceCheckLZCNTFunction)(void)'].
+ 	backEnd numCheckFeaturesOpcodes > 0 ifTrue:
- 	CogCompilerClass basicNew numCheckFeaturesOpcodes > 0 ifTrue:
  		[aCCodeGenerator
  			var: #ceCheckFeaturesFunction
  				declareC: 'static usqIntptr_t (*ceCheckFeaturesFunction)(void)'].
+ 	backEnd numICacheFlushOpcodes > 0 ifTrue:
- 	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: #cPICPrototype type: #'CogMethod *'.
  	aCCodeGenerator
+ 		declareVar: #cPICPrototype type: #'CogMethod *';
  		declareVar: #blockStarts type: #'BlockStart *';
+ 		declareVar: #fixups type: #'BytecodeFixup *';
+ 		declareVar: #methodZoneBase type: #usqInt.
- 		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 Smalltalk generator syntactic sugar.
- 	"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'.
+ 	self declareFlagVarsAsByteIn: aCCodeGenerator!
- 	aCCodeGenerator addSelectorTranslation: #halt: to: 'haltmsg'!

Item was added:
+ ----- Method: Cogit class>>declareFlagVarsAsByteIn: (in category 'translation') -----
+ declareFlagVarsAsByteIn: aCCodeGenerator
+ 	CogCompilerClass basicNew byteReadsZeroExtend ifTrue:
+ 		[self declareC: #(cFramePointerInUse codeModified deadCode directedSendUsesBinding
+ 						hasMovableLiteral hasNativeFrame hasYoungReferent inBlock needsFrame
+ 						regArgsHaveBeenPushed traceStores useTwoPaths)
+ 				as: #'unsigned char'
+ 					ifPresentIn: aCCodeGenerator]!

Item was changed:
  ----- Method: Cogit>>generateCaptureCStackPointers: (in category 'initialization') -----
  generateCaptureCStackPointers: captureFramePointer
  	"Generate the routine that writes the current values of the C frame and stack pointers into
  	 variables.  These are used to establish the C stack in trampolines back into the C run-time.
+ 	 This routine assumes the system's frame pointer is the same as that used in generated code."
+ 	| startAddress callerSavedReg pushedVarBaseReg |
+ 	<inline: #never>
- 
- 	 This is a presumptuous quick hack for x86.  It is presumptuous for two reasons.  Firstly
- 	 the system's frame and stack pointers may differ from those we use in generated code,
- 	 e.g. on register-rich RISCs.  Secondly the ABI may not support a simple frameless call
- 	 as written here (for example 128-bit stack alignment on Mac OS X)."
- 	| startAddress callerSavedReg |
- 	<inline: false>
  	self allocateOpcodes: 32 bytecodes: 0.
  	startAddress := methodZoneBase.
  	 "Must happen first; value may be used in accessing any of the following addresses"
  	callerSavedReg := 0.
+ 	pushedVarBaseReg := false.
  	backEnd hasVarBaseRegister ifTrue:
  		[(self isCallerSavedReg: VarBaseReg) ifFalse:
  			["VarBaseReg is not caller-saved; must save and restore it, either by using an available caller-saved reg or push/pop."
+ 			 callerSavedReg := self availableRegisterOrNoneIn: (ABICallerSavedRegisterMask bitClear: 1 << TempReg). "TempReg used below"
- 			 callerSavedReg := self availableRegisterOrNoneIn: ABICallerSavedRegisterMask.
  			 callerSavedReg = NoReg
+ 				ifTrue: [self NativePushR: VarBaseReg. pushedVarBaseReg := true]
- 				ifTrue: [self NativePushR: VarBaseReg]
  				ifFalse: [self MoveR: VarBaseReg R: callerSavedReg]].
  		 self MoveCq: self varBaseAddress R: VarBaseReg].
  	captureFramePointer ifTrue:
  		[self MoveR: FPReg Aw: self cFramePointerAddress].
  	"Capture the stack pointer prior to the call.  If we've pushed VarBaseReg take that into account."
+ 	(backEnd leafCallStackPointerDelta ~= 0 or: [pushedVarBaseReg])
- 	(backEnd leafCallStackPointerDelta ~= 0
- 	 or: [backEnd hasVarBaseRegister])
  		ifTrue:
  			[self LoadEffectiveAddressMw:
+ 					(pushedVarBaseReg
- 					((backEnd hasVarBaseRegister and: [callerSavedReg = NoReg])
  						ifTrue: [backEnd leafCallStackPointerDelta + objectMemory wordSize]
  						ifFalse: [backEnd leafCallStackPointerDelta])
  				r: NativeSPReg
  				R: TempReg.
  			 self MoveR: TempReg Aw: self cStackPointerAddress]
+ 		ifFalse:
+ 			[self MoveR: NativeSPReg Aw: self cStackPointerAddress].
- 		ifFalse: [self MoveR: NativeSPReg Aw: self cStackPointerAddress].
  	backEnd hasVarBaseRegister ifTrue:
  		[(self isCallerSavedReg: VarBaseReg) ifFalse:
+ 			[pushedVarBaseReg
- 			["VarBaseReg is not caller-saved; must save and restore it"
- 			 callerSavedReg = NoReg
  				ifTrue: [self NativePopR: VarBaseReg]
  				ifFalse: [self MoveR: callerSavedReg R: VarBaseReg]]].
  	self NativeRetN: 0.
  	self outputInstructionsForGeneratedRuntimeAt: startAddress.
  	backEnd flushICacheFrom: startAddress asUnsignedInteger to: methodZoneBase asUnsignedInteger.
  	self recordGeneratedRunTime: 'ceCaptureCStackPointers' address: startAddress.
  	ceCaptureCStackPointers := self cCoerceSimple: startAddress to: #'void (*)(void)'!

Item was added:
+ ----- Method: Cogit>>trampolineAddressFor: (in category 'debugging') -----
+ trampolineAddressFor: trampolineName
+ 	<doNotGenerate>
+ 	0 to: trampolineTableIndex - 3 by: 2 do:
+ 		[:i|
+ 		(trampolineAddresses at: i) = trampolineName ifTrue:
+ 			[^trampolineAddresses at: i + 1]].
+ 	^nil!

Item was changed:
  ----- Method: Cogit>>varBaseAddress (in category 'accessing') -----
  varBaseAddress
+ 	^coInterpreter stackPointerAddress - objectMemory wordSize!
- 	^coInterpreter stackPointerAddress!

Item was changed:
  ----- Method: StackInterpreter class>>declareCVarsIn: (in category 'translation') -----
  declareCVarsIn: aCCodeGenerator
  	| vmClass |
  	self class == thisContext methodClass ifFalse: [^self]. "Don't duplicate decls in subclasses"
  	vmClass := aCCodeGenerator vmClass. "Generate primitiveTable etc based on vmClass, not just StackInterpreter"
  	aCCodeGenerator
  		addHeaderFile:'<stddef.h> /* for e.g. alloca */';
  		addHeaderFile:'<setjmp.h>';
  		addHeaderFile:'<wchar.h> /* for wint_t */';
  		addHeaderFile:'"vmCallback.h"';
  		addHeaderFile:'"sqMemoryFence.h"';
  		addHeaderFile:'"dispdbg.h"'.
  	LowcodeVM ifTrue: [ aCCodeGenerator addHeaderFile:'"sqLowcodeFFI.h"'].
  
  	vmClass declareInterpreterVersionIn: aCCodeGenerator defaultName: 'Stack'.
  	aCCodeGenerator
  		var: #interpreterProxy  type: #'struct VirtualMachine*'.
  	aCCodeGenerator
  		declareVar: #sendTrace type: 'volatile int';
  		declareVar: #byteCount type: #usqInt.
  	"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 breakSelector)
  		as: #'char *'
  		in: aCCodeGenerator.
  	aCCodeGenerator
  		var: #breakSelectorLength
  		declareC: 'sqInt breakSelectorLength = MinSmallInteger'.
  	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: 'bytecodeSetSelector'].
  	BytecodeSetHasExtensions == false ifTrue:
  		[aCCodeGenerator
  			removeVariable: 'extA';
  			removeVariable: 'extB'].
  	aCCodeGenerator
  		var: #methodCache
  		declareC: 'sqIntptr_t methodCache[MethodCacheSize + 1 /* ', (MethodCacheSize + 1) printString, ' */]'.
  	NewspeakVM
  		ifTrue:
  			[aCCodeGenerator
  				var: #nsMethodCache
  				declareC: 'sqIntptr_t nsMethodCache[NSMethodCacheSize + 1 /* ', (NSMethodCacheSize + 1) printString, ' */]']
  		ifFalse:
  			[aCCodeGenerator
  				removeVariable: #nsMethodCache;
  				removeVariable: 'localAbsentReceiver';
  				removeVariable: 'localAbsentReceiverOrZero'].
  	AtCacheTotalSize isInteger ifTrue:
  		[aCCodeGenerator
  			var: #atCache
  			declareC: 'sqInt atCache[AtCacheTotalSize + 1 /* ', (AtCacheTotalSize + 1) printString, ' */]'].
  	aCCodeGenerator
  		var: #primitiveTable
  		declareC: 'void (*primitiveTable[MaxPrimitiveIndex + 2 /* ', (MaxPrimitiveIndex + 2) printString, ' */])(void) = ', vmClass primitiveTableString.
  	vmClass primitiveTable do:
  		[:symbolOrNot|
  		(symbolOrNot isSymbol
  		 and: [symbolOrNot ~~ #primitiveFail]) ifTrue:
  			[(aCCodeGenerator methodNamed: symbolOrNot) ifNotNil:
  				[:tMethod| tMethod returnType: #void]]].
  	vmClass objectMemoryClass hasSpurMemoryManagerAPI
  		ifTrue:
  			[aCCodeGenerator
  				var: #primitiveAccessorDepthTable
  				type: 'signed char'
  				sizeString: 'MaxPrimitiveIndex + 2 /* ', (MaxPrimitiveIndex + 2) printString, ' */'
  				array: vmClass primitiveAccessorDepthTable]
  		ifFalse:
  			[aCCodeGenerator removeVariable: #primitiveAccessorDepthTable].
  	aCCodeGenerator
  		var: #displayBits type: #'void *'.
  	self declareC: #(displayWidth displayHeight displayDepth) as: #int in: aCCodeGenerator.
  	aCCodeGenerator
  		var: #primitiveFunctionPointer
  			declareC: 'void (*primitiveFunctionPointer)()';
  		var: #externalPrimitiveTable
  			declareC: 'void (*externalPrimitiveTable[MaxExternalPrimitiveTableSize + 1 /* ', (MaxExternalPrimitiveTableSize + 1) printString, ' */])(void)';
  		var: #interruptCheckChain
  			declareC: 'void (*interruptCheckChain)(void) = 0';
  		var: #showSurfaceFn
  			declareC: 'int (*showSurfaceFn)(sqIntptr_t, int, int, int, int)';
  		var: #jmpBuf
  			declareC: 'jmp_buf jmpBuf[MaxJumpBuf + 1 /* ', (MaxJumpBuf + 1) printString, ' */]';
  		var: #suspendedCallbacks
  			declareC: 'usqInt suspendedCallbacks[MaxJumpBuf + 1 /* ', (MaxJumpBuf + 1) printString, ' */]';
  		var: #suspendedMethods
  			declareC: 'usqInt suspendedMethods[MaxJumpBuf + 1 /* ', (MaxJumpBuf + 1) printString, ' */]'.
  
  	self declareCAsUSqLong: #(nextPollUsecs nextWakeupUsecs longRunningPrimitiveGCUsecs
  								longRunningPrimitiveStartUsecs longRunningPrimitiveStopUsecs
  								"these are high-frequency enough that they're overflowing quite quickly on modern hardware"
  								statProcessSwitch statIOProcessEvents statForceInterruptCheck
  								statCheckForEvents statStackOverflow statStackPageDivorce
  								statIdleUsecs)
  		in: aCCodeGenerator.
  	aCCodeGenerator var: #nextProfileTick type: #sqLong.
+ 	aCCodeGenerator var: #reenterInterpreter type: 'jmp_buf'.
- 	aCCodeGenerator
- 		var: #reenterInterpreter
- 		declareC: 'jmp_buf reenterInterpreter; /* private export */'.
  	LowcodeVM
  		ifTrue:
  			[aCCodeGenerator
  				var: #lowcodeCalloutState type: #'sqLowcodeCalloutState*'.
  			 self declareC: #(nativeSP nativeStackPointer shadowCallStackPointer)
  				as: #'char *'
  				in: aCCodeGenerator]
  		ifFalse:
  			[#(lowcodeCalloutState nativeSP nativeStackPointer shadowCallStackPointer) do:
  				[:var| aCCodeGenerator removeVariable: var]].
  		
  	aCCodeGenerator
  		var: #primitiveDoMixedArithmetic
  		declareC: 'char primitiveDoMixedArithmetic = 1'.!

Item was changed:
  ----- Method: StackInterpreter class>>mustBeGlobal: (in category 'translation') -----
  mustBeGlobal: var
  	"Answer if a variable must be global and exported.  Used for inst vars that are accessed from VM support code,
  	 and for variables that are initialized to some value (e.g. primitiveDoMixedArithmetic)."
  
  	^(super mustBeGlobal: var)
  	   or: [(self objectMemoryClass mustBeGlobal: var)
  	   or: [(#('interpreterProxy' 'interpreterVersion' 'inIOProcessEvents' 'sendWheelEvents'
  			'deferDisplayUpdates' 'extraVMMemory'
  			'showSurfaceFn' 'displayBits' 'displayWidth' 'displayHeight' 'displayDepth'
  			'desiredNumStackPages' 'desiredEdenBytes'
  			'primitiveDoMixedArithmetic'
  			'breakLookupClassTag' 'breakSelector' 'breakSelectorLength' 'sendTrace' 'checkAllocFiller' 'checkedPluginName'
+ 			"'reenterInterpreter'" 'suppressHeartbeatFlag' 'ffiExceptionResponse'
- 			'reenterInterpreter' 'suppressHeartbeatFlag' 'ffiExceptionResponse'
  			'debugCallbackInvokes' 'debugCallbackPath' 'debugCallbackReturns') includes: var)
  	   or: [ "This allows slow machines to define bytecodeSetSelector as 0
  			to avoid the interpretation overhead."
  			MULTIPLEBYTECODESETS not and: [var = 'bytecodeSetSelector']]]]!

Item was changed:
  ----- Method: StackToRegisterMappingCogit class>>declareCVarsIn: (in category 'translation') -----
  declareCVarsIn: aCodeGen
  	aCodeGen
  		var: #methodAbortTrampolines
  			declareC: 'sqInt methodAbortTrampolines[4]';
  		var: #picAbortTrampolines
  			declareC: 'sqInt picAbortTrampolines[4]';
  		var: #picMissTrampolines
  			declareC: 'sqInt picMissTrampolines[4]';
  		var: 'ceCall0ArgsPIC'
  			declareC: 'void (*ceCall0ArgsPIC)(void)';
  		var: 'ceCall1ArgsPIC'
  			declareC: 'void (*ceCall1ArgsPIC)(void)';
  		var: 'ceCall2ArgsPIC'
  			declareC: 'void (*ceCall2ArgsPIC)(void)';
  		var: #ceCallCogCodePopReceiverArg0Regs
  			declareC: 'void (*ceCallCogCodePopReceiverArg0Regs)(void)';
  		var: #realCECallCogCodePopReceiverArg0Regs
  			declareC: 'void (*realCECallCogCodePopReceiverArg0Regs)(void)';
  		var: #ceCallCogCodePopReceiverArg1Arg0Regs
  			declareC: 'void (*ceCallCogCodePopReceiverArg1Arg0Regs)(void)';
  		var: #realCECallCogCodePopReceiverArg1Arg0Regs
  			declareC: 'void (*realCECallCogCodePopReceiverArg1Arg0Regs)(void)';
  		var: 'simStack'
  			declareC: 'SimStackEntry simStack[', self simStackSlots asString, ']';
  		var: 'simSelf'
  			type: #CogSimStackEntry;
  		var: #optStatus
  			type: #CogSSOptStatus;
  		var: 'prevBCDescriptor'
  			type: #'BytecodeDescriptor *'.
+ 	LowcodeVM
+ 		ifTrue:
+ 			[aCodeGen
+ 				var: 'simNativeStack'
+ 				declareC: 'CogSimStackNativeEntry simNativeStack[', self simNativeStackSlots asString, ']']
+ 		ifFalse:
+ 			[#(simNativeSpillBase simNativeStack "simNativeStackPtr" simNativeStackSize hasNativeFrame) do:
+ 				[:lowcodeVar| aCodeGen removeVariable: lowcodeVar ifAbsent: []]].
- 	LowcodeVM ifTrue: [
- 		aCodeGen var: 'simNativeStack'
- 			declareC: 'CogSimStackNativeEntry simNativeStack[', self simNativeStackSlots asString, ']'
- 	].
  
  	self numPushNilsFunction ifNotNil:
  		[aCodeGen
  			var: 'numPushNilsFunction'
  				declareC: 'sqInt (* const numPushNilsFunction)(struct _BytecodeDescriptor *,sqInt,sqInt,sqInt) = ', (aCodeGen cFunctionNameFor: self numPushNilsFunction);
  			var: 'pushNilSizeFunction'
  				declareC: 'sqInt (* const pushNilSizeFunction)(sqInt,sqInt) = ', (aCodeGen cFunctionNameFor: self pushNilSizeFunction)].
  
  	aCodeGen
  		addSelectorTranslation: #register to: (aCodeGen cFunctionNameFor: 'registerr');
+ 		addSelectorTranslation: #register: to: (aCodeGen cFunctionNameFor: 'registerr:').
+ 
+ 	self declareFlagVarsAsByteIn: aCodeGen!
- 		addSelectorTranslation: #register: to: (aCodeGen cFunctionNameFor: 'registerr:')!

Item was added:
+ ----- Method: VMClass class>>declareC:as:ifPresentIn: (in category 'translation') -----
+ declareC: arrayOfVariableNames as: aCType ifPresentIn: aCCodeGenerator
+ 	"Declare the variables in arrayOfVariableNames with the given type."
+ 
+ 	arrayOfVariableNames do:
+ 		[:varName |
+ 		 (aCCodeGenerator hasVariable: varName) ifTrue:
+ 			[((self mustBeGlobal: varName)
+ 			 and: [(aCCodeGenerator typeOfVariable: varName) ifNil: [false] ifNotNil: [:varType| aCType ~= varType]]) ifTrue:
+ 				[self error: 'attempting to change type of global var ', varName, '!!!!'].
+ 			 aCCodeGenerator var: varName type: aCType]]!

Item was changed:
  ----- Method: VMClass>>promptHex: (in category 'simulation support') -----
  promptHex: string
  	<doNotGenerate>
  	| s |
  	s := UIManager default request: string, ' (hex)'.
  	s := s withBlanksTrimmed.
  	^(s notEmpty and: ['-+0123456789abcdefABCDEF' includes: s first]) ifTrue:
+ 		[(s beginsWith: 'ce')
- 		[(s includes: $r)
  			ifTrue:
+ 				[self cogit trampolineAddressFor: s]
- 				[Number readFrom: s readStream]
  			ifFalse:
+ 				[(s includes: $r)
+ 					ifTrue:
+ 						[Number readFrom: s readStream]
+ 					ifFalse:
+ 						[(#('0x' '-0x') detect: [:prefix| s beginsWith: prefix] ifNone: []) ifNotNil:
+ 							[:prefix|
+ 							s := s allButFirst: prefix size.
+ 							prefix first = $- ifTrue: [s := '-', s]].
+ 						Integer readFrom: s readStream base: 16]]]!
- 				[(#('0x' '-0x') detect: [:prefix| s beginsWith: prefix] ifNone: []) ifNotNil:
- 					[:prefix|
- 					s := s allButFirst: prefix size.
- 					prefix first = $- ifTrue: [s := '-', s]].
- 				Integer readFrom: s readStream base: 16]]!



More information about the Vm-dev mailing list