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

commits at source.squeak.org commits at source.squeak.org
Wed Feb 1 01:43:20 UTC 2023


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

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

Name: VMMaker.oscog.seperateMarking-eem.3314
Author: eem
Time: 31 January 2023, 5:43:06.479622 pm
UUID: 19d4b92f-6399-4ce0-bf90-edd88349b29b
Ancestors: VMMaker.oscog.seperateMarking-eem.3313

Implement an optional TempVectReadBarrier for the IGC. If spurPostBecomeAction: uses followReceiverAndTemporaryForwardingPointersInStackZone then the read barrier is not needed. Slang must resolve "objectMemory gc" within StackInterpreter for this to work.

Slang: add a class variable to control the diagnostic output of the polymorphic message resolver. It produces a *lot* of output.

=============== Diff against VMMaker.oscog.seperateMarking-eem.3313 ===============

Item was changed:
  Object subclass: #CCodeGenerator
  	instanceVariableNames: 'vmClass structClasses translationDict asArgumentTranslationDict inlineList constants variables variableDeclarations scopeStack methods macros apiMethods apiVariables kernelReturnTypes currentMethod headerFiles globalVariableUsage useSymbolicConstants generateDeadCode requiredSelectors previousCommentMarksInlining previousCommenter logger suppressAsmLabels asmLabelCounts pools selectorTranslations staticallyResolvedPolymorphicReceivers recursivelyResolvedPolymorphicReceivers optionsDictionary breakSrcInlineSelectors breakDestInlineSelectors breakOnInline vmMaker accessorDepthCache beganInlining mappingForRecursivePolymophism removedForPolymorphism recursivePolymorphicMethodsMap toGenerate classesToBeGenerated'
+ 	classVariableNames: 'NoRegParmsInAssertVMs VerbosePolymorphismResolution'
- 	classVariableNames: 'NoRegParmsInAssertVMs'
  	poolDictionaries: 'VMBasicConstants'
  	category: 'VMMaker-Translation to C'!
  
  !CCodeGenerator commentStamp: 'tpr 5/2/2003 14:30' prior: 0!
  This class oversees the translation of a subset of Smalltalk to C, allowing the comforts of Smalltalk during development and the efficiency and portability of C for the resulting interpreter.  
  See VMMaker for more useful info!

Item was changed:
  ----- Method: CCodeGenerator class>>initialize (in category 'class initialization') -----
  initialize
  	"CCodeGenerator initialize"
  
+ 	NoRegParmsInAssertVMs := true.
+ 		"If NoRegParmsInAssertVMs is true the generator spits out an attribute turning off register parameters for static functions in the Assert and Debug VMs which makes debugging easier, since all functions can be safely called from gdb.  One might hope that -mregparm=0 would work but at least on Mac OS X's gcc 4.2.1 it does not and hence we have to use a per function attribute.  Sigh..."
+ 	"Set this to true to get information on polymorphic message resolution printed to the transcript."
+ 	VerbosePolymorphismResolution := false!
- 	NoRegParmsInAssertVMs := true
- 		"If NoRegParmsInAssertVMs is true the generator spits out an attribute turning off register parameters for static functions in the Assert and Debug VMs which makes debugging easier, since all functions can be safely called from gdb.  One might hope that -mregparm=0 would work but at least on Mac OS X's gcc 4.2.1 it does not and hence we have to use a per function attribute.  Sigh..."!

