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

commits at source.squeak.org commits at source.squeak.org
Tue Feb 24 19:17:28 UTC 2015


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

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

Name: VMMaker.oscog-eem.1077
Author: eem
Time: 24 February 2015, 11:16:06.136 am
UUID: 5c8fcc56-3a1d-4267-a434-e701ce9a2064
Ancestors: VMMaker.oscog-eem.1076

Fix a type declaration error uncvered by the new
inlining.  Inlcude freeMethod: in Cogit's api for method xray.

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

Item was changed:
  ----- Method: CoInterpreter>>convertToMachineCodeFrame:bcpc: (in category 'frame access') -----
  convertToMachineCodeFrame: cogHomeMethod bcpc: bcpc
+ 	<var: #cogHomeMethod type: #'CogMethod *'>
- 	<var: #cogHomeMethod type: #'CogHomeMethod *'>
  	<returnTypeC: #usqInt>
  	"Convert the current interpreter frame into a machine code frame
  	 and answer the machine code pc matching bcpc."
  	| startBcpc methodField closure cogMethod pc |
  	<var: #cogMethod type: #'CogBlockMethod *'>
  	<var: #p type: #'char *'>
  	self assert: (self isMachineCodeFrame: framePointer) not.
  	"Update the return pc, perhaps saving it in the caller's iframeSavedIP."
  	(self isBaseFrame: framePointer)
  		ifTrue:
  			[stackPages
  				longAt: framePointer + FoxCallerSavedIP
  				put: cogit ceBaseFrameReturnPC]
  		ifFalse:
  			[(self isMachineCodeFrame: (self frameCallerFP: framePointer)) ifFalse:
  				[self iframeSavedIP: (self frameCallerFP: framePointer)
  					put: (self frameCallerSavedIP: framePointer) asInteger.
  				 stackPages
  					longAt: framePointer + FoxCallerSavedIP
  					put: cogit ceReturnToInterpreterPC]].
  	"Compute the cog method field"
  	(self iframeIsBlockActivation: framePointer)
  		ifTrue:
  			[closure := self pushedReceiverOrClosureOfFrame: framePointer.
  			 startBcpc := self startPCOfClosure: closure.
  			 cogMethod := cogit
  								findMethodForStartBcpc: startBcpc
  								inHomeMethod: cogHomeMethod.
  			 methodField := cogMethod asInteger + MFMethodFlagIsBlockFlag]
  		ifFalse:
  			[startBcpc := self startPCOfMethodHeader: cogHomeMethod methodHeader.
  			 cogMethod := self cCoerceSimple: cogHomeMethod to: #'CogBlockMethod *'.
  			 methodField := cogHomeMethod asInteger].
  	"compute the pc before converting the frame to help with debugging."
  	pc := cogit mcPCForBackwardBranch: bcpc startBcpc: startBcpc in: cogMethod.
  	self assert: pc > (cogMethod asUnsignedInteger + cogit noCheckEntryOffset).
  	self assert: bcpc = (cogit bytecodePCFor: pc startBcpc: startBcpc in: cogMethod).
  	"now convert to a machine code frame"
  	stackPages
  		longAt: framePointer + FoxMethod
  		put: methodField
  			+ ((self iframeHasContext: framePointer)
  				ifTrue: [MFMethodFlagHasContextFlag]
  				ifFalse: [0]).
  	framePointer + FoxIFReceiver to: stackPointer by: objectMemory wordSize negated do:
  		[:p|
  		stackPages longAt: p + FoxMFReceiver - FoxIFReceiver put: (stackPages longAt: p)].
  	stackPointer := stackPointer + FoxMFReceiver - FoxIFReceiver.
  	^pc!

Item was changed:
  ----- Method: CoInterpreterPrimitives>>primitiveMethodXray (in category 'indexing primitives') -----
  primitiveMethodXray
  	"Lift the veil from a method and answer an integer describing the interior state
  	 of its machine code.
  	 Used for e.g. VM tests so they can verify they're testing what they think they're testing.
  	 0 implies a vanilla method.
  	 Bit 0 = method might be compiled to machine code
  	 Bit 1 = method is currently compiled to machine code
  	 Bit 2 = is compiled frameless.
  	 Bit 3 = method refers to young object.
  	 Bit 4 = method too big to be jitted (more than 64k of code, or needs more than 1.5Mb of stack space to compile)
  	 Bit 5 = method contains unknown/unjittable bytecode
  	 Bit 7 = method should not be jitted because it contains a primitive not to be called from machine code (unused)"
