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

commits at source.squeak.org commits at source.squeak.org
Thu May 1 15:35:41 UTC 2014


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

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

Name: VMMaker.oscog-eem.693
Author: eem
Time: 1 May 2014, 8:33:21.528 am
UUID: b7928132-78c6-4cdb-b4f3-e47dd7336fa7
Ancestors: VMMaker.oscog-eem.692

Eliminate the abuse of prepareToBeAddedToCodeGenerator:
to remove superclass methods.  Make method conflict
checking use shouldIncludeMethodFor:selector: asnd allow
option: pragma methods to override methods in other
hierarchies, albeit with a warning.

Either delete or simplify a whole lot of ugly
prepareToBeAddedToCodeGenerator: hacks.

Use the option: approach to organize the numRegArgs
implementations, which allows inlining and the necessary
dead code elimination in CoInterpreter to avoid implementing
the register enilopmarts in SimpleStackBasedCogit.

Fix slip bug in ObjectMemory>>isContextHeader:

externalSetStackPageAndPointersForSuspendedContextOfProcess:
must be marked <inline> to be reliably inlined in transferTo:/transfer:to: et al.

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

Item was changed:
  ----- Method: CCodeGenerator>>addMethod: (in category 'utilities') -----
  addMethod: aTMethod
  	"Add the given method to the code base and answer it.
  	 Only allow duplicate definitions for struct accessors, since we don't actually