Item was changed:
  ----- Method: CCodeGenerator>>resolveRecursivePolymorphism:in:fromMethod:in:ifMatch: (in category 'helpers polymorphic resolving') -----
  resolveRecursivePolymorphism: receiverSymbol in: aSendNode fromMethod: aTMethod in: aClass ifMatch: aReturnBlock
  
  	"- if the current TMethod is a base method we want to resolve it to the default
  	- if the current TMethod is a polymorphic method, meaning it got a type to resolve for, apply this type to submethods
  	- if the called method (from SendNode) is a polymorphic base method we resolve it to the default if we are not in a class associated with only one type. Should this be the case we resolve the method to this type"
  
  	"((aTMethod selector = #globalGarbageCollect) and: [aSendNode selector = #preGlobalGCActions]) ifTrue: [0 halt]."
  	
  	aTMethod isPolymorphicBase
  		ifTrue: [self resolve: receiverSymbol inSelfSend: aSendNode in: aClass to: aTMethod default ifFound: aReturnBlock.
  							
  				"if the polymorphic receiver is mentioned we resolve the method to the default"
  				self resolve: aSendNode to: aTMethod default ifFound: aReturnBlock.
  				
  				
  				"now get desperate. look if there is a method with the selectors name that is mentioned in a polymorphic context"
  				removedForPolymorphism at: aSendNode selector 
  					ifPresent: [:dictionary | dictionary at: aTMethod default 
  												ifPresent: [:selector |
  													aSendNode
  														setSelectorForPolymorphism: selector.
  													aReturnBlock value].
  												
  												"is the TMethods receiverClass associated with one of the polymorphic classes implementing  aSendNode selector?"
  											(mappingForRecursivePolymophism associationsSelect: [:assoc | assoc value = aTMethod default]) keys
  												detect: [:key | dictionary keys anySatisfy: [:ea | key includesBehavior: ea]]
  													ifFound: [:class | | actualClass |
  														actualClass := dictionary keys detect: [:ea | class includesBehavior: ea].
  														aSendNode
  															setSelectorForPolymorphism: (dictionary at: actualClass).
  														aReturnBlock value]].
  							
  				(self hasPolymorphicMethod: aSendNode selector in: aTMethod default)
  					ifTrue: [self halt]].
  						
  	aTMethod isPolymorphic
  		ifTrue: [self resolvePolymorphicMethod: receiverSymbol in: aSendNode fromMethod: aTMethod in: aClass ifMatch: aReturnBlock].
  	
  	methods at: aSendNode selector
  		ifPresent: [:calledMethod | 
  			calledMethod isPolymorphicBase
  				ifTrue: [ | alternativeClass matchingClass |
  					"we have type info and the calledMethod does not care which type it is -> use type info"
  					aTMethod isPolymorphic
  						ifTrue: [
  							aSendNode
  								setSelectorForPolymorphism: (calledMethod polymorphicSelectorForClass: aTMethod receiverClass).
  							aReturnBlock value ].
  						
  					"should we or one of our superclasses define the called method use the default because we call it ourself and there is no other info"
  					self resolve: receiverSymbol inSelfSend: aSendNode in: aClass to: calledMethod default ifFound: aReturnBlock.
  
  					"should the class be mapped to a fixed type use it to resolve the type of the method"
  					alternativeClass := mappingForRecursivePolymophism at: aClass ifAbsent: [nil].
  					(calledMethod classes includes: aClass)
  						ifTrue: [matchingClass := aClass]
  						ifFalse: [(calledMethod classes includes: alternativeClass)
  									ifTrue: [matchingClass := alternativeClass]].
  						matchingClass ifNotNil: [
  							aSendNode
  								setSelectorForPolymorphism: (calledMethod polymorphicSelectorForClass: matchingClass).
  							aReturnBlock value].
  						
  					"we have no info about the method, but we know it is a polymorphic base -> resolve to default because we assume everyone wants the default"
+ 					VerbosePolymorphismResolution ifTrue:
+ 						[Transcript show: 'Resolved ' , aSendNode asString.
+ 						 aSendNode setSelectorForPolymorphism: (calledMethod polymorphicSelectorForClass: calledMethod default).
+ 						 Transcript 
+ 							show: ' to ' , aSendNode asString , ' in ' , aTMethod asString , ' because it is the default for the defined polymorphic method.';
+ 							cr].
- 					Transcript show: 'Resolved ' , aSendNode asString.
- 					aSendNode setSelectorForPolymorphism: (calledMethod polymorphicSelectorForClass: calledMethod default).
- 					Transcript 
- 						show: ' to ' , aSendNode asString , ' in ' , aTMethod asString , ' because it is the default for the defined polymorphic method.';
- 						cr.
  					aReturnBlock value
  						]]
