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

commits at source.squeak.org commits at source.squeak.org
Wed Aug 4 02:24:15 UTC 2021


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

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

Name: VMMaker.oscog-eem.3024
Author: eem
Time: 3 August 2021, 7:23:47.714158 pm
UUID: 417aa150-be4e-4631-b35b-948afa18e190
Ancestors: VMMaker.oscog-eem.3023

Cog: add a trace flag to turn on logging of FastCCall primitives.
Mark a few of the flag methods in the Cogit as <inline: #always> and make compileOnStackExternalPrimitive:flags: a Spur-only option (it is anyway, so the code shouldn't be incuded in V3 Cogits).
Remove the inline marker from a couple of api methods.

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

Item was changed:
  ----- Method: CoInterpreter>>recordFastCCallPrimTraceForMethod: (in category 'compiled methods') -----
  recordFastCCallPrimTraceForMethod: aMethodObj
  	"This is a little elaborate.  The primTraceLog is only useful if it is not full of noise.
  	 To reduce noise when debugging a specific plugin we allow a plugin name to be
  	 specified and will only generate the primTraceLog code for primitives in that plugin."
  	<api>
- 	<inline: true>
  	^cogit recordFastCCallPrimTrace
  	  and: [primTracePluginName
  				ifNil: [true]
  				ifNotNil: [self methodHasPrimitiveInPrimTracePlugin: aMethodObj]]!

Item was changed:
  ----- Method: CoInterpreter>>recordPrimTraceForMethod: (in category 'compiled methods') -----
  recordPrimTraceForMethod: aMethodObj
  	"This is a little elaborate.  The primTraceLog is only useful if it is not full of noise.
  	 To reduce noise when debugging a specific plugin we allow a plugin name to be
  	 specified and will only generate the primTraceLog code for primitives in that plugin."
  	<api>
- 	<inline: true>
  	^cogit recordPrimTrace
  	  and: [primTracePluginName
  				ifNil: [true]
  				ifNotNil: [self methodHasPrimitiveInPrimTracePlugin: aMethodObj]]!

Item was changed:
  ----- Method: CogAbstractInstruction>>isWithinMwOffsetRange: (in category 'testing') -----
  isWithinMwOffsetRange: anAddress
  	"Answer if an address can be accessed using the offset in a MoveMw:r:R: or similar instruction.
  	 We assume this is true for 32-bit processors and expect 64-bit processors to answer false
  	 for values in the interpreter or the object memory."
+ 	<inline: true>
- 
  	^true!

Item was changed:
  ----- Method: CogObjectRepresentation>>canPinObjects (in category 'testing') -----
  canPinObjects
  	"Answer if the memory manager supports pinned objects."
+ 	<inline: #always>
  	^false!

Item was changed:
+ ----- Method: CogObjectRepresentation>>createsArraysInline (in category 'testing') -----
- ----- Method: CogObjectRepresentation>>createsArraysInline (in category 'bytecode generator support') -----
  createsArraysInline
  	"Answer if the object representation allocates arrays inline.  By
  	 default answer false. Better code can be generated when creating
  	 arrays inline if values are /not/ flushed to the stack."
+ 	<inline: #always>
  	^false!

Item was changed:
+ ----- Method: CogObjectRepresentation>>createsClosuresInline (in category 'testing') -----
- ----- Method: CogObjectRepresentation>>createsClosuresInline (in category 'bytecode generator support') -----
  createsClosuresInline
  	"Answer if the object representation allocates closures inline.  By
  	 default answer false. Better code can be generated when creating
  	 closures inline if copied values are /not/ flushed to the stack."
+ 	<inline: #always>
  	^false!

Item was changed:
  ----- Method: CogObjectRepresentation>>hasSpurMemoryManagerAPI (in category 'testing') -----
  hasSpurMemoryManagerAPI
+ 	<inline: #always>
  	^false!

Item was changed:
  ----- Method: CogObjectRepresentationForSpur>>canPinObjects (in category 'testing') -----
  canPinObjects
  	"Answer if the memory manager supports pinned objects."
+ 	<inline: #always>
  	^true!

Item was changed:
  ----- Method: CogObjectRepresentationForSpur>>createsArraysInline (in category 'bytecode generator support') -----
  createsArraysInline
  	"Answer if the object representation allocates arrays inline.  By
  	 default answer false. Better code can be generated when creating
  	 arrays inline if values are /not/ flushed to the stack."
+ 	<inline: #always>
  	^true!

Item was changed:
  ----- Method: CogObjectRepresentationForSpur>>createsClosuresInline (in category 'bytecode generator support') -----
  createsClosuresInline
  	"Answer if the object representation allocates closures inline.  By
  	 default answer false. Better code can be generated when creating
  	 closures inline if copied values are /not/ flushed to the stack."
