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

commits at source.squeak.org commits at source.squeak.org
Tue Jan 28 03:52:26 UTC 2020


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

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

Name: VMMaker.oscog-eem.2681
Author: eem
Time: 27 January 2020, 7:52:10.898262 pm
UUID: fc19206e-16d0-4529-a560-cea2f8bcfff5
Ancestors: VMMaker.oscog-eem.2680

Cogit:
More progress with dual mapped zone simulation.
Hide the simulated dual write for closed PICs in codeMemcpy:_:_:.

Claw back simulation speed by checking for valid dual zone ranges, rather that the while 1meg plus zone.

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

Item was added:
+ ----- Method: Cogit>>assertValidDualZoneFrom:to: (in category 'debugging') -----
+ assertValidDualZoneFrom: startAddress to: endAddress
+ 	"{(self firstInvalidDualZoneAddressFrom: startAddress to: endAddress) hex. ((self firstInvalidDualZoneAddressFrom: startAddress to: endAddress) + codeToDataDelta) hex }"
+ 	"{self firstInvalidDualZoneAddress. self firstInvalidDualZoneAddress + codeToDataDelta }"
+ 	"{self firstInvalidDualZoneAddress hex. (self firstInvalidDualZoneAddress + codeToDataDelta) hex }"
+ 	"{(objectMemory longAt: self firstInvalidDualZoneAddress) hex. (objectMemory longAt: self firstInvalidDualZoneAddress + codeToDataDelta) hex }"
+ 	"self armDisassembleDualZoneAnomalies"
+ 	"self armPrintDualZoneAnomalies"
+ 	self cCode: ''
+ 		inSmalltalk: [self assert: (self firstInvalidDualZoneAddressFrom: startAddress to: endAddress) isNil]!

Item was changed:
  ----- Method: Cogit>>codeMemcpy:_:_: (in category 'generate machine code') -----
  codeMemcpy: dest _: src _: bytes
  	"production uses the macro..."
  	<cmacro: '(dest,src,bytes) memcpy(dest,src,bytes)'>
  	self codeWriteBreakpoint: dest.
  	"simulation writes twice if simulating dual mapping..."
  	codeToDataDelta ~= 0 ifTrue:
+ 		[objectMemory memcpy: dest asInteger - codeToDataDelta _: src _: bytes].
- 		[objectMemory memcpy: dest + codeToDataDelta _: src _: bytes].
  	objectMemory memcpy: dest _: src _: bytes!

Item was changed:
  ----- Method: Cogit>>cogExtendPIC:CaseNMethod:tag:isMNUCase: (in category 'in-line cacheing') -----
  cogExtendPIC: cPIC CaseNMethod: caseNMethod tag: caseNTag isMNUCase: isMNUCase
  	"Extend the cPIC with the supplied case.  If caseNMethod is cogged dispatch direct to
  	 its unchecked entry-point.  If caseNMethod is not cogged, jump to the fast interpreter
  	 dispatch, and if isMNUCase then dispatch to fast MNU invocation and mark the cPIC as
  	 having the MNU case for cache flushing."
   	<var: #cPIC type: #'CogMethod *'>
  	| operand target address writablePIC |
  
  	coInterpreter
  		compilationBreak: cPIC selector
  		point: (objectMemory numBytesOf: cPIC selector)
  		isMNUCase: isMNUCase.
  
  	self assert: (objectRepresentation inlineCacheTagIsYoung: caseNTag) not.
  	"Caller patches to open pic if caseNMethod is young."
  	self assert: (caseNMethod notNil and: [(objectMemory isYoung: caseNMethod) not]).
  	(isMNUCase not and: [coInterpreter methodHasCogMethod: caseNMethod])
  		ifTrue: "this isn't an MNU and we have an already cogged method to jump to"
  			[operand := 0.
  			 target := (coInterpreter cogMethodOf: caseNMethod) asInteger + cmNoCheckEntryOffset]
  		ifFalse: 
  			[operand := caseNMethod.
  			 isMNUCase
  				ifTrue: "this is an MNU so tag the CPIC header and setup a jump to the MNUAbort"
  					[cPIC cpicHasMNUCase: true.
  					 target := cPIC asInteger + (self sizeof: CogMethod)]
  				ifFalse: "setup a jump to the interpretAborth so we can cog the target method"
  					[target := cPIC asInteger + self picInterpretAbortOffset]].
  
  	"find the end address of the new case"
  	address := self addressOfEndOfCase: cPIC cPICNumCases +1 inCPIC: cPIC.
  	
  	self rewriteCPICCaseAt: address tag: caseNTag objRef: operand target: target.
  
  	"finally, rewrite the jump 3 instr  before firstCPICCaseOffset to jump to the beginning of this new case"
  	self rewriteCPIC: cPIC caseJumpTo: address - cPICCaseSize. 
  
  	backEnd flushICacheFrom: cPIC asUnsignedInteger to: cPIC asUnsignedInteger + closedPICSize.
  	"update the header flag for the number of cases"
  	writablePIC := self cCoerceSimple: cPIC asUnsignedInteger + codeToDataDelta to: #'CogMethod *'.
  	writablePIC cPICNumCases: cPIC cPICNumCases + 1.
