[Vm-dev] VM Maker: VMMaker.oscogSPC-eem.2133.mcz

commits at source.squeak.org commits at source.squeak.org
Sat Feb 18 00:14:38 UTC 2017


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

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

Name: VMMaker.oscogSPC-eem.2133
Author: eem
Time: 17 February 2017, 4:13:50.823694 pm
UUID: 00a2a293-2a06-4bd9-9f74-101613c9c718
Ancestors: VMMaker.oscogSPC-eem.2132

Cogit:
Fix checking the lists of cog methods (openPICList and unpairedMethodList) when compacting.
Fix a bug with freeing a method that might have either a newxtMethod or an IRC.  Must not free CogMethods.
Fix a couple of C compilation warnings.

=============== Diff against VMMaker.oscogSPC-eem.2132 ===============

Item was changed:
  ----- Method: CogBlockMethod class>>instVarNamesAndTypesForTranslationDo: (in category 'translation') -----
  instVarNamesAndTypesForTranslationDo: aBinaryBlock
  	"enumerate aBinaryBlock with the names and C type strings for the
  	 inst vars to include in a CogMethod or CogBlockMethod struct."
  
  	self allInstVarNames do:
  		[:ivn|
  		"Notionally objectHeader is in a union with homeOffset and startpc but
  		 we don't have any convenient support for unions.  So hack, hack, hack, hack."
  		((self == CogBlockMethod
  			ifTrue: [#('objectHeader')]
  			ifFalse: [#('homeOffset' 'startpc' 'padToWord')]) includes: ivn) ifFalse:
  				[aBinaryBlock
  					value: ivn
  					value: (ivn caseOf: {
  								['objectHeader']			-> [self objectMemoryClass baseHeaderSize = 8
  																ifTrue: [#sqLong]
  																ifFalse: [#sqInt]].
  								['cmNumArgs']				-> [#(unsigned ' : 8')].		"SqueakV3 needs only 5 bits"
  								['cmType']					-> [#(unsigned ' : 3')].
  								['cmRefersToYoung']		-> [#(unsigned #Boolean ' : 1')].
  								['cpicHasMNUCaseOrCMIsFullBlock']
  															-> [#(unsigned #Boolean ' : 1')].
  								['cmUsageCount']			-> [#(unsigned ' : 3')].		"See CMMaxUsageCount in initialize"
  								['cmUsesPenultimateLit']	-> [#(unsigned #Boolean ' : 1')].
  								['cbUsesInstVars']			-> [#(unsigned #Boolean ' : 1')].
  								['cmUnusedFlags']			-> [#(unsigned ' : 2')].
+ 								['stackCheckOffset']		-> [#(unsigned ' : 12')].	"See MaxStackCheckOffset in initialize. a.k.a. cPICNumCases"
- 								['stackCheckOffset']		-> [#(unsigned ' : 12')].		"See MaxStackCheckOffset in initialize. a.k.a. cPICNumCases"
  								['blockSize']				-> [#'unsigned short'].		"See MaxMethodSize in initialize"
  								['blockEntryOffset']			-> [#'unsigned short'].
  								['homeOffset']				-> [#'unsigned short'].
  								['startpc']					-> [#'unsigned short'].
  								['padToWord']				-> [#(#BaseHeaderSize 8 'unsigned int')].
+ 								['nextMethodOrIRCs']		-> [#usqInt].				"See NewspeakCogMethod"
- 								['nextMethod']				-> ['struct _CogMethod *'].	"See NewspeakCogMethod"
  								['counters']					-> [#usqInt]}				"See SistaCogMethod"
  							otherwise:
  								[#sqInt])]]!

Item was changed:
  CogClass subclass: #CogMethodZone
+ 	instanceVariableNames: 'youngReferrers unpairedMethodList methodCount openPICList mzFreeStart baseAddress limitAddress methodBytesFreedSinceLastCompaction compactionInProgress coInterpreter objectRepresentation cogit objectMemory'
- 	instanceVariableNames: 'youngReferrers methodCount openPICList mzFreeStart baseAddress limitAddress methodBytesFreedSinceLastCompaction coInterpreter objectRepresentation cogit objectMemory unpairedMethodList'
  	classVariableNames: ''
  	poolDictionaries: 'CogMethodConstants VMBasicConstants'
  	category: 'VMMaker-JIT'!
  
  !CogMethodZone commentStamp: 'eem 9/24/2014 15:59' prior: 0!
  I am a simple allocator/deallocator for the native code zone.  I also manage the youngReferers list, which contains methods that may refer to one or more young objects, and the openPICList which is a linked list of all open PICs in the zone.
  
  Instance Variables
  	baseAddress:								<Integer address>
  	coInterpreter:								<CoInterpreter>
  	cogit:										<Cogit>
  	limitAddress:								<Integer address>
  	methodBytesFreedSinceLastCompaction:	<Integer>
  	methodCount:								<Integer>
  	mzFreeStart:								<Integer address>
  	objectMemory:								<NewCoObjectMemory|SpurCoMemoryManager>
  	objectRepresentation:						<CogObjectRepresentation:>
  	openPICList:								<CogMethod *|nil>
  	unpairedMethodList:						<CogMethod *|nil>
  	youngReferrers:							<Integer address>
  
  baseAddress
  	- the lowest address in the native method zone
  
  coInterpreter
  	- simulation-only
  
  cogit
  	- simulation-only
  
  limitAddress
  	- the address immediately following the native method zone
  
  methodBytesFreedSinceLastCompaction
  	- a count of the bytes in methods freed since the last compaction of the native method zone, used to answer the used bytes in the zone
  
  methodCount
  	- a count of the number of methods in the native method zone
  
  mzFreeStart
  	- the start of free space in the zone
  
  objectMemory
  	- simulation-only
  
  objectRepresentation
  	- simulation-only
  
  openPICList
  	- the head of the list of open PICs
  
  unpairedMethodList
  	- the head of the list of Cog methods with no associated CompiledMethod object (Newspeak only)
  
  youngReferrers
  	- the pointer to the start of an array of pointers to CogMethods that refer to young objects.  May contain false positives.  Occupies the top of the zone from youngReferrers up to limitAddress
  !

Item was changed:
  ----- Method: CogMethodZone>>compactCompiledCode (in category 'compaction') -----
  compactCompiledCode
  	| objectHeaderValue source dest bytes |
  	<var: #source type: #'CogMethod *'>
  	<var: #dest type: #'CogMethod *'>
+ 	compactionInProgress := true.
  	objectHeaderValue := objectMemory nullHeaderForMachineCodeMethod.
  	source := coInterpreter cCoerceSimple: baseAddress to: #'CogMethod *'.
  	openPICList := nil.
  	methodCount := 0.
  	NewspeakVM ifTrue: [unpairedMethodList := nil].
  	[source < self limitZony
  	 and: [source cmType ~= CMFree]] whileTrue:
  		[self assert: (cogit cogMethodDoesntLookKosher: source) = 0.
  		 source objectHeader: objectHeaderValue.
  		 source cmUsageCount > 0 ifTrue:
  			[source cmUsageCount: source cmUsageCount // 2].
  		 NewspeakVM ifTrue:
  				[(source cmType = CMMethod
  				  and: [(coInterpreter rawHeaderOf: source methodObject) asInteger ~= source asInteger]) ifTrue:
  					[source nextMethodOrIRCs: unpairedMethodList.
  					 unpairedMethodList := source asUnsignedInteger]].
  		 SistaVM ifTrue:
  			[self clearSavedPICUsageCount: source].
  		 source cmType = CMOpenPIC ifTrue:
  			[source nextOpenPIC: openPICList asUnsignedInteger.
  			 openPICList := source].
  		 methodCount := methodCount + 1.
  		 source := self methodAfter: source].
  	source >= self limitZony ifTrue:
  		[^self halt: 'no free methods; cannot compact.'].
  	dest := source.
  	[source < self limitZony] whileTrue:
  		[self assert: (cogit maybeFreeCogMethodDoesntLookKosher: source) = 0.
  		 bytes := source blockSize.
  		 source cmType ~= CMFree ifTrue:
  			[methodCount := methodCount + 1.
  			 objectMemory mem: dest mo: source ve: bytes.
  			 dest objectHeader: objectHeaderValue.
  			 dest cmType = CMMethod
  				ifTrue:
  					["For non-Newspeak there should be a one-to-one mapping between bytecoded and
  					  cog methods.  For Newspeak not necessarily, but only for anonymous accessors."
  					"Only update the original method's header if it is referring to this CogMethod."
  					 (coInterpreter rawHeaderOf: dest methodObject) asInteger = source asInteger
  						ifTrue:
  							[coInterpreter rawHeaderOf: dest methodObject put: dest asInteger]
  						ifFalse:
  							[self assert: (cogit noAssertMethodClassAssociationOf: dest methodObject) = objectMemory nilObject.
  							 NewspeakVM ifTrue:
  								[dest nextMethodOrIRCs: unpairedMethodList.
  								 unpairedMethodList := dest asUnsignedInteger]]]
  				ifFalse:
  					[SistaVM ifTrue:
  						[self clearSavedPICUsageCount: dest].
  					dest cmType = CMOpenPIC ifTrue:
  						[dest nextOpenPIC: openPICList asUnsignedInteger.
  						 openPICList := dest]].
  			 dest cmUsageCount > 0 ifTrue:
  				[dest cmUsageCount: dest cmUsageCount // 2].
  			 dest := coInterpreter
  								cCoerceSimple: dest asUnsignedInteger + bytes
  								to: #'CogMethod *'].
  		 source := coInterpreter
  							cCoerceSimple: source asUnsignedInteger + bytes
  							to: #'CogMethod *'].
  	mzFreeStart := dest asUnsignedInteger.
+ 	methodBytesFreedSinceLastCompaction := 0.
+ 	compactionInProgress := false!
- 	methodBytesFreedSinceLastCompaction := 0!

Item was added:
+ ----- Method: CogMethodZone>>compactionInProgress (in category 'accessing') -----
+ compactionInProgress
+ 	^compactionInProgress!

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.
- 	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.
  				 NewspeakVM ifTrue:
+ 					[(objectRepresentation canPinObjects and: [cogMethod nextMethodOrIRCs > self zoneEnd]) ifTrue:
- 					[(objectRepresentation canPinObjects and: [cogMethod nextMethodOrIRCs ~= 0]) ifTrue:
  						[objectRepresentation freeIRCs: cogMethod nextMethodOrIRCs]]]
  			ifFalse:
  				[self cCode: [self assert: (cogit noAssertMethodClassAssociationOf: cogMethod methodObject) = objectMemory nilObject]
  					inSmalltalk: [self assert: ((cogit noAssertMethodClassAssociationOf: cogMethod methodObject) = objectMemory nilObject
  											or: [coInterpreter isKindOf: CurrentImageCoInterpreterFacade])].
  				 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 changed:
  ----- Method: CogMethodZone>>initialize (in category 'initialization') -----
  initialize
  	"Make youngReferrers arithmetic for addressIsInCodeZone:"
+ 	youngReferrers := methodCount := methodBytesFreedSinceLastCompaction := 0.
+ 	compactionInProgress := false!
- 	youngReferrers := 0!

Item was changed:
  ----- Method: Cogit>>addressIsInFixups: (in category 'testing') -----
  addressIsInFixups: address
  	<var: #address type: #'BytecodeFixup *'>
+ 	^self cCode: '(BytecodeFixup *)address >= fixups && (BytecodeFixup *)address < (fixups + numAbstractOpcodes)'
- 	^self cCode: '(AbstractInstruction *)address >= fixups && (AbstractInstruction *)address < (fixups + numAbstractOpcodes)'
  		inSmalltalk:
  			[fixups notNil
  			 and: [(fixups object identityIndexOf: address) between: 1 and: numAbstractOpcodes]]!

Item was changed:
  ----- Method: Cogit>>allMachineCodeObjectReferencesValid (in category 'garbage collection') -----
  allMachineCodeObjectReferencesValid
  	"Check that all methods have valid selectors, and that all linked sends are to valid targets and have valid cache tags"
  	| ok cogMethod |
  	<var: #cogMethod type: #'CogMethod *'>
  	ok := true.
  	cogMethod := self cCoerceSimple: methodZoneBase to: #'CogMethod *'.
  	[cogMethod < methodZone limitZony] whileTrue:
  		[cogMethod cmType ~= CMFree ifTrue:
  			[(self asserta: (objectRepresentation checkValidOopReference: cogMethod selector)) ifFalse:
  				[ok := false].
  			 (self asserta: (self cogMethodDoesntLookKosher: cogMethod) = 0) ifFalse:
  				[ok := false]].
  		(cogMethod cmType = CMMethod
  		 or: [cogMethod cmType = CMOpenPIC]) ifTrue:
  			[(self asserta: ((self mapFor: cogMethod
  								 performUntil: #checkIfValidOopRefAndTarget:pc:cogMethod:
  								 arg: cogMethod asInteger) = 0)) ifFalse:
  				[ok := false]].
  		(cogMethod cmType = CMMethod
  		 and: [(NewspeakVM or: [SistaVM])
  		 and: [objectRepresentation canPinObjects]]) ifTrue:
  			[(SistaVM and: [cogMethod counters ~= 0]) ifTrue:
  				[(self asserta: (objectRepresentation checkValidDerivedObjectReference: cogMethod counters)) ifFalse:
  					[ok := false]].
  			 (NewspeakVM and: [cogMethod nextMethodOrIRCs ~= 0]) ifTrue:
+ 				[(cogMethod nextMethodOrIRCs > methodZone zoneEnd) ifTrue:
+ 					[(self asserta: (objectRepresentation checkValidDerivedObjectReference: cogMethod nextMethodOrIRCs)) ifFalse:
+ 						[ok := false]]]].
- 				[(self asserta: (objectRepresentation checkValidDerivedObjectReference: cogMethod nextMethodOrIRCs)) ifFalse:
- 					[ok := false]]].
  		cogMethod cmType = CMClosedPIC ifTrue:
  			[(self asserta: (self noTargetsFreeInClosedPIC: cogMethod)) ifFalse:
  				[ok := false]].
  		cogMethod := methodZone methodAfter: cogMethod].
  	^ok!

Item was changed:
  ----- Method: Cogit>>cogMethodDoesntLookKosher: (in category 'debugging') -----
  cogMethodDoesntLookKosher: cogMethod
  	"Check that the header fields onf a non-free method are consistent with
  	 the type. Answer 0 if it is ok, otherwise answer a code for the error."
  	<api>
  	<inline: false>
  	<var: #cogMethod type: #'CogMethod *'>
  	((cogMethod blockSize bitAnd: objectMemory wordSize - 1) ~= 0
  	 or: [cogMethod blockSize < (self sizeof: CogMethod)
  	 or: [cogMethod blockSize >= 32768]]) ifTrue:
  		[^1].
  
  	cogMethod cmType = CMFree ifTrue: [^2].
  
  	cogMethod cmType = CMMethod ifTrue:
  		[(objectMemory isIntegerObject: cogMethod methodHeader) ifFalse:
  			[^11].
  		 (objectRepresentation couldBeObject: cogMethod methodObject) ifFalse:
  			[^12].
  		 (cogMethod stackCheckOffset > 0
  		  and: [cogMethod stackCheckOffset < cmNoCheckEntryOffset]) ifTrue:
  			[^13].
  		 (SistaVM
  		  and: [objectRepresentation canPinObjects
  		  and: [cogMethod counters ~= 0]]) ifTrue:
  			[(objectRepresentation couldBeDerivedObject: cogMethod counters) ifFalse:
  				[^14]].
  		 (NewspeakVM
  		  and: [objectRepresentation canPinObjects
  		  and: [cogMethod nextMethodOrIRCs ~= 0]]) ifTrue:
+ 			[(cogMethod nextMethodOrIRCs < methodZone zoneEnd)
+ 				ifTrue: "check the nextMethod (unpairedMethodList) unless we're compacting."
+ 					[(methodZone compactionInProgress
+ 					  or: [cogMethod nextMethodOrIRCs = (methodZone methodFor: cogMethod nextMethodOrIRCs) asUnsignedInteger]) ifFalse:
+ 						[^15]]
+ 				ifFalse:
+ 					[(objectRepresentation couldBeDerivedObject: cogMethod nextMethodOrIRCs) ifFalse:
+ 						[^16]]].
- 			[(objectRepresentation couldBeDerivedObject: cogMethod nextMethodOrIRCs) ifFalse:
- 				[^15]].
  		 ^0].
  
  	cogMethod cmType = CMOpenPIC ifTrue:
  		[cogMethod blockSize ~= openPICSize ifTrue:
  			[^21].
  		 cogMethod methodHeader ~= 0 ifTrue:
  			[^22].
- 		
  		 "Check the nextOpenPIC link unless we're compacting"
  		 cogMethod objectHeader >= 0 ifTrue:
+ 			[(cogMethod methodObject = 0
+ 			  or: [methodZone compactionInProgress
+ 			  or: [cogMethod methodObject = (methodZone methodFor: cogMethod methodObject) asUnsignedInteger]]) ifFalse:
- 			[(cogMethod methodObject ~= 0
- 			 and: [cogMethod methodObject < methodZoneBase
- 				   or: [cogMethod methodObject > (methodZone freeStart - openPICSize)
- 				   or: [(cogMethod methodObject bitAnd: objectMemory wordSize - 1) ~= 0
- 				   or: [(self cCoerceSimple: cogMethod methodObject
- 							to: #'CogMethod *') cmType ~= CMOpenPIC]]]]) ifTrue:
  				[^23]].
  		 cogMethod stackCheckOffset ~= 0 ifTrue:
  			[^24].
  		 ^0].
  
  	cogMethod cmType = CMClosedPIC ifTrue:
  		[cogMethod blockSize ~= closedPICSize ifTrue:
  			[^31].
  		 (cogMethod cPICNumCases between: 1 and: MaxCPICCases) ifFalse:
  			[^32].
  		 cogMethod methodHeader ~= 0 ifTrue:
  			[^33].
  		 cogMethod methodObject ~= 0 ifTrue:
  			[^34].
  		 ^0].
  
  	^9!

Item was changed:
  ----- Method: Cogit>>warnMultiple:selectors: (in category 'debug printing') -----
  warnMultiple: cogMethod selectors: aSelectorOop
  	<inline: true>
  	<var: 'cogMethod' type: #'CogMethod *'>
  	self cCode:
  			[self fp: #stderr
  				r: 'Warning, attempt to use method with selector %.*s and selector %.*s\n'
  				i: (self cCoerceSimple: (objectMemory numBytesOf: cogMethod selector) to: #int)
  				n: (self cCoerceSimple: (objectMemory firstIndexableField: cogMethod selector) to: #'char *')
+ 				t: (self cCoerceSimple: (objectMemory numBytesOf: aSelectorOop) to: #int)
- 				t: (objectMemory numBytesOf: aSelectorOop)
  				f: (self cCoerceSimple: (objectMemory firstIndexableField: aSelectorOop) to: #'char *')]
  		inSmalltalk:
  			[self warn: 'Warning, attempt to use method with selector ',
  						(coInterpreter stringOf: cogMethod selector),
  						' and selector ',
  						(coInterpreter stringOf: aSelectorOop)]!

Item was changed:
  CogMethod subclass: #NewspeakCogMethod
  	instanceVariableNames: 'nextMethodOrIRCs'
  	classVariableNames: ''
  	poolDictionaries: ''
  	category: 'VMMaker-JIT'!
+ 
+ !NewspeakCogMethod commentStamp: 'eem 2/17/2017 16:12' prior: 0!
+ A NewspeakCogMethod is a specialization of CogMethod for Newspeak.  It adds support for the unpairdMethodsList and for implicit receiver caches.  Since the unpairedMethodList only holds methods that are inst var accessors, these cannot have implicit receiver caches.  Therefore we use the same variable for either the next link in the unpairedMethodList or the reference to the method's implciit receiver caches, which keeps the header size down.
+ 
+ Instance Variables
+ 	nextMethodOrIRCs:		<0 or CogMethod * or oop>
+ 
+ nextMethodOrIRCs
+ 	- either 0 or the next link in the unpairedMethodList or the first field of a method's implciit receiver caches
+ !



More information about the Vm-dev mailing list