+ 	<inline: #always>
  	^true!

Item was changed:
  ----- Method: CogObjectRepresentationForSpur>>hasSpurMemoryManagerAPI (in category 'testing') -----
  hasSpurMemoryManagerAPI
+ 	<inline: #always>
  	^true!

Item was changed:
  ----- Method: CogObjectRepresentationForSpur>>isSmallIntegerTagNonZero (in category 'object representation') -----
  isSmallIntegerTagNonZero
+ 	<inline: #always>
  	^true!

Item was changed:
  ----- Method: CogObjectRepresentationForSpur>>smallIntegerIsOnlyImmediateType (in category 'testing') -----
  smallIntegerIsOnlyImmediateType
+ 	<inline: #always>
  	^false!

Item was changed:
  ----- Method: CogObjectRepresentationForSqueakV3>>isSmallIntegerTagNonZero (in category 'object representation') -----
  isSmallIntegerTagNonZero
+ 	<inline: #always>
  	^true!

Item was changed:
  ----- Method: CogObjectRepresentationForSqueakV3>>smallIntegerIsOnlyImmediateType (in category 'testing') -----
  smallIntegerIsOnlyImmediateType
+ 	<inline: #always>
  	^true!

Item was changed:
  ----- Method: CogX64Compiler>>isWithinMwOffsetRange: (in category 'testing') -----
  isWithinMwOffsetRange: anAddress
  	"Answer if an address can be accessed using the offset in a MoveMw:r:R: or similar instruction.
  	 We assume this is true for 32-bit processors and expect 64-bit processors to answer false
  	 for values in the interpreter or the object memory.    Restrict our use of offsets to reference
  	 addresses within the method zone, rather than checking for a 32-bit offset, so as to keep the
  	 simulator and real VM in sync."
+ 	<inline: true>
- 
  	^cogit addressIsInCodeZone: anAddress!

Item was changed:
  ----- Method: SimpleStackBasedCogit>>compileOnStackExternalPrimitive:flags: (in category 'primitive generators') -----
  compileOnStackExternalPrimitive: primitiveRoutine flags: flags
  	"Compile a fast call of a C primitive using the current stack page, avoiding the stack switch except on failure.
  	 This convention still uses stackPointer and argumentCount to access operands.  Push all operands to the stack,
  	 assign stackPointer, argumentCount, and zero primFailCode.  Make the call (saving a LinkReg if required).
  	 Test for failure and return.  On failure on Spur, if there is an accessor depth, assign framePointer and newMethod,
  	 do the stack switch, call checkForAndFollowForwardedPrimitiveState, and loop back if forwarders are found.
  	 Fall through to frame build."
