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

commits at source.squeak.org commits at source.squeak.org
Mon Sep 6 02:30:55 UTC 2021


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

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

Name: VMMaker.oscog-eem.3058
Author: eem
Time: 5 September 2021, 7:30:41.127457 pm
UUID: 86a18528-b506-4c9a-a64d-041bcf5f8be4
Ancestors: VMMaker.oscog-eem.3057

Leak Checking: better idea: replace all sends of cr and/or eek in the leak checking printing with a send of eekcr, implemented in StackInterpreter as a never inlined method, suitable for placing a breakpoint on.  A better solution would be replacing all these prints with printf style calls of e.g. leakCheckPrintf:.  But I'm not sure how to express va_list methods through Slang.
Slang: fix multiple NeverInline function attributes.

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

Item was changed:
  ----- Method: Cogit>>checkIfValidOopRef:pc:cogMethod: (in category 'garbage collection') -----
  checkIfValidOopRef: annotation pc: mcpc cogMethod: cogMethod
  	"Check for a valid object reference, if any, at a map entry.  Answer a code unique to each error for debugging."
  	<var: #mcpc type: #'char *'>
  	<var: #cogMethod type: #'CogMethod *'>
  
  	<var: #nsSendCache type: #'NSSendCache *'>
  	annotation = IsObjectReference ifTrue:
  		[| literal |
  		 literal := literalsManager fetchLiteralAtAnnotatedAddress: mcpc asUnsignedInteger using: backEnd.
  		 (objectRepresentation checkValidOopReference: literal) ifFalse:
+ 			[coInterpreter print: 'object ref leak in CM '; printHex: cogMethod asInteger; print: ' @ '; printHex: mcpc asInteger; eekcr.
- 			[coInterpreter print: 'object ref leak in CM '; printHex: cogMethod asInteger; print: ' @ '; printHex: mcpc asInteger; cr.
  			^1]].
  
  	NewspeakVM ifTrue:
  		[annotation = IsNSSendCall ifTrue:
  			[| nsSendCache enclosingObject |
  			nsSendCache := self nsSendCacheFromReturnAddress: mcpc asInteger.
  			[(objectRepresentation checkValidOopReference: nsSendCache selector) ifFalse:
+ 				[coInterpreter print: 'selector leak in CM '; printHex: cogMethod asInteger; print: ' @ '; printHex: mcpc asInteger; eekcr.
- 				[coInterpreter print: 'selector leak in CM '; printHex: cogMethod asInteger; print: ' @ '; printHex: mcpc asInteger; cr.
  				^1]].
  			(enclosingObject := nsSendCache enclosingObject) ~= 0 ifTrue:
  				[[(objectRepresentation checkValidOopReference: enclosingObject) ifFalse:
+ 					[coInterpreter print: 'enclosing object leak in CM '; printHex: cogMethod asInteger; print: ' @ '; printHex: mcpc asInteger; eekcr.
- 					[coInterpreter print: 'enclosing object leak in CM '; printHex: cogMethod asInteger; print: ' @ '; printHex: mcpc asInteger; cr.
  					^1]]]]].
  
  	(self isPureSendAnnotation: annotation) ifTrue:
  		[| entryPoint selectorOrCacheTag offset |
  		 entryPoint := backEnd callTargetFromReturnAddress: mcpc asInteger.
  		 entryPoint <= methodZoneBase
  			ifTrue:
  				[offset := entryPoint]
  			ifFalse:
  				[self
  					offsetAndSendTableFor: entryPoint
  					annotation: annotation
  					into: [:off :table| offset := off]].
  		 selectorOrCacheTag := backEnd inlineCacheTagAt: mcpc asInteger.
  		 (entryPoint > methodZoneBase
  		  and: [offset ~= cmNoCheckEntryOffset
  		  and: [(self cCoerceSimple: entryPoint - offset to: #'CogMethod *') cmType ~= CMOpenPIC]])
  			ifTrue: "linked non-super send, cacheTag is a cacheTag"
  				[(objectRepresentation validInlineCacheTag: selectorOrCacheTag) ifFalse:
+ 					[coInterpreter print: 'cache tag leak in CM '; printHex: cogMethod asInteger; print: ' @ '; printHex: mcpc asInteger; eekcr.
- 					[coInterpreter print: 'cache tag leak in CM '; printHex: cogMethod asInteger; print: ' @ '; printHex: mcpc asInteger; cr.
  					^1]]
  			ifFalse: "unlinked send or super send; cacheTag is a selector unless 64-bit, in which case it is an index."
  				[(self inlineCacheTagsAreIndexes
  				  or: [objectRepresentation checkValidOopReference: selectorOrCacheTag]) ifFalse:
+ 					[coInterpreter print: 'selector leak in CM '; printHex: cogMethod asInteger; print: ' @ '; printHex: mcpc asInteger; eekcr.
- 					[coInterpreter print: 'selector leak in CM '; printHex: cogMethod asInteger; print: ' @ '; printHex: mcpc asInteger; cr.
  					^1]]].
  	^0 "keep scanning"!

Item was changed:
  ----- Method: Cogit>>checkIntegrityOfObjectReferencesInCode: (in category 'debugging') -----
  checkIntegrityOfObjectReferencesInCode: gcModes
  	<api>
  	"Answer if all references to objects in machine-code are valid."	
  	| cogMethod ok count |
  	<var: #cogMethod type: #'CogMethod *'>
  	cogMethod := self cCoerceSimple: methodZoneBase to: #'CogMethod *'.
  	ok := true.
  	[cogMethod < methodZone limitZony] whileTrue:
  		[cogMethod cmType ~= CMFree ifTrue:
  			[cogMethod cmRefersToYoung ifTrue:
  				[(count := methodZone occurrencesInYoungReferrers: cogMethod) ~= 1 ifTrue:
  					[coInterpreter print: 'young referrer CM '; printHex: cogMethod asInteger.
  					 count = 0
+ 						ifTrue: [coInterpreter print: ' is not in youngReferrers'; eekcr]
+ 						ifFalse: [coInterpreter print: ' is in youngReferrers '; printNum: count; print: ' times!!'; eekcr].
- 						ifTrue: [coInterpreter print: ' is not in youngReferrers'; cr]
- 						ifFalse: [coInterpreter print: ' is in youngReferrers '; printNum: count; print: ' times!!'; cr].
  					 ok := false]].
  			 (objectRepresentation checkValidOopReference: cogMethod selector) ifFalse:
+ 				[coInterpreter print: 'object leak in CM '; printHex: cogMethod asInteger; print: ' selector'; eekcr.
- 				[coInterpreter print: 'object leak in CM '; printHex: cogMethod asInteger; print: ' selector'; cr.
  				 ok := false].
  			 cogMethod cmType = CMMethod
  				ifTrue:
  					[self assert: cogMethod objectHeader = objectMemory nullHeaderForMachineCodeMethod.
  					 (objectRepresentation checkValidObjectReference: cogMethod methodObject) ifFalse:
+ 						[coInterpreter print: 'object leak in CM '; printHex: cogMethod asInteger; print: ' methodObject'; eekcr.
- 						[coInterpreter print: 'object leak in CM '; printHex: cogMethod asInteger; print: ' methodObject'; cr.
  						 ok := false].
  					 (objectMemory isOopCompiledMethod: cogMethod methodObject) ifFalse:
+ 						[coInterpreter print: 'non-method in CM '; printHex: cogMethod asInteger; print: ' methodObject'; eekcr.
- 						[coInterpreter print: 'non-method in CM '; printHex: cogMethod asInteger; print: ' methodObject'; cr.
  						 ok := false].
  					 (self mapFor: cogMethod
  						 performUntil: #checkIfValidOopRef:pc:cogMethod:
  						 arg: cogMethod) ~= 0
  							ifTrue: [ok := false].
  					 (objectRepresentation hasSpurMemoryManagerAPI
  					  or: [gcModes anyMask: GCModeNewSpace]) ifTrue:
  						[(((objectMemory isYoungObject: cogMethod methodObject)
  						    or: [objectMemory isYoung: cogMethod selector])
  						   and: [cogMethod cmRefersToYoung not]) ifTrue:
+ 							[coInterpreter print: 'CM '; printHex: cogMethod asInteger; print: ' refers to young but not marked as such'; eekcr.
- 							[coInterpreter print: 'CM '; printHex: cogMethod asInteger; print: ' refers to young but not marked as such'; cr.
  							 ok := false]]]
  				ifFalse:
  					[cogMethod cmType = CMClosedPIC
  						ifTrue:
  							[(self checkValidObjectReferencesInClosedPIC: cogMethod) ifFalse:
  								[ok := false]]
  						ifFalse:
  							[cogMethod cmType = CMOpenPIC
  								ifTrue:
  									[(self mapFor: cogMethod
  										performUntil: #checkIfValidOopRef:pc:cogMethod:
  										arg: cogMethod) ~= 0
  											ifTrue: [ok := false]]]]].
  		cogMethod := methodZone methodAfter: cogMethod].
  	^ok!

Item was removed:
- ----- Method: NewCoObjectMemorySimulator>>eek (in category 'memory access') -----
- eek
- 	self halt!

Item was changed:
  ObjectMemory subclass: #NewObjectMemory
+ 	instanceVariableNames: 'coInterpreter freeStart reserveStart scavengeThreshold needGCFlag edenBytes checkForLeaks statGCEndUsecs heapMap'
- 	instanceVariableNames: 'coInterpreter freeStart reserveStart scavengeThreshold needGCFlag edenBytes checkForLeaks statGCEndUsecs heapMap leakDetected'
  	classVariableNames: ''
  	poolDictionaries: ''
  	category: 'VMMaker-Interpreter'!
  
  !NewObjectMemory commentStamp: '<historical>' prior: 0!
  I am a refinement of ObjectMemory that eliminates the need for pushRemappableOop:/popRemappableOop in the interpreter proper.  Certain primitives that do major allocation may still want to provoke a garbage collection and hence may still need to remap private pointers.  But the interpreter subclass of this class does not have to provided it reserves sufficient space for it to make progress to the next scavenge point (send or backward branch).!

Item was changed:
  ----- Method: NewObjectMemory class>>mustBeGlobal: (in category 'translation') -----
  mustBeGlobal: var
  	"Answer if a variable must be global and exported.  Used for inst vars that are accessed from VM support code."
  
  	^(super mustBeGlobal: var)
+ 	   or: ['checkForLeaks' = var]!
- 	   or: [#('checkForLeaks' 'leakDetected') includes: var]!

Item was changed:
  ----- Method: NewObjectMemory>>checkHeapIntegrity (in category 'memory access') -----
  checkHeapIntegrity
  	"Perform an integrity/leak check using the heapMap.  Assume
  	 clearLeakMapAndMapAccessibleObjects has set a bit at each
  	 object's header.  Scan all objects in the heap checking that every
  	 pointer points to a header.  Scan the rootTable, remapBuffer and
  	 extraRootTable checking that every entry is a pointer to a header.
  	 Check that the number of roots is correct and that all rootTable
  	 entries have their rootBit set. Answer if all checks pass."
  	| ok obj sz hdr fmt fi fieldOop numRootsInHeap |
  	<inline: false>
  	ok := true.
  	numRootsInHeap := 0.
  	obj := self firstObject.
  	[self oop: obj isLessThan: self startOfFreeSpace] whileTrue:
  		[(self isFreeObject: obj)
  			ifTrue:
  				[sz := self sizeOfFree: obj]
  			ifFalse:
  				[hdr := self baseHeader: obj.
  				 (self isYoungRootHeader: hdr) ifTrue:
  					[numRootsInHeap := numRootsInHeap + 1].
  				 (self compactClassIndexOfHeader: hdr) = 0 ifTrue:
  					[fieldOop := (self classHeader: obj) bitAnd: AllButTypeMask.
  					 ((self isIntegerObject: fieldOop)
  					   or: [(heapMap heapMapAtWord: (self pointerForOop: fieldOop)) = 0]) ifTrue:
+ 						[self print: 'object leak in '; printHex: obj; print: ' class = '; printHex: fieldOop; eekcr.
- 						[self print: 'object leak in '; printHex: obj; print: ' class = '; printHex: fieldOop; cr.
- 						 self eek.
  						 ok := false]].
  				 fmt := self formatOfHeader: hdr.
  				 (fmt <= 4 "pointers" or: [fmt >= 12 "compiled method"]) ifTrue:
  					[fmt >= 12
  						ifTrue: [fi := (self literalCountOf: obj) + LiteralStart]
  						ifFalse: [(fmt = 3 and: [self isContextHeader: hdr])
  									ifTrue: [fi := CtxtTempFrameStart + (coInterpreter fetchStackPointerOf: obj)]
  									ifFalse: [fi := self lengthOf: obj]].
  					[(fi := fi - 1) >= 0] whileTrue:
  						[fieldOop := self fetchPointer: fi ofObject: obj.
  						 (self isNonIntegerObject: fieldOop) ifTrue:
  							[(fieldOop bitAnd: self wordSize - 1) ~= 0
  								ifTrue:
+ 									[self print: 'misaligned oop in '; printHex: obj; print: ' @ '; printNum: fi; print: ' = '; printHex: fieldOop; eekcr.
- 									[self print: 'misaligned oop in '; printHex: obj; print: ' @ '; printNum: fi; print: ' = '; printHex: fieldOop; cr.
- 									 self eek.
  									 ok := false]
  								ifFalse:
  									[(heapMap heapMapAtWord: (self pointerForOop: fieldOop)) = 0 ifTrue:
+ 										[self print: 'object leak in '; printHex: obj; print: ' @ '; printNum: fi; print: ' = '; printHex: fieldOop; eekcr.
- 										[self print: 'object leak in '; printHex: obj; print: ' @ '; printNum: fi; print: ' = '; printHex: fieldOop; cr.
- 										 self eek.
  										 ok := false]]]]].
  				 sz := self sizeBitsOf: obj].
  		 obj := self oopFromChunk: obj + sz].
  	numRootsInHeap ~= rootTableCount ifTrue:
  		[self print: 'root count mismatch. #heap roots '; printNum: numRootsInHeap; print: '; #roots '; printNum: rootTableCount; cr.
  		"But the system copes with overflow..."
  		ok := rootTableOverflowed and: [needGCFlag]].
  	1 to: rootTableCount do:
  		[:ri|
  		obj := rootTable at: ri.
  		(obj bitAnd: self wordSize - 1) ~= 0
  			ifTrue:
+ 				[self print: 'misaligned oop in rootTable @ '; printNum: ri; print: ' = '; printHex: obj; eekcr.
- 				[self print: 'misaligned oop in rootTable @ '; printNum: ri; print: ' = '; printHex: obj; cr.
- 				 self eek.
  				 ok := false]
  			ifFalse:
  				[(heapMap heapMapAtWord: (self pointerForOop: obj)) = 0
  					ifTrue:
+ 						[self print: 'object leak in rootTable @ '; printNum: ri; print: ' = '; printHex: obj; eekcr.
- 						[self print: 'object leak in rootTable @ '; printNum: ri; print: ' = '; printHex: obj; cr.
- 						 self eek.
  						 ok := false]
  					ifFalse:
  						[hdr := self baseHeader: obj.
  						 (self isYoungRootHeader: hdr) ifFalse:
+ 							[self print: 'non-root in rootTable @ '; printNum: ri; print: ' = '; printHex: obj; eekcr.
- 							[self print: 'non-root in rootTable @ '; printNum: ri; print: ' = '; printHex: obj; cr.
- 							 self eek.
  							 ok := false]]]].
  	1 to: remapBufferCount do:
  		[:ri|
  		obj := remapBuffer at: ri.
  		(obj bitAnd: self wordSize - 1) ~= 0
  			ifTrue:
+ 				[self print: 'misaligned remapRoot @ '; printNum: ri; print: ' = '; printHex: obj; eekcr.
- 				[self print: 'misaligned remapRoot @ '; printNum: ri; print: ' = '; printHex: obj; cr.
- 				 self eek.
  				 ok := false]
  			ifFalse:
  				[(heapMap heapMapAtWord: (self pointerForOop: obj)) = 0
  					ifTrue:
+ 						[self print: 'object leak in remapRoots @ '; printNum: ri; print: ' = '; printHex: obj; eekcr.
- 						[self print: 'object leak in remapRoots @ '; printNum: ri; print: ' = '; printHex: obj; cr.
- 						 self eek.
  						 ok := false]]].
  	1 to: extraRootCount do:
  		[:ri|
  		obj := (extraRoots at: ri) at: 0.
  		(obj bitAnd: self wordSize - 1) ~= 0
  			ifTrue:
+ 				[self print: 'misaligned extraRoot @ '; printNum: ri; print: ' => '; printHex: obj; eekcr.
- 				[self print: 'misaligned extraRoot @ '; printNum: ri; print: ' => '; printHex: obj; cr.
- 				 self eek.
  				 ok := false]
  			ifFalse:
  				[(heapMap heapMapAtWord: (self pointerForOop: obj)) = 0
  					ifTrue:
+ 						[self print: 'object leak in extraRoots @ '; printNum: ri; print: ' => '; printHex: obj; eekcr.
- 						[self print: 'object leak in extraRoots @ '; printNum: ri; print: ' => '; printHex: obj; cr.
- 						 self eek.
  						 ok := false]]].
  	^ok!

Item was removed:
- ----- Method: NewObjectMemory>>eek (in category 'memory access') -----
- eek
- 	<inline: #never>
- 	leakDetected := true!

Item was changed:
  ----- Method: NewObjectMemory>>initialize (in category 'initialization') -----
  initialize
  	"Initialize NewObjectMemory when simulating the VM inside Smalltalk."
  	super initialize.
  	checkForLeaks := 0.
+ 	needGCFlag := false.
- 	needGCFlag := leakDetected := false.
  	heapMap := CogCheck32BitHeapMap new!

Item was removed:
- ----- Method: NewObjectMemorySimulator>>eek (in category 'memory access') -----
- eek
- 	self halt!

Item was changed:
  ----- Method: ObjectMemory>>checkOopIntegrity:named:index: (in category 'debug support') -----
  checkOopIntegrity: obj named: name index: i
  	<inline: false>
  	<var: #name type: #'char *'>
  	(self heapMapAtWord: (self pointerForOop: obj)) ~= 0 ifTrue:
  		[^true].
+ 	self print: name; print: ' leak @ '; printNum: i; print: ' = '; printHex: obj; eekcr.
- 	self print: name; print: ' leak @ '; printNum: i; print: ' = '; printHex: obj; cr.
  	^false!

Item was added:
+ ----- Method: Spur32BitMMLECoSimulator>>checkHeapIntegrity:classIndicesShouldBeValid: (in category 'debug support') -----
+ checkHeapIntegrity: excludeUnmarkedObjs classIndicesShouldBeValid: classIndicesShouldBeValid
+ 	"Almost all of the time spent in SpurMemoryManager>>checkHeapIntegrity:classIndicesShouldBeValid: used to go into the asserts in fetchPointer:ofObject: in the simulator class overrides.
+ 	 Since we know here the indices used are valid we temporarily remove them to claw back that performance."
+ 	^self withSimulatorFetchPointerMovedAsideDo:
+ 		[super checkHeapIntegrity: excludeUnmarkedObjs classIndicesShouldBeValid: classIndicesShouldBeValid]!

Item was removed:
- ----- Method: Spur32BitMMLECoSimulator>>eek (in category 'debug support') -----
- eek
- 	self halt!

Item was changed:
  ----- Method: Spur32BitMMLESimulator>>checkHeapIntegrity:classIndicesShouldBeValid: (in category 'debug support') -----
  checkHeapIntegrity: excludeUnmarkedObjs classIndicesShouldBeValid: classIndicesShouldBeValid
+ 	"Almost all of the time spent in SpurMemoryManager>>checkHeapIntegrity:classIndicesShouldBeValid: used to go into the asserts in fetchPointer:ofObject: in the simulator class overrides.
- 	"Almost all of the time spent in SourMemoryManager>>checkHeapIntegrity:classIndicesShouldBeValid: used to go into the asserts in fetchPointer:ofObject: in the simulator class overrides.
  	 Since we know here the indices used are valid we temporarily remove them to claw back that performance."
  	^self withSimulatorFetchPointerMovedAsideDo:
  		[super checkHeapIntegrity: excludeUnmarkedObjs classIndicesShouldBeValid: classIndicesShouldBeValid]!

Item was removed:
- ----- Method: Spur32BitMMLESimulator>>eek (in category 'debug support') -----
- eek
- 	self halt!

Item was changed:
  ----- Method: Spur64BitMMLECoSimulator>>checkHeapIntegrity:classIndicesShouldBeValid: (in category 'debug support') -----
  checkHeapIntegrity: excludeUnmarkedObjs classIndicesShouldBeValid: classIndicesShouldBeValid
+ 	"Almost all of the time spent in SpurMemoryManager>>checkHeapIntegrity:classIndicesShouldBeValid: used to go into the asserts in fetchPointer:ofObject: in the simulator class overrides.
- 	"Almost all of the time spent in SourMemoryManager>>checkHeapIntegrity:classIndicesShouldBeValid: used to go into the asserts in fetchPointer:ofObject: in the simulator class overrides.
  	 Since we know here the indices used are valid we temporarily remove them to claw back that performance."
  	^self withSimulatorFetchPointerMovedAsideDo:
  		[super checkHeapIntegrity: excludeUnmarkedObjs classIndicesShouldBeValid: classIndicesShouldBeValid]!

Item was removed:
- ----- Method: Spur64BitMMLECoSimulator>>eek (in category 'debug support') -----
- eek
- 	self halt!

Item was changed:
  ----- Method: Spur64BitMMLESimulator>>checkHeapIntegrity:classIndicesShouldBeValid: (in category 'debug support') -----
  checkHeapIntegrity: excludeUnmarkedObjs classIndicesShouldBeValid: classIndicesShouldBeValid
+ 	"Almost all of the time spent in SpurMemoryManager>>checkHeapIntegrity:classIndicesShouldBeValid: used to go into the asserts in fetchPointer:ofObject: in the simulator class overrides.
- 	"Almost all of the time spent in SourMemoryManager>>checkHeapIntegrity:classIndicesShouldBeValid: used to go into the asserts in fetchPointer:ofObject: in the simulator class overrides.
  	 Since we know here the indices used are valid we temporarily remove them to claw back that performance."
  	^self withSimulatorFetchPointerMovedAsideDo:
  		[super checkHeapIntegrity: excludeUnmarkedObjs classIndicesShouldBeValid: classIndicesShouldBeValid]!

Item was removed:
- ----- Method: Spur64BitMMLESimulator>>eek (in category 'debug support') -----
- eek
- 	self halt!

Item was changed:
  CogClass subclass: #SpurMemoryManager
(excessive size, no diff calculated)

Item was changed:
  ----- Method: SpurMemoryManager class>>mustBeGlobal: (in category 'translation') -----
  mustBeGlobal: var
  	"Answer if a variable must be global and exported.  Used for inst vars that are accessed from VM support code."
  
+ 	^#('checkForLeaks' 'maxOldSpaceSize') includes: var!
- 	^#('checkForLeaks' 'maxOldSpaceSize' 'leakDetected') includes: var!

Item was changed:
  ----- Method: SpurMemoryManager>>checkHeapFreeSpaceIntegrity (in category 'debug support') -----
  checkHeapFreeSpaceIntegrity
  	"Perform an integrity/leak check using the heapMap.  Assume clearLeakMapAndMapAccessibleFreeSpace
  	 has set a bit at each free chunk's header.  Scan all objects in the heap checking that no pointer points
  	 to a free chunk and that all free chunks that refer to others refer to marked chunks.  Answer if all checks pass."
  	| ok total |
  	<inline: false>
  	<var: 'total' type: #usqInt>
  	ok := true.
  	total := 0.
  	0 to: self numFreeLists - 1 do:
  		[:i|
  		(freeLists at: i) ~= 0 ifTrue:
  			[(heapMap heapMapAtWord: (self pointerForOop: (freeLists at: i))) = 0 ifTrue:
+ 				[coInterpreter print: 'leak in free list '; printNum: i; print: ' to non-free '; printHex: (freeLists at: i); eekcr.
- 				[coInterpreter print: 'leak in free list '; printNum: i; print: ' to non-free '; printHex: (freeLists at: i); cr.
- 				 self eek.
  				 ok := false]]].
  
  	"Excuse the duplication but performance is at a premium and we avoid
  	 some tests by splitting the newSpace and oldSpace enumerations."
  	self allNewSpaceEntitiesDo:
  		[:obj| | fieldOop |
  		 (self isFreeObject: obj)
  			ifTrue:
+ 				[coInterpreter print: 'young object '; printHex: obj; print: ' is free'; eekcr.
- 				[coInterpreter print: 'young object '; printHex: obj; print: ' is free'; cr.
- 				 self eek.
  				 ok := false]
  			ifFalse:
  				[obj ~= freeSpaceCheckOopToIgnore ifTrue:
  					[0 to: (self numPointerSlotsOf: obj) - 1 do:
  						[:fi|
  						 fieldOop := self fetchPointer: fi ofObject: obj.
  						 (self isNonImmediate: fieldOop) ifTrue:
  							[(heapMap heapMapAtWord: (self pointerForOop: fieldOop)) ~= 0 ifTrue:
+ 								[coInterpreter print: 'object leak in '; printHex: obj; print: ' @ '; printNum: fi; print: ' = '; printHex: fieldOop; print: ' is free'; eekcr.
- 								[coInterpreter print: 'object leak in '; printHex: obj; print: ' @ '; printNum: fi; print: ' = '; printHex: fieldOop; print: ' is free'; cr.
- 								 self eek.
  								 ok := false]]]]]].
  	self allOldSpaceEntitiesDo:
  		[:obj| | fieldOop |
  		(self isFreeObject: obj)
  			ifTrue:
  				[(heapMap heapMapAtWord: (self pointerForOop: obj)) = 0 ifTrue:
+ 					[coInterpreter print: 'leak in free chunk '; printHex: obj; print: ' is unmapped?!! '; eekcr.
- 					[coInterpreter print: 'leak in free chunk '; printHex: obj; print: ' is unmapped?!! '; cr.
- 					 self eek.
  					 ok := false].
  				 fieldOop := self fetchPointer: self freeChunkNextIndex ofFreeChunk: obj.
  				 (fieldOop ~= 0
  				 and: [(heapMap heapMapAtWord: (self pointerForOop: fieldOop)) = 0]) ifTrue:
+ 					[coInterpreter print: 'leak in free chunk '; printHex: obj; print: ' @ 0 = '; printHex: fieldOop; print: ' is unmapped'; eekcr.
- 					[coInterpreter print: 'leak in free chunk '; printHex: obj; print: ' @ 0 = '; printHex: fieldOop; print: ' is unmapped'; cr.
- 					 self eek.
  					 ok := false].
  				(self isLilliputianSize: (self bytesInBody: obj)) ifFalse:
  					[fieldOop := self fetchPointer: self freeChunkPrevIndex ofFreeChunk: obj.
  					 (fieldOop ~= 0
  					 and: [(heapMap heapMapAtWord: (self pointerForOop: fieldOop)) = 0]) ifTrue:
+ 						[coInterpreter print: 'leak in free chunk '; printHex: obj; print: ' @ 0 = '; printHex: fieldOop; print: ' is unmapped'; eekcr.
- 						[coInterpreter print: 'leak in free chunk '; printHex: obj; print: ' @ 0 = '; printHex: fieldOop; print: ' is unmapped'; cr.
- 						 self eek.
  						 ok := false]].
  				(self isLargeFreeObject: obj) ifTrue:
  					[self freeChunkParentIndex to: self freeChunkLargerIndex do:
  						[:fi|
  						 fieldOop := self fetchPointer: fi ofFreeChunk: obj.
  						 (fieldOop ~= 0
  						 and: [(heapMap heapMapAtWord: (self pointerForOop: fieldOop)) = 0]) ifTrue:
+ 							[coInterpreter print: 'leak in free chunk '; printHex: obj; print: ' @ '; printNum: fi; print: ' = '; printHex: fieldOop; print: ' is unmapped'; eekcr.
- 							[coInterpreter print: 'leak in free chunk '; printHex: obj; print: ' @ '; printNum: fi; print: ' = '; printHex: fieldOop; print: ' is unmapped'; cr.
- 							 self eek.
  							 ok := false]]].
  				total := total + (self bytesInBody: obj)]
  			ifFalse:
  				[obj ~= freeSpaceCheckOopToIgnore ifTrue:
  					[0 to: (self numPointerSlotsOf: obj) - 1 do:
  						[:fi|
  						 (self isForwarded: obj)
  							ifTrue: 
  								[self assert: fi = 0. "I'm now trying to use forwarders in GC algorithms..."
  								 fieldOop := self fetchPointer: fi ofMaybeForwardedObject: obj] 
  							ifFalse: "We keep #fetchPointer:ofObject: API here for assertions"
  								[fieldOop := self fetchPointer: fi ofObject: obj].
  						 (self isNonImmediate: fieldOop) ifTrue:
  							[(heapMap heapMapAtWord: (self pointerForOop: fieldOop)) ~= 0 ifTrue:
+ 								[coInterpreter print: 'object leak in '; printHex: obj; print: ' @ '; printNum: fi; print: ' = '; printHex: fieldOop; print: ' is free'; eekcr.
- 								[coInterpreter print: 'object leak in '; printHex: obj; print: ' @ '; printNum: fi; print: ' = '; printHex: fieldOop; print: ' is free'; cr.
- 								 self eek.
  								 ok := false]]]]]].
  	total ~= totalFreeOldSpace ifTrue:
+ 		[coInterpreter print: 'incorrect totalFreeOldSpace; expected '; printNum: totalFreeOldSpace; print: ' found '; printNum: total; eekcr.
- 		[coInterpreter print: 'incorrect totalFreeOldSpace; expected '; printNum: totalFreeOldSpace; print: ' found '; printNum: total; cr.
- 		 self eek.
  		 ok := false].
  	^ok!

Item was changed:
  ----- Method: SpurMemoryManager>>checkHeapIntegrity:classIndicesShouldBeValid: (in category 'debug support') -----
(excessive size, no diff calculated)

Item was changed:
  ----- Method: SpurMemoryManager>>checkOopIntegrity:named: (in category 'debug support') -----
  checkOopIntegrity: obj named: name
  	<inline: false>
  	<var: #name type: #'char *'>
  	((self oop: obj isLessThan: endOfMemory)
  	 and: [(heapMap heapMapAtWord: (self pointerForOop: obj)) ~= 0]) ifTrue:
  		[^true].
+ 	coInterpreter print: name; print: ' leak '; printHex: obj; eekcr.
- 	coInterpreter print: name; print: ' leak '; printHex: obj; cr.
  	^false!

Item was changed:
  ----- Method: SpurMemoryManager>>checkOopIntegrity:named:index: (in category 'debug support') -----
  checkOopIntegrity: obj named: name index: i
  	<inline: false>
  	<var: #name type: #'char *'>
  	((self oop: obj isLessThan: endOfMemory)
  	 and: [(heapMap heapMapAtWord: (self pointerForOop: obj)) ~= 0]) ifTrue:
  		[^true].
+ 	coInterpreter print: name; print: ' leak @ '; printNum: i; print: ' = '; printHex: obj; eekcr.
- 	coInterpreter print: name; print: ' leak @ '; printNum: i; print: ' = '; printHex: obj; cr.
  	^false!

Item was removed:
- ----- Method: SpurMemoryManager>>eek (in category 'debug support') -----
- eek
- 	<inline: #never>
- 	leakDetected := true!

Item was changed:
  ----- Method: SpurMemoryManager>>initialize (in category 'initialization') -----
  initialize
  	"We can put all initializations that set something to 0 or to false here.
  	 In C all global variables are initialized to 0, and 0 is false."
  	| moreThanEnough |
  	remapBuffer := Array new: RemapBufferSize.
  	remapBufferCount := extraRootCount := 0. "see below"
  	freeListsMask := totalFreeOldSpace := lowSpaceThreshold := 0.
  	checkForLeaks := 0.
+ 	needGCFlag := signalLowSpace := marking := false.
- 	needGCFlag := signalLowSpace := marking := leakDetected := false.
  	becomeEffectsFlags := gcPhaseInProgress := validatedIntegerClassFlags := 0.
  	statScavenges := statIncrGCs := statFullGCs := 0.
  	statMaxAllocSegmentTime := 0.
  	statMarkUsecs := statSweepUsecs := statScavengeGCUsecs := statIncrGCUsecs := statFullGCUsecs := statCompactionUsecs := statGCEndUsecs := gcSweepEndUsecs := 0.
  	statSGCDeltaUsecs := statIGCDeltaUsecs := statFGCDeltaUsecs := 0.
  	statGrowMemory := statShrinkMemory := statRootTableCount := statAllocatedBytes := 0.
  	statRootTableOverflows := statMarkCount := statCompactPassCount := statCoalesces := 0.
  
  	"We can initialize things that are allocated but are lazily initialized."
  	unscannedEphemerons := SpurContiguousObjStack new.
  
  	"we can initialize things that are virtual in C."
  	scavenger := SpurGenerationScavenger simulatorClass new manager: self; yourself.
  	segmentManager := SpurSegmentManager simulatorClass new manager: self; yourself.
  	compactor := self class compactorClass simulatorClass new manager: self; yourself.
  
  	"We can also initialize here anything that is only for simulation."
  	heapMap := CogCheck32BitHeapMap new.
  
  	"N.B. We *don't* initialize extraRoots because we don't simulate it."
  
  	"This is needed on 64-bits. We don't want a simulation creating a huge heap by default.
  	 By default use 512Mb on 64-bits, 256Mb on 32-bits."
  	moreThanEnough := 1024 * 1024 * 1024 / (16 / self wordSize). "One million dollars, ha ha ha ha ha,... ha, ha ha ha ha, ..."
  	maxOldSpaceSize := self class initializationOptions
  							ifNotNil: [:initOpts| initOpts at: #maxOldSpaceSize ifAbsent: [moreThanEnough]]
  							ifNil: [moreThanEnough]!

Item was added:
+ ----- Method: StackInterpreter>>eekcr (in category 'debug printing') -----
+ eekcr
+ 	"For marking the end of a leak check print message"
+ 	<api>
+ 	<inline: #never>
+ 	self printf: '\n'.
+ 	self cCode: '' inSmalltalk: [self halt]!

Item was changed:
  ----- Method: TMethod>>addFunctionAttribute: (in category 'accessing') -----
  addFunctionAttribute: aString
+ 	functionAttributes
+ 		ifNil: [functionAttributes := aString]
+ 		ifNotNil:
+ 			[(functionAttributes includesSubstring: aString) ifFalse:
+ 				[functionAttributes := functionAttributes, ' ', aString]]!
- 	functionAttributes := functionAttributes
- 							ifNil: [aString]
- 							ifNotNil: [functionAttributes, ' ', aString]!



More information about the Vm-dev mailing list