+ 		ifAbsent: []	.!
- 		ifAbsent: []	.
- 	
- 	!

Item was changed:
  ----- Method: CCodeGenerator>>writeCallGraphCSV: (in category 'call graph') -----
  writeCallGraphCSV: connections
  
+ 	FileStream
+ 		fileNamed: 'output.csv'
+ 		do: [:file|
+ 			file 
+ 				nextPutAll: 'caller';
+ 				tab;
+ 				nextPutAll: 'callee';
+ 				cr; lf.
+ 
+ 			connections keysAndValuesDo: [:callee :callers |
+ 				"self halt."
+ 				callers do: [:caller | 
+ 					file
+ 						nextPutAll: caller asString;
+ 						tab;
+ 						nextPutAll: callee asString;
+ 						cr; lf]]].
+ 
- 	| file |
- 	file := FileStream fileNamed: 'output.csv'.
- 	
- 	file 
- 		nextPutAll: 'source';
- 		nextPut: Character tab;
- 		nextPutAll: 'target';
- 		cr; lf.
- 		
- 	connections keysAndValuesDo: [:key :value |
- 		"self halt."
- 		value do: [:ea | 
- 			file
- 				nextPutAll: ea asString;
- 				nextPut: Character tab;
- 				nextPutAll: key asString;
- 				cr; lf]].
- 		
- 		
  	^ connections!

Item was changed:
  ----- Method: SpurMemoryManager class>>declareCVarsIn: (in category 'translation') -----
  declareCVarsIn: aCCodeGenerator
  
  	self wantsIncrementalGC
  		ifTrue: [aCCodeGenerator
  					recursivelyResolvePolymorpicReceiver: 'gc' toVariants: {SpurIncrementalGarbageCollector. SpurStopTheWorldGarbageCollector} in: self default: SpurIncrementalGarbageCollector;
  					staticallyResolvedPolymorphicReceiver: 'gc' to: self markerClass in: SpurIncrementalGarbageCollector; 
  					staticallyResolvedPolymorphicReceiver: 'compactor' to: self compactorClass in: self; 
  					staticallyResolvedPolymorphicReceiver: 'marker' to: self markerClass in: self].
  
  	self class == thisContext methodClass ifFalse: [^self]. "Don't duplicate decls in subclasses"
  	aCCodeGenerator removeVariable: 'memory'. "memory is a simulation time thing only"
  	self declareCAsOop: #(	freeStart scavengeThreshold newSpaceStart pastSpaceStart
  							oldSpaceStart lowSpaceThreshold freeOldSpaceStart endOfMemory)
  		in: aCCodeGenerator.
  	self declareCAsUSqLong: (self allInstVarNames select: [:ivn| ivn endsWith: 'Usecs']), #(statAllocatedBytes)
  		in: aCCodeGenerator.
  	aCCodeGenerator
  		var: #lastHash type: #usqInt;
  		var: #freeListsMask type: #usqInt;
  		var: #freeLists type: #'sqInt *';
  		var: #objStackInvalidBecause type: #'char *';
  		var: #unscannedEphemerons type: #SpurContiguousObjStack;
  		var: #heapGrowthToSizeGCRatio type: #float;
  		var: #heapSizeAtPreviousGC type: #usqInt;
  		var: #totalFreeOldSpace type: #usqInt;
  		var: #maxOldSpaceSize type: #usqInt.
  	aCCodeGenerator
  		var: #oldSpaceUsePriorToScavenge type: #sqLong.
  	aCCodeGenerator
  		var: #remapBuffer
  		declareC: 'sqInt remapBuffer[RemapBufferSize + 1 /* ', (RemapBufferSize + 1) printString, ' */]'.
  	aCCodeGenerator
  		var: #extraRoots
  		declareC: 'sqInt *extraRoots[ExtraRootsSize + 1 /* ', (ExtraRootsSize + 1) printString, ' */]'.