+ 	<option: #SpurObjectMemory>
- 	
  	<var: #primitiveRoutine declareC: 'void (*primitiveRoutine)(void)'>
  	| calleeSavedRegisterMask linkRegSaveRegister spRegSaveRegister jmp retry |
  	self assert: (objectRepresentation hasSpurMemoryManagerAPI and: [flags anyMask: PrimCallOnSmalltalkStack]).
  	self deny: (backEnd hasVarBaseRegister
  				and: [self register: VarBaseReg isInMask: ABICallerSavedRegisterMask]).
  
  	(coInterpreter recordFastCCallPrimTraceForMethod: methodObj) ifTrue:
  		[self genFastPrimTraceUsing: ClassReg and: SendNumArgsReg].
  
  	"Clear the primFailCode and set argumentCount"
  	self MoveCq: 0 R: TempReg.
  	self MoveR: TempReg Aw: coInterpreter primFailCodeAddress.
  	methodOrBlockNumArgs ~= 0 ifTrue:
  		[self AddCq: methodOrBlockNumArgs R: TempReg]. "As small or smaller than move on most archs"
  	self MoveR: TempReg Aw: coInterpreter argumentCountAddress.
  	self genExternalizeStackPointerForFastPrimitiveCall.
  	"We may need to save LinkReg and/or SPReg, and given the stack machinations
  	  it is much easier to save them in callee saved registers than on the stack itself."
  	calleeSavedRegisterMask := ABICalleeSavedRegisterMask bitClear: (self registerMaskFor: ClassReg).
  	backEnd hasLinkRegister ifTrue:
  		[linkRegSaveRegister := self availableRegisterOrNoneIn: calleeSavedRegisterMask.
  		 self deny: linkRegSaveRegister = NoReg.
  		 self MoveR: LinkReg R: linkRegSaveRegister.
  		 calleeSavedRegisterMask := calleeSavedRegisterMask bitClear: (self registerMaskFor: linkRegSaveRegister)].
  	spRegSaveRegister := NoReg.
  	(SPReg ~= NativeSPReg
  	 and: [(self isCalleeSavedReg: SPReg) not]) ifTrue:
  		[spRegSaveRegister := self availableRegisterOrNoneIn: calleeSavedRegisterMask.
  		 self deny: spRegSaveRegister = NoReg.
  		 self MoveR: SPReg R: spRegSaveRegister].
  	retry := self Label.
  	(flags anyMask: PrimCallOnSmalltalkStackAlign2x)
  		ifTrue: [self AndCq: (objectMemory wordSize * 2 - 1) bitInvert R: SPReg R: NativeSPReg]
  		ifFalse:
  			[SPReg ~= NativeSPReg ifTrue:
  				[backEnd genLoadNativeSPRegWithAlignedSPReg]].
  	self CallFullRT: primitiveRoutine.
  	self MoveAw: coInterpreter primFailCodeAddress R: TempReg.
  	spRegSaveRegister ~= NoReg ifTrue:
  		[self MoveR: spRegSaveRegister R: SPReg].
  	self CmpCq: 0 R: TempReg.
  	jmp := self JumpNonZero: 0.
  	"At this point the primitive has cut back stackPointer to point to the result."
  	self MoveAw: coInterpreter stackPointerAddress R: TempReg.
  	"get result and restore retpc"
  	backEnd hasLinkRegister
  		ifTrue:
  			[self MoveMw: 0 r: TempReg R: ReceiverResultReg;
  				AddCq: objectMemory wordSize R: TempReg R: SPReg;
  				MoveR: linkRegSaveRegister R: LinkReg]
  		ifFalse:
  			[| retpcOffset |
  			"The original retpc is (argumentCount + 1) words below stackPointer."
  			 retpcOffset := (methodOrBlockNumArgs + 1 * objectMemory wordSize) negated.
  			 self MoveMw: retpcOffset r: TempReg R: ClassReg; "get retpc"
  				MoveR: TempReg R: SPReg;
  			 	MoveMw: 0 r: TempReg R: ReceiverResultReg;
  				MoveR: ClassReg Mw: 0 r: TempReg "put it back on stack for the return..."].
  	self RetN: 0.
  
  	jmp jmpTarget: self Label.
  	(coInterpreter accessorDepthForExternalPrimitiveMethod: methodObj) >= 0
  		ifTrue:
  			[| skip |
  			 "Given that following primitive state to the accessor depth is recursive, we're asking for
  			  trouble if we run the fixup on the Smalltalk stack page.  Run it on the full C stack instead.
  			 This won't be a performance issue since primitive failure should be very rare."
  			self MoveR: FPReg Aw: coInterpreter framePointerAddress.
  			self MoveCw: primitiveRoutine asInteger R: TempReg.
  			self MoveR: TempReg Aw: coInterpreter primitiveFunctionPointerAddress.
  			methodLabel addDependent:
  				(self annotateAbsolutePCRef:
  					(self MoveCw: methodLabel asInteger R: ClassReg)).
  			self MoveMw: (self offset: CogMethod of: #methodObject) r: ClassReg R: TempReg.
  			self MoveR: TempReg Aw: coInterpreter newMethodAddress.
  			self genLoadCStackPointersForPrimCall.
  			self CallFullRT: (self cCode: [#checkForAndFollowForwardedPrimitiveState asUnsignedIntegerPtr]
  								   inSmalltalk: [self simulatedTrampolineFor: #checkForAndFollowForwardedPrimitiveState]).
  			backEnd genLoadStackPointersForFastPrimCall: ClassReg.
  			self CmpCq: 0 R: ABIResultReg.
  			skip := self JumpZero: 0.
  			self MoveCq: 0 R: TempReg.
  			self MoveR: TempReg Aw: coInterpreter primFailCodeAddress.
  			self Jump: retry.
  			skip jmpTarget: self Label]
  		ifFalse: "must reload SPReg to undo any alignment change,"
  			[(flags anyMask: PrimCallOnSmalltalkStackAlign2x) ifTrue:
  				[backEnd genLoadStackPointersForFastPrimCall: ClassReg]].
  	"The LinkRegister now contains the return address either of the primitive call or of checkForAndFollowForwardedPrimitiveState.
  	 It must be restored to the return address of the send invoking this primtiive method."
  	backEnd hasLinkRegister ifTrue:
  		[self MoveR: linkRegSaveRegister R: LinkReg].
  	"Finally remember to reload ReceiverResultReg if required.  Even if
  	 arguments have been pushed, the prolog sequence assumes it is live."
  	(self register: ReceiverResultReg isInMask: ABICallerSavedRegisterMask) ifTrue:
  		[self MoveMw: (methodOrBlockNumArgs + (backEnd hasLinkRegister ifTrue: [0] ifFalse: [1])) * objectMemory wordSize
  			r: SPReg
  			R: ReceiverResultReg].
  	"continue to frame build..."
  	^0!

Item was changed:
  ----- Method: SimpleStackBasedCogit>>compilePrimitive (in category 'primitive generators') -----
  compilePrimitive
  	"Compile a primitive.  If possible, performance-critical primitives will
  	 be generated by their own routines (primitiveGenerator).  Otherwise,
  	 if there is a primitive at all, we call the C routine with the usual
  	 stack-switching dance, test the primFailCode and then either return
  	 on success or continue to the method body."
  	<inline: false>
  	| primitiveDescriptor primitiveRoutine flags |
  	<var: #primitiveDescriptor type: #'PrimitiveDescriptor *'>
  	<var: #primitiveRoutine declareC: 'void (*primitiveRoutine)(void)'>
  	primitiveIndex = 0 ifTrue: [^0].
  	"If a descriptor specifies an argument count (by numArgs >= 0) then it must match
  	 for the generated code to be correct.  For example for speed many primitives use
  	 ResultReceiverReg instead of accessing the stack, so the receiver better be at
  	 numArgs down the stack.  Use the interpreter version if not."
  	((primitiveDescriptor := self primitiveGeneratorOrNil) notNil
  	 and: [primitiveDescriptor primitiveGenerator notNil
  	 and: [(primitiveDescriptor primNumArgs < 0 "means generator doesn't care"
  		   or: [primitiveDescriptor primNumArgs = (coInterpreter argumentCountOf: methodObj)])]]) ifTrue:
  		[| opcodeIndexAtPrimitive code |
  		"Note opcodeIndex so that any arg load instructions
  		 for unimplemented primitives can be discarded."
  		 opcodeIndexAtPrimitive := opcodeIndex.
  		 code := objectRepresentation perform: primitiveDescriptor primitiveGenerator.
  
  		(code < 0 and: [code ~= UnimplementedPrimitive]) ifTrue: "Generator failed, so no point continuing..."
  			[^code].
  		"If the primitive can never fail then there is nothing more that needs to be done."
  		code = UnfailingPrimitive ifTrue:
  			[^0].
  		"If the machine code version handles all cases the only reason to call the interpreter
  		 primitive is to reap the primitive error code.  Don't bother if it isn't used."
  		(code = CompletePrimitive
  		 and: [(self methodUsesPrimitiveErrorCode: methodObj header: methodHeader) not]) ifTrue:
  			[^0].
  		"Discard any arg load code generated by the primitive generator."
  		code = UnimplementedPrimitive ifTrue:
  			[opcodeIndex := opcodeIndexAtPrimitive]].
  
  	primitiveRoutine := coInterpreter
  							functionPointerForCompiledMethod: methodObj
  							primitiveIndex: primitiveIndex
  							primitivePropertyFlagsInto: (self addressOf: flags put: [:val| flags := val]).
  	(flags anyMask: PrimCallDoNotJIT) ifTrue:
  		[^ShouldNotJIT].
  
  	(primitiveRoutine = 0 "no primitive"
  	or: [primitiveRoutine = (self cCoerceSimple: #primitiveFail to: 'void (*)(void)')]) ifTrue:
  		[^self genFastPrimFail].
  
  	(flags anyMask: PrimCallOnSmalltalkStack) ifTrue:
  		[self deny: ((flags anyMask: FastCPrimitiveUseCABIFlag) and: [flags anyMask: PrimCallOnSmalltalkStackAlign2x]).
  		(flags anyMask: FastCPrimitiveUseCABIFlag) ifTrue:
  			[^self compileMachineCodeInterpreterPrimitive: (self cCoerceSimple: (coInterpreter mcprimFunctionForPrimitiveIndex: primitiveIndex)
  															to: 'void (*)(void)')].
+ 		objectRepresentation hasSpurMemoryManagerAPI ifTrue:
+ 			[^self compileOnStackExternalPrimitive: primitiveRoutine flags: flags]].
- 		^self compileOnStackExternalPrimitive: primitiveRoutine flags: flags].
  	minValidCallAddress := minValidCallAddress min: primitiveRoutine asUnsignedInteger.
  	^self compileInterpreterPrimitive: primitiveRoutine flags: flags!



More information about the Vm-dev mailing list