+ 	 generate code for these methods and hence the conflict doesn't matter.
+ 	 Allow subclasses to redefine methods (Smalltalk has inheritance after all)."
- 	 generate code for these methods and hence the conflict doesn't matter."
  
  	(methods at: aTMethod selector ifAbsent: []) ifNotNil:
  		[:conflict |
  		aTMethod compiledMethod isSubclassResponsibility ifTrue:
  			[^nil].
  		(conflict isStructAccessor
  		 and: [aTMethod isStructAccessor
  		 and: [conflict compiledMethod decompileString = aTMethod compiledMethod decompileString]]) ifTrue:
  			[^nil].
+ 		((aTMethod definingClass inheritsFrom: conflict definingClass)
+ 		 or: [(aTMethod compiledMethod pragmaAt: #option:) notNil]) ifFalse:
+ 			[self error: 'Method name conflict: ', aTMethod selector]].
- 		(conflict definingClass inheritsFrom: aTMethod definingClass) ifTrue:
- 			[^nil].
- 		self error: 'Method name conflict: ', aTMethod selector].
  	^methods at: aTMethod selector put: aTMethod!

Item was changed:
  ----- Method: CCodeGenerator>>checkClassForNameConflicts: (in category 'error notification') -----
  checkClassForNameConflicts: aClass
  	"Verify that the given class does not have constant, variable, or method names that conflict with
  	 those of previously added classes. Raise an error if a conflict is found, otherwise just return."
  
  	"check for constant name collisions in class pools"
  	aClass classPool associationsDo:
  		[:assoc |
  		(constants includesKey: assoc key asString) ifTrue:
  			[self error: 'Constant ', assoc key, ' was defined in a previously added class']].
  
  	"and in shared pools"
  	(aClass sharedPools reject: [:pool| pools includes: pool]) do:
  		[:pool |
  		pool bindingsDo:
  			[:assoc |
  			(constants includesKey: assoc key asString) ifTrue:
  				[self error: 'Constant ', assoc key, ' was defined in a previously added class']]].
  
  	"check for instance variable name collisions"
  	(aClass inheritsFrom: VMStructType) ifFalse:
  		[(self instVarNamesForClass: aClass) do:
  			[:varName |
  			(variables includes: varName) ifTrue:
  				[self error: 'Instance variable ', varName, ' was defined in a previously added class']]].
  
  	"check for method name collisions"
  	aClass selectors do:
  		[:sel | | tmeth meth |
+ 		((self shouldIncludeMethodFor: aClass selector: sel)
+ 		and: [(tmeth := methods at: sel ifAbsent: nil) notNil
- 		((tmeth := methods at: sel ifAbsent: nil) notNil
  		and: [(aClass isStructClass and: [(aClass isAccessor: sel)
  				and: [(methods at: sel) isStructAccessor]]) not
+ 		and: [(meth := aClass >> sel) isSubclassResponsibility not
+ 		and: [(aClass includesBehavior: tmeth definingClass) not]]]]) ifTrue:
+ 			[((aClass >>sel) pragmaAt: #option:)
+ 				ifNil: [self error: 'Method ', sel, ' was defined in a previously added class.']
+ 				ifNotNil:
+ 					[logger
+ 						ensureCr;
+ 						show: 'warning, method ', aClass name, '>>', sel storeString,
+ 								' overrides ', tmeth definingClass, '>>', sel storeString;
+ 						cr]]]!
- 		and: [((meth := aClass compiledMethodAt: sel) pragmaAt: #doNotGenerate) isNil
- 		and: [meth isSubclassResponsibility not
- 		and: [(tmeth definingClass inheritsFrom: aClass) not]]]]) ifTrue:
- 			[self error: 'Method ', sel, ' was defined in a previously added class.']]!

Item was changed:
  ----- Method: CCodeGenerator>>shouldIncludeMethodFor:selector: (in category 'utilities') -----
  shouldIncludeMethodFor: aClass selector: selector
+ 	"Answer whether a method shoud be translated.  Process optional methods by
+ 	 interpreting the argument to the option: pragma as either a Cogit class name
+ 	 or a class variable name or a variable name in VMBasicConstants.  Exclude
+ 	 methods with the doNotGenerate pragma."
- 	"process optional methods by interpreting the argument to the option: pragma as either
- 	 a Cogit class name or a class variable name or a variable name in VMBasicConstants."
  	(aClass >> selector pragmaAt: #option:) ifNotNil:
  		[:pragma| | key |
  		key := pragma argumentAt: 1.
  		vmMaker ifNotNil:
  			[vmMaker cogitClassName ifNotNil:
  				[(Cogit withAllSubclasses anySatisfy: [:c| c name = key]) ifTrue:
  					[| cogitClass optionClass |
  					 cogitClass := Smalltalk classNamed: vmMaker cogitClassName.
  					 optionClass := Smalltalk classNamed: key.
  					 ^cogitClass includesBehavior: optionClass]].
  			((vmClass
  				ifNotNil: [vmClass initializationOptions]
  				ifNil: [vmMaker options]) at: key ifAbsent: [false]) ifNotNil:
  				[:option| option ~~ false ifTrue: [^true]].
  		(aClass bindingOf: key) ifNotNil:
  			[:binding|
  			binding value ~~ false ifTrue: [^true]].
  		(VMBasicConstants bindingOf: key) ifNotNil:
  			[:binding|
  			binding value ~~ false ifTrue: [^true]]].
  		^false].
+ 	^(aClass >> selector pragmaAt: #doNotGenerate) isNil!
- 	^true!

Item was changed:
  ----- Method: CoInterpreter class>>prepareToBeAddedToCodeGenerator: (in category 'translation') -----
  prepareToBeAddedToCodeGenerator: aCodeGen
- 	"Override to avoid repeating StackInterpreter's preparations and to delete
- 	 StackInterpreter & StackInterpreterPrimitives methods we override."
- 	aCodeGen removeVariable: 'cogit'.
- 	self selectors do:
- 		[:sel|
- 		 (superclass whichClassIncludesSelector: sel) ifNotNil:
- 			[aCodeGen removeMethodForSelector: sel]].
  	"It is either this or scan cmacro methods for selectors."
  	aCodeGen retainMethods: #(enterSmalltalkExecutiveImplementation)!

Item was removed:
- ----- Method: CoInterpreterStackPages class>>prepareToBeAddedToCodeGenerator: (in category 'translation') -----
- prepareToBeAddedToCodeGenerator: aCodeGen
- 	aCodeGen
- 		removeVariable: 'coInterpreter';
- 		removeVariable: 'objectMemory'!

Item was removed:
- ----- Method: CogIA32Compiler class>>prepareToBeAddedToCodeGenerator: (in category 'translation') -----
- prepareToBeAddedToCodeGenerator: aCodeGen
- 	"Remove the methods of CogAbstractInstruction we override."
- 	self selectors do:
- 		[:sel|
- 		 (superclass includesSelector: sel) ifTrue:
- 			[aCodeGen removeMethodForSelector: sel]].!

Item was removed:
- ----- Method: CogObjectRepresentation class>>prepareToBeAddedToCodeGenerator: (in category 'translation') -----
- prepareToBeAddedToCodeGenerator: aCodeGen
- 	"This is a horrible hack to keep an optimization lost by necessary
- 	 refactoring of StackToRegisterMappingCogit>>#numRegArgs
- 	 when the Spur object representation was added.  Avert your gaze?
- 	 Refactoring was needed because SimpleStackBasedCogit defines numregArgs as ^0,
- 	 so if the object representations also defined numregArgs there would be a clash.
- 
- 	 To make numRegArgs a method that answers a constant and hence a
- 	 method that Slang will inline at compile time and do code elimination on,
- 	 we slam in the preferredNumRegArgs method that does answer a constant.
- 
- 	 Another option I played with was defining a <soft> pragma that would be used in
- 	 the object representation's numRegArgs, which would cause the code generator
- 	 to discard it when used with the SimpleStackBasedCogit, and allow the numRegArgs
- 	 in StackToRegisterMappingCogit to have the <doNotGenerate> pragma.  Which hack
- 	 to prefer is up for debate."
- 	((self includesSelector: #preferredNumRegArgs)
- 	 and: [(self >> #preferredNumRegArgs) messages asArray ~= #(subclassResponsibility)]) ifTrue:
- 		[(aCodeGen methodNamed: #numRegArgs) ifNotNil:
- 			[:aTMethod| | doppelganger |
- 			 aTMethod compiledMethod messages asArray = #(preferredNumRegArgs) ifTrue:
- 				[doppelganger := aCodeGen compileToTMethodSelector: #preferredNumRegArgs in: self.
- 				 doppelganger selector: #numRegArgs.
- 				 doppelganger mergePropertiesOfSuperMethod: aTMethod.
- 				 aCodeGen
- 					removeMethodForSelector: #numRegArgs;
- 					addMethod: doppelganger]]]!

Item was added:
+ ----- Method: CogObjectRepresentation>>numRegArgs (in category 'calling convention') -----
+ numRegArgs
+ 	"Define how many register arguments a StackToRegisterMappingCogit can and should use
+ 	 with the receiver.  The value must be 0, 1 or 2.  Note that a SimpleStackBasedCogit always
+ 	 has 0 register args (although the receiver is passed in a register).  The method must
+ 	 be inlined in CoInterpreter, and dead code eliminated so that the register-popping
+ 	 enilopmarts such as enterRegisterArgCogMethod:at:receiver: do not have to be
+ 	 implemented in SimpleStackBasedCogit."
+ 	<api>
+ 	<option: #StackToRegisterMappingCogit>
+ 	<inline: true>
+ 	self subclassResponsibility!

Item was removed:
- ----- Method: CogObjectRepresentation>>preferredNumRegArgs (in category 'calling convention') -----
- preferredNumRegArgs
- 	"Define how many register arguments a StackToRegisterMappingCogit can and should use
- 	 with the receiver.  The value must be 0, 1 or 2.  Note that a SimpleStackBasedCogit always
- 	 has 0 register args (although the receiver is passed in a register)."
- 	self subclassResponsibility!

Item was added:
+ ----- Method: CogObjectRepresentationForSpur>>numRegArgs (in category 'calling convention') -----
+ numRegArgs
+ 	"Define how many register arguments a StackToRegisterMappingCogit can
+ 	 and should use with the receiver.  The value must be 0, 1 or 2.  Note that a
+ 	 SimpleStackBasedCogit always has 0 register args (although the receiver is
+ 	 passed in a register).  The Spur object representation is simple enough that
+ 	 implementing at:put: is straight-forward and hence 2 register args are worth
+ 	 while.  The method must be inlined in CoInterpreter, and dead code eliminated
+ 	 so that the register-popping enilopmarts such as enterRegisterArgCogMethod:-
+ 	 at:receiver: do not have to be implemented in SimpleStackBasedCogit."
+ 	<api>
+ 	<option: #StackToRegisterMappingCogit>
+ 	<inline: true>
+ 	^2!

Item was removed:
- ----- Method: CogObjectRepresentationForSpur>>preferredNumRegArgs (in category 'calling convention') -----
- preferredNumRegArgs
- 	"Define how many register arguments a StackToRegisterMappingCogit can
- 	 and should use with the receiver.  The value must be 0, 1 or 2.  Note that a
- 	 SimpleStackBasedCogit always has 0 register args (although the receiver is
- 	 passed in a register).  The Spur object representation is simple enough that
- 	 implementing at:put: is straight-forward and hence 2 register args are worth while."
- 	<inline: true>
- 	^2!

Item was added:
+ ----- Method: CogObjectRepresentationForSqueakV3>>numRegArgs (in category 'calling convention') -----
+ numRegArgs
+ 	"Define how many register arguments a StackToRegisterMappingCogit can
+ 	 and should use with the receiver.  The value must be 0, 1 or 2.  Note that a
+ 	 SimpleStackBasedCogit always has 0 register args (although the receiver is
+ 	 passed in a register).  CogObjectRepresentationForSqueakV3 only implements
+ 	 at most 1-arg primitives, because the complexity of the object representation
+ 	 makes it difficult to implement at:put:, the most performance-critical 2-argument
+ 	 primitive..  The method must be inlined in CoInterpreter, and dead code eliminated
+ 	 so that the register-popping enilopmarts such as enterRegisterArgCogMethod:-
+ 	 at:receiver: do not have to be implemented in SimpleStackBasedCogit."
+ 	<api>
+ 	<option: #StackToRegisterMappingCogit>
+ 	<inline: true>
+ 	^1!

Item was removed:
- ----- Method: CogObjectRepresentationForSqueakV3>>preferredNumRegArgs (in category 'calling convention') -----
- preferredNumRegArgs
- 	"Define how many register arguments a StackToRegisterMappingCogit can
- 	 and should use with the receiver.  The value must be 0, 1 or 2.  Note that a
- 	 SimpleStackBasedCogit always has 0 register args (although the receiver is
- 	 passed in a register).  CogObjectRepresentationForSqueakV3 only implements
- 	 at most 1-arg primitives, because the complexity of the object representation
- 	 makes it difficult to implement at:put:, the most performance-critical 2-argument
- 	 primitive."
- 	<inline: true>
- 	^1!

Item was removed:
- ----- Method: CogThreadManager class>>prepareToBeAddedToCodeGenerator: (in category 'translation') -----
- prepareToBeAddedToCodeGenerator: aCodeGen
- 	aCodeGen
- 		removeVariable: 'coInterpreter';
- 		removeVariable: 'cogit'!

Item was removed:
- ----- Method: IA32ABIPlugin class>>prepareToBeAddedToCodeGenerator: (in category 'translation') -----
- prepareToBeAddedToCodeGenerator: aCodeGen
- 	aCodeGen removeMethodForSelector: #setInterpreter:!

Item was changed:
  ----- Method: NewObjectMemory class>>prepareToBeAddedToCodeGenerator: (in category 'translation') -----
  prepareToBeAddedToCodeGenerator: aCodeGen
+ 	"Remove the instance variables we don't use."
- 	"Remove the superclass methods we override
- 	 and the instance variables we don't use."
- 	self selectors do:
- 		[:sel|
- 		 (superclass whichClassIncludesSelector: sel) ifNotNil:
- 			[aCodeGen removeMethodForSelector: sel]].
  	self ~~ NewObjectMemory ifTrue:
  		[^self].
+ 	aCodeGen
+ 		removeMethodForSelector: #markPhase; "we implement markPhase:"
+ 		removeMethodForSelector: #printWronglySizedContexts. "we implement printWronglySizedContexts:"
- 	aCodeGen removeMethodForSelector: #markPhase. "we implement markPhase:"
  	"This class uses freeStart in place of freeBlock.  It does
  	 not maintain an allocationCount nor stats there-of.
  	 Having an interpreter that uses a stack zone, it doesn't
  	 need an optimized context allocator."
  	aCodeGen
  		removeVariable: 'freeBlock';
  		removeVariable: 'allocationCount';
  		removeVariable: 'allocationsBetweenGCs';
  		removeVariable: 'statAllocationCount';
  		removeVariable: 'freeContexts';
  		removeVariable: 'freeLargeContexts';
  		removeVariable: 'statGCEndTime' "replaced by statGCEndUsecs"!

Item was removed:
- ----- Method: NewspeakInterpreter class>>prepareToBeAddedToCodeGenerator: (in category 'translation') -----
- prepareToBeAddedToCodeGenerator: aCodeGen
- 	"Override to avoid repeating ObjectMemory's preparations
- 	 and to delete ObjectMemory methods we override."
- 	self selectors do:
- 		[:sel|
- 		 (superclass whichClassIncludesSelector: sel) ifNotNil:
- 			[aCodeGen removeMethodForSelector: sel]]!

Item was removed:
- ----- Method: NewsqueakIA32ABIPlugin class>>prepareToBeAddedToCodeGenerator: (in category 'translation') -----
- prepareToBeAddedToCodeGenerator: aCodeGen
- 	aCodeGen removeMethodForSelector: #setInterpreter:!

Item was changed:
  ----- Method: ObjectMemory>>isContextHeader: (in category 'contexts') -----
  isContextHeader: aHeader
  	<inline: true>
  	"c.f. {BlockContext. MethodContext. PseudoContext} collect: [:class| class -> class indexIfCompact]"
+ 	^(self compactClassIndexOfHeader: aHeader) = 13			"BlockContext"
+ 		or: [(self compactClassIndexOfHeader: aHeader) = 14]		"MethodContext"!
- 	^(self compactClassIndexOf: aHeader) = 13			"BlockContext"
- 		or: [(self compactClassIndexOf: aHeader) = 14]		"MethodContext"!

Item was removed:
- ----- Method: SimpleStackBasedCogit class>>prepareToBeAddedToCodeGenerator: (in category 'translation') -----
- prepareToBeAddedToCodeGenerator: aCCodeGenerator
- 	"Override to avoid repeating Cogit's preparations and remove the methods we override."
- 	self selectors do:
- 		[:sel|
- 		 (Cogit includesSelector: sel) ifTrue:
- 			[aCCodeGenerator removeMethodForSelector: sel]]!

Item was removed:
- ----- Method: SpurMemoryManager class>>prepareToBeAddedToCodeGenerator: (in category 'translation') -----
- prepareToBeAddedToCodeGenerator: aCodeGen
- 	"Remove the superclass methods we override."
- 	self selectors do:
- 		[:sel|
- 		 (superclass whichClassIncludesSelector: sel) ifNotNil:
- 			[aCodeGen removeMethodForSelector: sel]]!

Item was removed:
- ----- Method: StackInterpreter class>>prepareToBeAddedToCodeGenerator: (in category 'translation') -----
- prepareToBeAddedToCodeGenerator: aCodeGen
- 	"Override to delete InterpreterPrimitives methods we override."
- 	aCodeGen removeVariable: 'cogit'.
- 	self selectors do:
- 		[:sel|
- 		 (superclass whichClassIncludesSelector: sel) ifNotNil:
- 			[aCodeGen removeMethodForSelector: sel]]!

Item was changed:
  ----- Method: StackInterpreter>>externalSetStackPageAndPointersForSuspendedContextOfProcess: (in category 'frame access') -----
  externalSetStackPageAndPointersForSuspendedContextOfProcess: aProcess
  	"Set stackPage, instructionPointer, framePointer and stackPointer for the suspendedContext of
  	 aProcess, marrying the context if necessary, and niling the suspendedContext slot.  This is used
  	 on process switch to ensure a context has a stack frame and so can continue execution."
  	| newContext theFrame thePage newPage |
+ 	<inline: true>
  	<var: #theFrame type: #'char *'>
  	<var: #thePage type: #'StackPage *'>
  	<var: #newPage type: #'StackPage *'>
  	
  	newContext := objectMemory fetchPointer: SuspendedContextIndex ofObject: aProcess.
  	self assert: (objectMemory isContext: newContext).
  	(self isMarriedOrWidowedContext: newContext) ifTrue:
  		[self assert: (self checkIsStillMarriedContext: newContext currentFP: framePointer)].
  	objectMemory
  		storePointerUnchecked: SuspendedContextIndex
  		ofObject: aProcess
  		withValue: objectMemory nilObject.
  	(self isStillMarriedContext: newContext)
  		ifTrue:
  			[theFrame := self frameOfMarriedContext: newContext.
  			 thePage := stackPages stackPageFor: theFrame.
  			 theFrame ~= thePage headFP ifTrue:
  				["explicit assignment of suspendedContext can cause switch to interior frame."
  				 newPage := self newStackPage.
  				 self moveFramesIn: thePage
  					through: (self findFrameAbove: theFrame inPage: thePage)
  					toPage: newPage.
  				  stackPages markStackPageLeastMostRecentlyUsed: newPage].
  			 self assert: thePage headFP = theFrame]
  		ifFalse:
  			[thePage := self makeBaseFrameFor: newContext.
  			 theFrame := thePage baseFP].
  	self setStackPageAndLimit: thePage.
  	stackPointer := thePage headSP.
  	framePointer := thePage headFP.
  	(self isMachineCodeFrame: framePointer) ifFalse:
  		[self setMethod: (self iframeMethod: framePointer)].
  	instructionPointer := self popStack.
  	self assertValidExecutionPointe: instructionPointer r: framePointer s: stackPointer!

Item was removed:
- ----- Method: StackToRegisterMappingCogit class>>prepareToBeAddedToCodeGenerator: (in category 'translation') -----
- prepareToBeAddedToCodeGenerator: aCCodeGenerator
- 	"Override to avoid repeating SimpleStackBasedCogit's preparations and remove the methods we override."
- 	self selectors do:
- 		[:sel|
- 		 (superclass whichClassIncludesSelector: sel) ifNotNil:
- 			[aCCodeGenerator removeMethodForSelector: sel]]!

Item was changed:
  ----- Method: StackToRegisterMappingCogit>>numRegArgs (in category 'compile abstract instructions') -----
  numRegArgs
+ 	<doNotGenerate>
+ 	^objectRepresentation numRegArgs!
- 	<api>
- 	^objectRepresentation preferredNumRegArgs!

Item was removed:
- ----- Method: ThreadedFFIPlugin class>>prepareToBeAddedToCodeGenerator: (in category 'translation') -----
- prepareToBeAddedToCodeGenerator: aCodeGen
- 	"Remove the methods of ThreadedFFIPlugin any concrete subclass overrides,
- 	 and the methods of InterpreterPlugin that ThreadedFFIPlugin overrides."
- 	self selectors do:
- 		[:sel|
- 		 (superclass includesSelector: sel) ifTrue:
- 			[aCodeGen removeMethodForSelector: sel]]!

Item was removed:
- ----- Method: VMStructType class>>prepareToBeAddedToCodeGenerator: (in category 'translation') -----
- prepareToBeAddedToCodeGenerator: aCodeGen
- 	aCodeGen
- 		removeVariable: 'coInterpreter';
- 		removeVariable: 'cogit';
- 		removeVariable: 'objectMemory';
- 		removeVariable: 'objectRepresentation' ifAbsent: []!



More information about the Vm-dev mailing list