+ 
+ 	aCCodeGenerator
+ 		staticallyResolvedPolymorphicReceiver: 'objectMemory gc'
+ 		to: (Smalltalk classNamed: (InitializationOptions at: 'gcClass'))
+ 		in: StackInterpreter.
- 		
  	self wantsIncrementalGC
  		ifTrue: [aCCodeGenerator
  					staticallyResolvedPolymorphicReceiver: 'manager gc' to: SpurIncrementalGarbageCollector in: SpurSegmentManager;
  					"the vm needs (from handwritten C code) the method fullGC. Generate it later on"
  					generate: #fullGC from: #SIGC_fullGC]!

Item was changed:
  ----- Method: StackInterpreter>>spurPostBecomeAction: (in category 'object memory support') -----
  spurPostBecomeAction: theBecomeEffectsFlags
  	"Insulate the stack zone from the effects of a become.
  	 All receivers must be unfollowed for two reasons:
  		1. inst var access is direct with no read barrier
  		2. super sends (always to the receiver) have no class check and so don't trap
  		   for forwarded receivers.  This is an issue for primitives that assume their receiver
  		   is valid and don't validate.
  	 Super sends require an explicit check to ensure receivers in super sends are unforwarded.
  	 e.g. super doSomethingWith: (self become: other) forwards the receiver self pushed on the
  	 stack.  So we could avoid following non-pointer receivers.  But this is too tricky,  Instead, we
  	 always follow receivers.
  	 Methods must be unfollowed since bytecode access is direct with no read barrier.
  	 But this only needs to be done if the becomeEffectsFlags indicate that a
  	 CompiledMethod was becommed.
  	 The scheduler state must be followed, but only if the becomeEffectsFlags indicate
  	 that a pointer object was becommed."
  	<option: #SpurObjectMemory>
  	<inline: false> "For VM profiling"
  	self flushAtCache.
  	theBecomeEffectsFlags ~= 0 ifTrue:
  		[(theBecomeEffectsFlags anyMask: BecameActiveClassFlag) ifTrue:
  			[self flushBecommedClassesInMethodCache].
  		 (theBecomeEffectsFlags anyMask: BecamePointerObjectFlag) ifTrue:
  			[self followForwardingPointersInScheduler.
  			 self followForwardingPointersInSpecialObjectsArray].
  		 (theBecomeEffectsFlags anyMask: BecamePointerObjectFlag + BecameCompiledMethodFlag) ifTrue:
  			[self followForwardingPointersInProfileState.
  			 (theBecomeEffectsFlags anyMask: BecameCompiledMethodFlag) ifTrue:
  				[self followForwardedMethodsInMethodCache.
  				 self followMethodNewMethodAndInstructionPointer]]].
+ 	"There are two scans of the stack zone post become, and three cases to consider.
+ 	 There is no way of naming an indirection vector in a context/stack frame, so if the GC is not
+ 	 incremental (if incremental compaction is not done), indirection vectors should never be forwarded.
+ 	 Yes, one could forward explicitly via thisContext, but we copnsider that shooting onesself in the foot.
+ 	 If the GC is incremental then indirection vectors can be forwarded.  To cope with this we can either
+ 	 have an explicit read barrier (TempVectReadBarrier) or we can follow temporary variables as well
+ 	 as the receiver. Performance measurements indicate that following tempoiraries as well as the
+ 	 method and receiver won't increase the time spent in become very much. So we implement both
+ 	 and will decide what's better when we can do real performance tests."
+ 	objectMemory gc isIncremental
+ 		ifTrue:
+ 			[TempVectReadBarrier
+ 				ifTrue: [self followForwardingPointersInStackZone]
+ 				ifFalse: [self followReceiverAndTemporaryForwardingPointersInStackZone]]
+ 		ifFalse:
+ 			[self followForwardingPointersInStackZone]!
- 	self followForwardingPointersInStackZone!

Item was changed:
  ----- Method: VMClass class>>initializeMiscConstants (in category 'initialization') -----
  initializeMiscConstants
  	"Falsify the `what type of VM is this?' flags that are defined in the various interp.h files.
  	 Subclass implementations need to include a super initializeMiscConstants"
  
  	| omc |
  	VMBIGENDIAN class. "Mention this for the benefit of CCodeGenerator>>emitCConstantsOn:"
  	SPURVM := STACKVM := COGVM := COGMTVM := false.
  
  	InitializationOptions ifNil: [InitializationOptions := Dictionary new].
  	omc := InitializationOptions at: #ObjectMemory ifAbsent: nil.
  	(omc isNil and: [self defaultObjectMemoryClass notNil]) ifTrue:
  		[omc := InitializationOptions at: #ObjectMemory put: self defaultObjectMemoryClass name].
  	omc := omc ifNotNil: [Smalltalk at: omc].
  	InitializationOptions
  		at: #SqueakV3ObjectMemory	"the good ole default"
  			ifAbsentPut: (omc
  					ifNil: [true]
  					ifNotNil: [omc includesBehavior: ObjectMemory]);
  		at: #SpurObjectMemory		"the new contender"
  			ifAbsentPut: (omc
  					ifNil: [false]
  					ifNotNil: [omc includesBehavior: SpurMemoryManager]).
  	omc validateInitializationOptions. "hack around edge cases"
  
  	"Use ifAbsentPut: so that they will get copied back to the
  	 VMMaker's options and dead code will likely be eliminated."
  	PharoVM := InitializationOptions at: #PharoVM ifAbsentPut: [false].
  	NewspeakVM := InitializationOptions at: #NewspeakVM ifAbsentPut: [false].
  	SistaVM := InitializationOptions at: #SistaVM ifAbsentPut: [false].
  	TempVectReadBarrier := InitializationOptions at: #TempVectReadBarrier ifAbsentPut: [false].
  	LowcodeVM := InitializationOptions at: #LowcodeVM ifAbsentPut: [false].
  	MULTIPLEBYTECODESETS := InitializationOptions at: #MULTIPLEBYTECODESETS ifAbsentPut: [false].
  	"Simulation only; on by default..."
  	CloneOnGC := InitializationOptions at: #CloneOnGC ifAbsentPut: [true].
  	CloneOnScavenge := InitializationOptions at: #CloneOnScavenge ifAbsentPut: [true].
  
  	"These must be set only if specified, not defaulted, because they are set on the command line or in include files."
  	InitializationOptions
  		at: #VMBIGENDIAN	ifPresent: [:value| VMBIGENDIAN := value];
  		at: #ObjectMemory	ifPresent: [:value| SPURVM := value beginsWith: 'Spur'];
  		at: #STACKVM		ifPresent: [:value| STACKVM := value];
  		at: #COGVM		ifPresent: [:value| COGVM := InitializationOptions at: #COGVM];
  		at: #COGMTVM		ifPresent: [:value| COGMTVM := InitializationOptions at: #COGMTVM].
  
  	"consistency checks"
+ 	SPURVM ifFalse:
+ 		[TempVectReadBarrier ifTrue: [self error: 'read barrier works with spur VM only...'].
+ 		 SistaVM ifTrue: [self error: 'Sista VM works with spur VM only...']].
- 	SPURVM
- 		ifTrue:
- 			[(TempVectReadBarrier not
- 			  and: [{SpurMemoryManager compactorClass}, (SpurMemoryManager compactorClass ancilliaryClasses) anySatisfy:
- 						[:c| c == SpurSelectiveCompactor or: [c == SpurIncrementalSweepAndCompact]]]) ifTrue:
- 				[self error: 'Selective compactor requires read barrier']]
- 		ifFalse:
- 			[TempVectReadBarrier ifTrue: [self error: 'read barrier works with spur VM only...'].
- 			 SistaVM ifTrue: [self error: 'Sista VM works with spur VM only...']].
  
  	"And not these; they're compile-time"
  	IMMUTABILITY := InitializationOptions at: #IMMUTABILITY ifAbsent: [SPURVM] "Default as enabled for Spur VMs"!



More information about the Vm-dev mailing list