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

commits at source.squeak.org commits at source.squeak.org
Wed Jan 6 00:07:59 UTC 2021


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

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

Name: VMMaker.oscog-eem.2925
Author: eem
Time: 5 January 2021, 4:07:48.282359 pm
UUID: bc30e1c2-363b-4238-ac06-0fc4bc0cfa96
Ancestors: VMMaker.oscog-eem.2924

Cogit:
More cleanup given that sqVirtualMachine.h reveals the direct interpreter API to SQUEAK_BUILTIN_PLUGIN which is alas defined for cogit.c.  Hence the conflicts between sqVirtualMachine.h and cointerp.h force us to not include sq.h in cogit.c.  Maybe this is worse than the disease of sqVirtualMachine.h's API being inaccurate.  But ione step at a time.

MTVM:
Smilaiton time recording of instructions in tryLockVMOwnerTo: while debugging x86_64's implementation.

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

Item was changed:
  ----- Method: CCodeGenerator>>emitCHeaderOn: (in category 'C code generator') -----
  emitCHeaderOn: aStream
  	"Emit the initial part of a source file on aStream, comprising the version stamp,
  	 the global struct usage flags, the header files and preamble code."
  
  	| headerClass |
  	headerClass := [vmClass coreInterpreterClass]
  						on: MessageNotUnderstood
  						do: [:ex| vmClass].
  	aStream nextPutAll: (self fileHeaderVersionStampForSourceClass: headerClass); cr; cr.
  	self emitGlobalStructFlagOn: aStream.
  
+ 	(vmClass isNil or: [vmClass wantsSqDotH]) ifTrue:
+ 		[self addHeaderFileFirst: '"sq.h"'].
- 	self addHeaderFileFirst: '"sq.h"'.
  	"Additional header files; include C library ones first."
  	self emitHeaderFiles: (headerFiles select: [:hdr| hdr includes: $<]) on: aStream.
  	"Additional header files; include squeak VM ones last"
  	self emitHeaderFiles: (headerFiles reject: [:hdr| hdr includes: $<]) on: aStream.
  
  	self maybePutPreambleFor: vmClass on: aStream.
  
  	aStream cr!

Item was changed:
  ----- Method: CoInterpreter>>interpret (in category 'interpreter shell') -----
  interpret
  	"This is the main interpreter loop.
  	 In a pure interpreter it loops forever, fetching and executing bytecodes.
  	 With the Cogit JIT executing code as well, the interpreter is reentered from machine code
  	 whenever the machine code wants to interpret a method instead of executing its machine
  	 code.  Entry into the interpreter is done via a ''jump call'' in machine code that uses
  	 CFramePointer and CStackPointer to find the base of the C stack (set in CoInterpreter>>
  	 enterSmalltalkExecutiveImplementation) and substitutes CReturnAddress as the return
  	 address in the code so it always appears that interpret has been called from
  	 CoInterpreter>>enterSmalltalkExecutiveImplementation, which may be important to,
  	 for example, C exception handling inside the VM.
  
  	 When running in the context of a browser plugin VM the interpreter must return control
  	 to the browser periodically. This should done only when the state of the currently running
  	 Squeak thread is safely stored in the object heap. Since this is the case at the moment
  	 that a check for interrupts is performed, that is when we return to the browser if it is time
  	 to do so. Interrupt checks happen quite frequently."
  