+ 	self assertValidDualZoneFrom: cPIC asUnsignedInteger to: cPIC asUnsignedInteger + closedPICSize!
- 	self assertValidDualZone!

Item was changed:
  ----- Method: Cogit>>cogMNUPICSelector:receiver:methodOperand:numArgs: (in category 'in-line cacheing') -----
  cogMNUPICSelector: selector receiver: rcvr methodOperand: methodOperand numArgs: numArgs
  	<api>
  	"Attempt to create a one-case PIC for an MNU.
  	 The tag for the case is at the send site and so doesn't need to be generated."
  	<returnTypeC: #'CogMethod *'>
  	| startAddress writablePIC actualPIC |
  	((objectMemory isYoung: selector)
  	 or: [(objectRepresentation inlineCacheTagForInstance: rcvr) = self picAbortDiscriminatorValue]) ifTrue:
  		[^0].
  	coInterpreter
  		compilationBreak: selector
  		point: (objectMemory numBytesOf: selector)
  		isMNUCase: true.
  	self assert: endCPICCase0 notNil.
  
  	"get memory in the code zone for the CPIC; if that fails we return an error code for the sender to use to work out how to blow up"
  	startAddress := methodZone allocate: closedPICSize.
  	startAddress = 0 ifTrue:
  		[coInterpreter callForCogCompiledCodeCompaction.
  		 ^0].
  	self maybeBreakGeneratingFrom: startAddress to: startAddress + closedPICSize - 1.
  
  	writablePIC := self cCoerceSimple: startAddress + codeToDataDelta to: #'CogMethod *'.
  	"memcpy the prototype across to our allocated space; because anything else would be silly"
  	self codeMemcpy: writablePIC
  		_: (self cCoerceSimple: cPICPrototype to: #'CogMethod *')
  		_: closedPICSize.
  
  	self
  		fillInCPICHeader: writablePIC
  		numArgs: numArgs
  		numCases: 1
  		hasMNUCase: true
  		selector: selector.
  
  	self configureMNUCPIC: (actualPIC := self cCoerceSimple: startAddress to: #'CogMethod *')
  		methodOperand: methodOperand
  		numArgs: numArgs
  		delta: startAddress - cPICPrototype.
  
  	self assert: (backEnd callTargetFromReturnAddress: startAddress + missOffset) = (self picAbortTrampolineFor: numArgs).
+ 	self assertValidDualZoneFrom: startAddress to: startAddress + closedPICSize.
- 	self assertValidDualZone.
  	backEnd flushICacheFrom: startAddress to: startAddress + closedPICSize.
  
  	^actualPIC!

Item was changed:
  ----- Method: Cogit>>cogPICSelector:numArgs:Case0Method:Case1Method:tag:isMNUCase: (in category 'in-line cacheing') -----
  cogPICSelector: selector numArgs: numArgs Case0Method: case0CogMethod Case1Method: case1MethodOrNil tag: case1Tag isMNUCase: isMNUCase
  	"Attempt to create a two-case PIC for case0CogMethod and  case1Method,case1Tag.
  	 The tag for case0CogMethod is at the send site and so doesn't need to be generated.
  	 case1Method may be any of
  		- a Cog method; link to its unchecked entry-point
  		- a CompiledMethod; link to ceInterpretMethodFromPIC:
  		- a CompiledMethod; link to ceMNUFromPICMNUMethod:receiver:"
  	<var: #case0CogMethod type: #'CogMethod *'>
  	<returnTypeC: #'CogMethod *'>
  	| startAddress writablePIC actualPIC |
  	(objectMemory isYoung: selector) ifTrue:
  		[^self cCoerceSimple: YoungSelectorInPIC to: #'CogMethod *'].
  	coInterpreter
  		compilationBreak: selector
  		point: (objectMemory numBytesOf: selector)
  		isMNUCase: isMNUCase.
  	
  	"get memory in the code zone for the CPIC; if that fails we return an error code for the sender to use to work out how to blow up"
  	startAddress := methodZone allocate: closedPICSize.
  	startAddress = 0 ifTrue:
  		[^self cCoerceSimple: InsufficientCodeSpace to: #'CogMethod *'].
  	self maybeBreakGeneratingFrom: startAddress to: startAddress + closedPICSize - 1.
  
  	writablePIC := self cCoerceSimple: startAddress + codeToDataDelta to: #'CogMethod *'.
  	"memcpy the prototype across to our allocated space; because anything else would be silly"
  	self codeMemcpy: writablePIC
  		_: (self cCoerceSimple: cPICPrototype to: #'CogMethod *')
  		_: closedPICSize.
  
  	self
  		fillInCPICHeader: writablePIC
  		numArgs: numArgs
  		numCases: 2
  		hasMNUCase: isMNUCase
  		selector: selector.
  
  	self configureCPIC: (actualPIC := self cCoerceSimple: startAddress to: #'CogMethod *')
  		Case0: case0CogMethod
  		Case1Method: case1MethodOrNil
  		tag: case1Tag
  		isMNUCase: isMNUCase
  		numArgs: numArgs
  		delta: startAddress - cPICPrototype.
  
  	self assert: (backEnd callTargetFromReturnAddress: startAddress + missOffset) = (self picAbortTrampolineFor: numArgs).
+ 	self assertValidDualZoneFrom: startAddress to: startAddress + closedPICSize.
- 	self assertValidDualZone.
  	backEnd flushICacheFrom: startAddress to: startAddress + closedPICSize.
  
  	^actualPIC!

Item was changed:
  ----- Method: Cogit>>fillInMethodHeader:size:selector: (in category 'generate machine code') -----
  fillInMethodHeader: method size: size selector: selector
  	"Fill in the header for theCogMehtod method.  This may be located at the writable mapping."
  	<var: #method type: #'CogMethod *'>
  	| originalMethod rawHeader actualMethodLocation |
  	<var: #originalMethod type: #'CogMethod *'>
  	actualMethodLocation := method asUnsignedInteger - codeToDataDelta.
  	method cmType: CMMethod.
  	method objectHeader: objectMemory nullHeaderForMachineCodeMethod.
  	method blockSize: size.
  	method methodObject: methodObj.
  	rawHeader := coInterpreter rawHeaderOf: methodObj.
  	"If the method has already been cogged (e.g. Newspeak accessors) then
  	 leave the original method attached to its cog method, but get the right header."
  	(coInterpreter isCogMethodReference: rawHeader)
  		ifTrue:
  			[originalMethod := self cCoerceSimple: rawHeader to: #'CogMethod *'.
  			self assert: originalMethod blockSize = size.
  			self assert: methodHeader = originalMethod methodHeader.
  			NewspeakVM ifTrue:
  				[methodZone addToUnpairedMethodList: method]]
  		ifFalse:
  			[coInterpreter rawHeaderOf: methodObj put: actualMethodLocation.
  			 NewspeakVM ifTrue:
  				[method nextMethodOrIRCs: theIRCs]].
  	method methodHeader: methodHeader.
  	method selector: selector.
  	method cmNumArgs: (coInterpreter argumentCountOfMethodHeader: methodHeader).
  	method cmHasMovableLiteral: hasMovableLiteral.
  	(method cmRefersToYoung: hasYoungReferent) ifTrue:
  		[methodZone addToYoungReferrers: method].
  	method cmUsageCount: self initialMethodUsageCount.
  	method cpicHasMNUCase: false.
  	method cmUsesPenultimateLit: maxLitIndex >= ((objectMemory literalCountOfMethodHeader: methodHeader) - 2).
  	method blockEntryOffset: (blockEntryLabel notNil
  								ifTrue: [blockEntryLabel address - actualMethodLocation]
  								ifFalse: [0]).
  	"This can be an error check since a large stackCheckOffset is caused by compiling
  	 a machine-code primitive, and hence depends on the Cogit, not the input method."
  	needsFrame ifTrue:
  		[stackCheckLabel address - actualMethodLocation <= MaxStackCheckOffset ifFalse:
  			[self error: 'too much code for stack check offset']].
  	method stackCheckOffset: (needsFrame
  								ifTrue: [stackCheckLabel address - actualMethodLocation]
  								ifFalse: [0]).
  	self assert: (backEnd callTargetFromReturnAddress: actualMethodLocation + missOffset)
  				= (self methodAbortTrampolineFor: method cmNumArgs).
  	self assert: size = (methodZone roundUpLength: size).
  	backEnd flushICacheFrom: actualMethodLocation to: actualMethodLocation + size.
+ 	self assertValidDualZoneFrom: actualMethodLocation to: actualMethodLocation + size.
- 	self assertValidDualZone.
  	self maybeEnableSingleStep!

Item was changed:
  ----- Method: Cogit>>fillInOPICHeader:numArgs:selector: (in category 'generate machine code') -----
  fillInOPICHeader: pic numArgs: numArgs selector: selector
  	"Fill in the header for the OpenPIC pic.  This may be located at the writable mapping."
  	<var: #pic type: #'CogMethod *'>
  	<inline: true>
  	pic cmType: CMOpenPIC.
  	pic objectHeader: 0.
  	pic blockSize: openPICSize.
  	"pic methodObject: 0.""This is also the nextOpenPIC link so don't initialize it"
  	methodZone addToOpenPICList: pic.
  	pic methodHeader: 0.
  	pic selector: selector.
  	pic cmNumArgs: numArgs.
  	pic cmHasMovableLiteral: (objectMemory isNonImmediate: selector).
  	(pic cmRefersToYoung: (objectMemory isYoung: selector)) ifTrue:
  		[methodZone addToYoungReferrers: pic].
  	pic cmUsageCount: self initialOpenPICUsageCount.
  	pic cpicHasMNUCase: false.
  	pic cPICNumCases: 0.
  	pic blockEntryOffset: 0.
  	self assert: pic cmType = CMOpenPIC.
  	self assert: pic selector = selector.
  	self assert: pic cmNumArgs = numArgs.
  	self assert: (backEnd callTargetFromReturnAddress: pic asInteger - codeToDataDelta + missOffset) = (self picAbortTrampolineFor: numArgs).
  	self assert: openPICSize = (methodZone roundUpLength: openPICSize).
  	backEnd flushICacheFrom: pic asUnsignedInteger - codeToDataDelta to: pic asUnsignedInteger - codeToDataDelta + openPICSize.
+ 	self assertValidDualZoneFrom: pic asUnsignedInteger - codeToDataDelta to: pic asUnsignedInteger - codeToDataDelta + openPICSize.
- 	self assertValidDualZone.
  	self maybeEnableSingleStep!

Item was added:
+ ----- Method: Cogit>>firstInvalidDualZoneAddressFrom:to: (in category 'debugging') -----
+ firstInvalidDualZoneAddressFrom: startAddress to: endAddress
+ 	codeToDataDelta > 0 ifTrue:
+ 		[startAddress to: endAddress - 1 by: objectMemory wordSize do:
+ 			[:address|
+ 			(objectMemory longAt: address) ~= (objectMemory longAt: address + codeToDataDelta) ifTrue:
+ 				[^address]]].
+ 	^nil!

Item was changed:
  ----- Method: Cogit>>genTrampolineFor:called:numArgs:arg:arg:arg:arg:regsToSave:pushLinkReg:resultReg:appendOpcodes: (in category 'initialization') -----
  genTrampolineFor: aRoutine called: trampolineName numArgs: numArgs arg: regOrConst0 arg: regOrConst1 arg: regOrConst2 arg: regOrConst3 regsToSave: regMask pushLinkReg: pushLinkReg resultReg: resultRegOrNone appendOpcodes: appendBoolean
  	"Generate a trampoline with up to four arguments.  Generate either a call or a jump to aRoutineOrNil
  	 as requested by callJumpBar.  If generating a call and resultRegOrNone is not NoReg pass the C result
  	 back in resultRegOrNone.
  	 Hack: a negative value indicates an abstract register, a non-negative value indicates a constant."
  	<var: #aRoutine type: #'void *'>
  	<var: #trampolineName type: #'char *'>
  	| startAddress |
  	<inline: false>
  	startAddress := methodZoneBase.
  	appendBoolean ifFalse:
  		[self zeroOpcodeIndex].
  	self compileTrampolineFor: aRoutine
  		numArgs: numArgs
  		arg: regOrConst0
  		arg: regOrConst1
  		arg: regOrConst2
  		arg: regOrConst3
  		regsToSave: regMask
  		pushLinkReg: pushLinkReg
  		resultReg: resultRegOrNone.
  	self outputInstructionsForGeneratedRuntimeAt: startAddress.
  	self recordGeneratedRunTime: trampolineName address: startAddress.
  	self recordRunTimeObjectReferences.
+ 	self assertValidDualZoneFrom: codeBase to: methodZoneBase.
- 	self assertValidDualZone.
  	^startAddress!



More information about the Vm-dev mailing list