- 	<export: true>
  	| alreadyCogged flags cogMethod |
  	<var: #cogMethod type: #'CogMethod *'>
  	(self methodWithHeaderShouldBeCogged: (objectMemory methodHeaderOf: self stackTop))
  		ifTrue:
  			[alreadyCogged := self maybeMethodHasCogMethod: self stackTop.
  			 flags := 1.
  			 alreadyCogged ifFalse:
  				[cogMethod := cogit cog: self stackTop selector: objectMemory nilObject.
  				 (cogMethod = nil
  				  and: [cogCompiledCodeCompactionCalledFor]) ifTrue:
  					[self commenceCogCompiledCodeCompaction.
  					 cogMethod := cogit cog: self stackTop selector: objectMemory nilObject].
  			 cogMethod asInteger
  				caseOf: {
  					[MethodTooBig] -> [flags := 1 + 16].
  					[EncounteredUnknownBytecode] -> [1 + 32].
  					[ShouldNotJIT] -> [1 + 64] }
  				otherwise: [self deny: (cogMethod asInteger between: MaxNegativeErrorCode and: NotFullyInitialized)]].
  			 (flags = 1
  			  and: [self maybeMethodHasCogMethod: self stackTop]) ifTrue:
  				[cogMethod := self cogMethodOf: self stackTop.
  				 flags := cogMethod stackCheckOffset = 0 ifTrue: [7] ifFalse: [3].
  				 cogMethod cmRefersToYoung ifTrue:
  					[flags := flags + 8].
  				 alreadyCogged ifFalse:
  					[cogit freeMethod: cogMethod]]]
  		ifFalse: [flags := 0].
  	self pop: 1 thenPush: (objectMemory integerObjectOf: flags)!

Item was changed:
  ----- Method: CogMethodZone>>freeMethod: (in category 'compaction') -----
  freeMethod: cogMethod
+ 	<api>
  	<var: #cogMethod type: #'CogMethod *'>
  	<inline: false>
  	self assert: cogMethod cmType ~= CMFree.
  	self assert: ((cogit cogMethodDoesntLookKosher: cogMethod) = 0
  				 or: [(cogit cogMethodDoesntLookKosher: cogMethod) = 23
  					 and: [(cogit cCoerceSimple: cogMethod methodObject to: #'CogMethod *') cmType = CMFree]]).
  	cogMethod cmType = CMMethod ifTrue:
  		["For non-Newspeak there should ne a one-to-one mapping between bytecoded and
  		  cog methods.  For Newspeak not necessarily, but only for anonymous accessors."
  		"Only reset the original method's header if it is referring to this CogMethod."
  		 (coInterpreter rawHeaderOf: cogMethod methodObject) asInteger = cogMethod asInteger
  			ifTrue:
  				[coInterpreter rawHeaderOf: cogMethod methodObject put: cogMethod methodHeader.
  				 self cppIf: NewspeakVM ifTrue:
  					[(objectRepresentation canPinObjects and: [cogMethod nextMethodOrIRCs ~= 0]) ifTrue:
  						[objectRepresentation freeIRCs: cogMethod nextMethodOrIRCs]]]
  			ifFalse:
  				[self assert: (cogit noAssertMethodClassAssociationOf: cogMethod methodObject) = objectMemory nilObject.
  				 self cppIf: NewspeakVM ifTrue:
  					[self removeFromUnpairedMethodList: cogMethod]].
  		 cogit maybeFreeCountersOf: cogMethod].
  	cogMethod cmType = CMOpenPIC ifTrue:
  		[self removeFromOpenPICList: cogMethod].
  	cogMethod cmRefersToYoung: false.
  	cogMethod cmType: CMFree.
  	methodBytesFreedSinceLastCompaction := methodBytesFreedSinceLastCompaction
  												+ cogMethod blockSize!

Item was added:
+ ----- Method: Cogit>>freeMethod: (in category 'jit - api') -----
+ freeMethod: cogMethod
+ 	<doNotGenerate>
+ 	methodZone freeMethod: cogMethod!



More information about the Vm-dev mailing list