+ 	<api>
  	<inline: false>
  	"If stacklimit is zero then the stack pages have not been initialized."
  	stackLimit = 0 ifTrue:
  		[^self initStackPagesAndInterpret].
  	"An unchecked write is probably faster, so instead of
  	 CReturnAddress ifNil:
  		[CReturnAddress := self cCoerceSimple: self getReturnAddress to: #usqIntptr_t]
  	 we have simply"
  	self assert: (CReturnAddress isNil or: [CReturnAddress = (self cCoerceSimple: self getReturnAddress to: #usqIntptr_t)]).
  	CReturnAddress := self cCoerceSimple: self getReturnAddress to: #usqIntptr_t.
  
  	self useCogitBreakBlockIfNone.
  	"record entry time when running as a browser plug-in"
  	self browserPluginInitialiseIfNeeded.
  	self setMethod: (self iframeMethod: framePointer).
  	self deny: instructionPointer = cogit ceReturnToInterpreterPC.
  	self assertValidExecutionPointe: instructionPointer r: framePointer s: stackPointer imbar: true line: #'__LINE__'.
  	self internalizeIPandSP.
  	self initExtensions.
  	self fetchNextBytecode.
  	[true] whileTrue:
  		[self aboutToDispatchBytecode.
  		 self dispatchOn: currentBytecode in: BytecodeTable].
  	localIP := localIP - 1.  "undo the pre-increment of IP before returning"
  	self externalizeIPandSP.
  	^nil!

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"
+ 	"N.B. We *do not* include sq.h; it pulls in conflicting definitions now that sqVirtualMachine.h
+ 	 declares cointerp's functions, and declares some of them inaccurately for histrical reasons.
+ 	 We pull in CoInterpreter's api via cointerp.h which is accurate."
  	aCCodeGenerator
  		addHeaderFile:'<stddef.h>'; "for e.g. offsetof"
+ 		addHeaderFile:'"sqConfig.h"';
+ 		addHeaderFile:'"sqMemoryAccess.h"';
  		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: #ceInvokeInterpret
  			declareC: 'void (*ceInvokeInterpret)(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)(usqIntptr_t)\#endif'.
  
  	backEnd numICacheFlushOpcodes > 0 ifTrue:
  		[aCCodeGenerator
  			var: #ceFlushICache
  				declareC: 'static void (*ceFlushICache)(usqIntptr_t from, usqIntptr_t to)'].
  	aCCodeGenerator
  		var: #ceFlushDCache
  			declareC: '#if DUAL_MAPPED_CODE_ZONE\static void (*ceFlushDCache)(usqIntptr_t from, usqIntptr_t to)\#endif';
  		var: #codeToDataDelta
  			declareC: '#if DUAL_MAPPED_CODE_ZONE\static sqInt codeToDataDelta\#else\# define codeToDataDelta 0\#endif'.
  
  	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 *';
  		declareVar: #blockStarts type: #'BlockStart *';
  		declareVar: #fixups type: #'BytecodeFixup *';
  		declareVar: #methodZoneBase type: #usqInt.
  	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
  		addConstantForBinding: self bindingForNumTrampolines;
  		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'.
  	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.
  	 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!

Item was added:
+ ----- Method: Cogit class>>wantsSqDotH (in category 'translation') -----
+ wantsSqDotH
+ 	^false!

Item was added:
+ ----- Method: Cogit>>null (in category 'translation') -----
+ null
+ 	"This is needed since Cogits do not include sq.h."
+ 	<cmacro: ' 0'>
+ 	^nil!

Item was added:
+ ----- Method: Cogit>>reportInstructions: (in category 'debugging') -----
+ reportInstructions: instructions
+ 	<doNotGenerate>
+ 	| skipNext printInst |
+ 	skipNext := false.
+ 	printInst := [:inst|
+ 				coInterpreter transcript nextPutAll:
+ 					(EagerInstructionDecoration
+ 						ifTrue: [inst]
+ 						ifFalse: [processor
+ 									decorateDisassembly: inst
+ 									for: self
+ 									fromAddress: ((inst at: 3) = $r
+ 													ifTrue: [Integer readFrom: inst readStream]
+ 													ifFalse: [Integer readFrom: inst readStream base: 16])]); cr].
+ 	instructions withIndexDo:
+ 		[:thing :idx|
+ 		skipNext
+ 			ifTrue: [skipNext := false]
+ 			ifFalse:
+ 				[thing isString
+ 					ifFalse:
+ 						[thing first isString "i.e. { '(simulated return to '. processor retpcIn: coInterpreter memory. ')'}"
+ 							ifTrue:
+ 								[thing do:
+ 									[:stringOrNumber|
+ 									coInterpreter transcript nextPutAll: (stringOrNumber isString
+ 															ifTrue: [stringOrNumber]
+ 															ifFalse: [stringOrNumber hex])].
+ 									coInterpreter transcript cr]
+ 							ifFalse: "if possible, add the label to the instruction line to condense the output"
+ 								[coInterpreter transcript cr.
+ 								 (thing at: processor registerStatePCIndex ifAbsent: []) ifNotNil:
+ 									[:pc| | next label |
+ 									 label := self relativeLabelForPC: pc.
+ 									 ((next := instructions at: idx + 1 ifAbsent: []) notNil
+ 									  and: [next isString
+ 									  and: [(Integer readFrom: next readStream radix: 16) = pc]])
+ 										ifTrue: "Decorate instruction and eliminate pc line"
+ 											[skipNext := true.
+ 											 processor printRegisterStateExceptPC: thing on: coInterpreter transcript.
+ 											 label ifNotNil: [coInterpreter transcript nextPutAll: label; space].
+ 											 printInst value: next]
+ 										ifFalse:
+ 											[label ifNotNil: [coInterpreter transcript nextPutAll: label; nextPut: $:; cr].
+ 											 processor printRegisterState: thing on: coInterpreter transcript]]]]
+ 					ifTrue:
+ 						[printInst value: thing]]].
+ 	coInterpreter transcript flush!

Item was changed:
  ----- Method: Cogit>>reportLastNInstructions (in category 'debugging') -----
  reportLastNInstructions
  	<doNotGenerate>
+ 	self reportInstructions: lastNInstructions!
- 	| skipNext printInst |
- 	skipNext := false.
- 	printInst := [:inst|
- 				coInterpreter transcript nextPutAll:
- 					(EagerInstructionDecoration
- 						ifTrue: [inst]
- 						ifFalse: [processor
- 									decorateDisassembly: inst
- 									for: self
- 									fromAddress: ((inst at: 3) = $r
- 													ifTrue: [Integer readFrom: inst readStream]
- 													ifFalse: [Integer readFrom: inst readStream base: 16])]); cr].
- 	lastNInstructions withIndexDo:
- 		[:thing :idx|
- 		skipNext
- 			ifTrue: [skipNext := false]
- 			ifFalse:
- 				[thing isString
- 					ifFalse:
- 						[thing first isString "i.e. { '(simulated return to '. processor retpcIn: coInterpreter memory. ')'}"
- 							ifTrue:
- 								[thing do:
- 									[:stringOrNumber|
- 									coInterpreter transcript nextPutAll: (stringOrNumber isString
- 															ifTrue: [stringOrNumber]
- 															ifFalse: [stringOrNumber hex])].
- 									coInterpreter transcript cr]
- 							ifFalse: "if possible, add the label to the instruction line to condense the output"
- 								[coInterpreter transcript cr.
- 								 (thing at: processor registerStatePCIndex ifAbsent: []) ifNotNil:
- 									[:pc| | next label |
- 									 label := self relativeLabelForPC: pc.
- 									 ((next := lastNInstructions at: idx + 1 ifAbsent: []) notNil
- 									  and: [next isString
- 									  and: [(Integer readFrom: next readStream radix: 16) = pc]])
- 										ifTrue: "Decorate instruction and eliminate pc line"
- 											[skipNext := true.
- 											 processor printRegisterStateExceptPC: thing on: coInterpreter transcript.
- 											 label ifNotNil: [coInterpreter transcript nextPutAll: label; space].
- 											 printInst value: next]
- 										ifFalse:
- 											[label ifNotNil: [coInterpreter transcript nextPutAll: label; nextPut: $:; cr].
- 											 processor printRegisterState: thing on: coInterpreter transcript]]]]
- 					ifTrue:
- 						[printInst value: thing]]].
- 	coInterpreter transcript flush!

Item was changed:
  ----- Method: Cogit>>tryLockVMOwnerTo: (in category 'multi-threading') -----
  tryLockVMOwnerTo: value
  	<api>
  	"ceTryLockVMOwner does an atomic compare-and-swap of the vmOwner
  	 variable with zero and the argument, setting vmOwner to value if it was
  	 zero. It answers if the lock was zero and hence was acquired.
  
  	 See CogThreadManager>>#tryLockVMOwnerTo: for the simulation of
  	 processor thread switching which surrounds this method."
  	<cmacro: '(value) ceTryLockVMOwner(value)'>
  	| breakPCWasTrue |
+ 	"(thisContext findContextSuchThat: [:ctxt| ctxt selector == #primitiveRelinquishProcessor]) ifNil:
+ 		[self halt]."
- 	(thisContext findContextSuchThat: [:ctxt| ctxt selector == #primitiveRelinquishProcessor]) ifNil:
- 		[self halt].
  	(breakPCWasTrue := breakPC == true) ifTrue:
  		[breakPC := nil].
  	processor abiMarshalArg0: value in: objectMemory memory.
+ 	^[	| result instructions |
+ 		lastNInstructions removeAll.
- 	^[	| result |
  		result := self simulateLeafCallOf: ceTryLockVMOwner.
+ 		instructions := lastNInstructions copy.
  		self assert: (result ~= 0) = (coInterpreter threadManager getVMOwner = value).
  		result ~= 0] ensure:
  			[processor abiUnmarshal: 1.
  			 breakPCWasTrue ifTrue:
  				[breakPC := true]]!

Item was added:
+ ----- Method: VMClass class>>wantsSqDotH (in category 'translation') -----
+ wantsSqDotH
+ 	^true!



More information about the Vm-dev mailing list