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

commits at source.squeak.org commits at source.squeak.org
Thu Jan 11 21:29:09 UTC 2018


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

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

Name: VMMaker.oscog-eem.2313
Author: eem
Time: 11 January 2018, 1:28:45.142727 pm
UUID: ded2cdb5-af55-4fc2-bba8-2eeccd629745
Ancestors: VMMaker.oscog-eem.2312

Cogit:
Fix bad bug in ceSend:above:to:numArgs: which was written to accept an association, not a class.  The rewrite agrees with the interpreter's definition.

Fix bad bug in ceSend:super:to:numArgs: and ceSend:above:to:numArgs:.  Can only patch a send site to an Open PIC if the send is a normal one.  So don't patch in ceSend:above:to:numArgs:, and only if not a super send in ceSend:super:to:numArgs:.

Fix initializeBytecodeTable to default to V3PlusClosures+SistaV1 when MULTIPLEBYTECODESETS is true, again mirroring the interpreter.

Fix in-image compilation for full blocks.  Needs CompiledBlock>>numCopiedValues from e.g. Kernel-eem.1143.

Nuke numCopiedTemps:, which is obsolete given full blocks.

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

Item was changed:
  ----- Method: CoInterpreter>>ceSend:above:to:numArgs: (in category 'trampolines') -----
+ ceSend: selector above: methodClass to: rcvr numArgs: numArgs
- ceSend: selector above: startAssociationArg to: rcvr numArgs: numArgs
  	"Entry-point for an unlinked directed super send in a CogMethod.  Smalltalk stack looks like
  					receiver
  					args
  		head sp ->	sender return pc
  	startAssociation is an association whose value is the class above which to start the lookup.
  
  	If an MNU then defer to handleMNUInMachineCodeTo:... which will dispatch the MNU and
  	may choose to allocate a closed PIC with a fast MNU dispatch for this send.  Otherwise
  	attempt to link the send site as efficiently as possible.  All link attempts may fail; e.g.
  	because we're out of code memory.
  
  	Continue execution via either executeMethod or interpretMethodFromMachineCode:
  	depending on whether the target method is cogged or not."
  	<api>
  	<option: #BytecodeSetHasDirectedSuperSend>
+ 	| classTag classObj errSelIdx cogMethod |
- 	| startAssociation classTag classObj errSelIdx cogMethod |
  	<inline: false>
  	<var: #cogMethod type: #'CogMethod *'>
  	<var: #newCogMethod type: #'CogMethod *'>
  	"self printExternalHeadFrame"
  	"self printStringOf: selector"
  	cogit assertCStackWellAligned.
  	self assert: (objectMemory addressCouldBeOop: rcvr).
  	self sendBreakpoint: selector receiver: rcvr.
+ 	classTag := objectMemory classTagForClass: (self superclassOf: (objectMemory followMaybeForwarded: methodClass)).
- 	startAssociation := objectMemory followMaybeForwarded: startAssociationArg.
- 	classTag := objectMemory classTagForClass: (self superclassOf: (objectMemory fetchPointer: ValueIndex ofObject: startAssociation)).
  	argumentCount := numArgs.
  	(self lookupInMethodCacheSel: selector classTag: classTag)
  		ifTrue:"check for coggability because method is in the cache"
  			[self
  				ifAppropriateCompileToNativeCode: newMethod
  				selector: selector]
  		ifFalse:
  			[self deny: (objectMemory isForwardedClassTag: classTag).
  			 (objectMemory isOopForwarded: selector) ifTrue:
  				[^self
  					ceSend: (self handleForwardedSelectorFaultFor: selector)
+ 					above: methodClass
- 					above: startAssociation
  					to: rcvr
  					numArgs: numArgs].
  			 messageSelector := selector.
  			 classObj := objectMemory classForClassTag: classTag.
  			 (errSelIdx := self lookupOrdinaryNoMNUEtcInClass: classObj) ~= 0 ifTrue:
  				[(errSelIdx = SelectorDoesNotUnderstand
  				  and: [(cogMethod := cogit cogMNUPICSelector: messageSelector
  											receiver: rcvr
  											methodOperand: (self mnuMethodOrNilFor: rcvr)
  											numArgs: argumentCount) asUnsignedInteger
  						> cogit minCogMethodAddress]) ifTrue:
  						[cogit
  							linkSendAt: (stackPages longAt: stackPointer)
  							in: (self mframeHomeMethod: framePointer)
  							to: cogMethod
  							offset: cogit noCheckEntryOffset
  							receiver: rcvr].
  				self handleMNU: errSelIdx
  					InMachineCodeTo: rcvr
  					classForMessage: classObj.
  				self assert: false "NOTREACHED"]].
  	"Method found and has a cog method.  Attempt to link to it.  The receiver's class may be young.
+ 	 We must not link to an Open PIC since they perform normal sends."
- 	 If the Cogit can't store young classes in inline caches we can link to an open PIC instead."
  	(self maybeMethodHasCogMethod: newMethod) ifTrue:
  		[cogMethod := self cogMethodOf: newMethod.
  		 cogMethod selector = objectMemory nilObject
  			ifTrue: [cogit setSelectorOf: cogMethod to: selector]
  			ifFalse:
  				["Deal with anonymous accessors, e.g. in Newspeak.  The cogMethod may not have the
  				  correct selector.  If not, try and compile a new method with the correct selector."
  				 cogMethod selector ~= selector ifTrue:
  					[(cogit cog: newMethod selector: selector) ifNotNil:
  						[:newCogMethod| cogMethod := newCogMethod]]].
+ 		 cogMethod selector = selector ifTrue:
+ 			[cogit
+ 				linkSendAt: (stackPages longAt: stackPointer)
+ 				in: (self mframeHomeMethod: framePointer)
+ 				to: cogMethod
+ 				offset: cogit noCheckEntryOffset
+ 				receiver: rcvr].
- 		 cogMethod selector = selector
- 			ifTrue:
- 				[cogit
- 					linkSendAt: (stackPages longAt: stackPointer)
- 					in: (self mframeHomeMethod: framePointer)
- 					to: cogMethod
- 					offset: cogit noCheckEntryOffset
- 					receiver: rcvr]
- 			ifFalse: "If patchToOpenPICFor:.. returns we're out of code memory"
- 				[cogit
- 					patchToOpenPICFor: selector
- 					numArgs: numArgs
- 					receiver: rcvr].
  		 instructionPointer := self popStack.
  		 self executeNewMethod.
  		 self assert: false "NOTREACHED"].
  	instructionPointer := self popStack.
  	^self interpretMethodFromMachineCode
  	"NOTREACHED"!

Item was changed:
  ----- Method: CoInterpreter>>ceSend:super:to:numArgs: (in category 'trampolines') -----
  ceSend: selector super: superNormalBar to: rcvr numArgs: numArgs
  	"Entry-point for an unlinked send in a CogMethod.  Smalltalk stack looks like
  					receiver
  					args
  		head sp ->	sender return pc
  		
  	If an MNU then defer to handleMNUInMachineCodeTo:... which will dispatch the MNU and
  	may choose to allocate a closed PIC with a fast MNU dispatch for this send.  Otherwise
  	attempt to link the send site as efficiently as possible.  All link attempts may fail; e.g.
  	because we're out of code memory.
  
  	Continue execution via either executeMethod or interpretMethodFromMachineCode:
  	depending on whether the target method is cogged or not."
  	<api>
  	| classTag classObj errSelIdx cogMethod |
  	<inline: false>
  	<var: #cogMethod type: #'CogMethod *'>
  	<var: #newCogMethod type: #'CogMethod *'>
  	"self printExternalHeadFrame"
  	"self printStringOf: selector"
  	cogit assertCStackWellAligned.
  	self assert: (objectMemory addressCouldBeOop: rcvr).
  	self sendBreakpoint: selector receiver: rcvr.
  	superNormalBar = 0
  		ifTrue: [classTag := objectMemory fetchClassTagOf: rcvr]
  		ifFalse: [classTag := objectMemory classTagForClass: (self superclassOf: (self methodClassOf: (self frameMethodObject: framePointer)))].
  	argumentCount := numArgs.
  	(self lookupInMethodCacheSel: selector classTag: classTag)
  		ifTrue:"check for coggability because method is in the cache"
  			[self
  				ifAppropriateCompileToNativeCode: newMethod
  				selector: selector]
  		ifFalse:
  			[(objectMemory isOopForwarded: selector) ifTrue:
  				[^self
  					ceSend: (self handleForwardedSelectorFaultFor: selector)
  					super: superNormalBar
  					to: rcvr
  					numArgs: numArgs].
  			 (objectMemory isForwardedClassTag: classTag) ifTrue:
  				[self assert: superNormalBar = 0.
  				^self
  					ceSend: selector
  					super: superNormalBar
  					to: (self handleForwardedSendFaultForReceiver: rcvr stackDelta: 1 "skip return pc")
  					numArgs: numArgs].
  			 messageSelector := selector.
  			 classObj := objectMemory classForClassTag: classTag.
  			 (errSelIdx := self lookupOrdinaryNoMNUEtcInClass: classObj) ~= 0 ifTrue:
  				[(errSelIdx = SelectorDoesNotUnderstand
  				  and: [(cogMethod := cogit cogMNUPICSelector: messageSelector
  											receiver: rcvr
  											methodOperand: (self mnuMethodOrNilFor: rcvr)
  											numArgs: argumentCount) asUnsignedInteger
  						> cogit minCogMethodAddress]) ifTrue:
  						[cogit
  							linkSendAt: (stackPages longAt: stackPointer)
  							in: (self mframeHomeMethod: framePointer)
  							to: cogMethod
  							offset: (superNormalBar = 0
  									ifTrue: [cogit entryOffset]
  									ifFalse: [cogit noCheckEntryOffset])
  							receiver: rcvr].
  				self handleMNU: errSelIdx InMachineCodeTo: rcvr classForMessage: classObj.
  				self assert: false "NOTREACHED"]].
  	"Method found and has a cog method.  Attempt to link to it.  The receiver's class may be young.
  	 If the Cogit can't store young classes in inline caches we can link to an open PIC instead."
  	(self maybeMethodHasCogMethod: newMethod) ifTrue:
  		[cogMethod := self cogMethodOf: newMethod.
  		 cogMethod selector = objectMemory nilObject
  			ifTrue: [cogit setSelectorOf: cogMethod to: selector]
  			ifFalse:
  				["Deal with anonymous accessors, e.g. in Newspeak.  The cogMethod may not have the
  				  correct selector.  If not, try and compile a new method with the correct selector."
  				 cogMethod selector ~= selector ifTrue:
  					[(cogit cog: newMethod selector: selector) ifNotNil:
  						[:newCogMethod| cogMethod := newCogMethod]]].
  		 cogMethod selector = selector
  			ifTrue:
  				[cogit
  					linkSendAt: (stackPages longAt: stackPointer)
  					in: (self mframeHomeMethod: framePointer)
  					to: cogMethod
  					offset: (superNormalBar = 0
  								ifTrue: [cogit entryOffset]
  								ifFalse: [cogit noCheckEntryOffset])
  					receiver: rcvr]
  			ifFalse: "If patchToOpenPICFor:.. returns we're out of code memory"
+ 				[superNormalBar = 0 ifTrue: "Open PICs perform normal sends. Can't patch if this is a super send."
+ 					[cogit
+ 						patchToOpenPICFor: selector
+ 						numArgs: numArgs
+ 						receiver: rcvr]].
- 				[cogit
- 					patchToOpenPICFor: selector
- 					numArgs: numArgs
- 					receiver: rcvr].
  		 instructionPointer := self popStack.
  		 self executeNewMethod.
  		 self assert: false "NOTREACHED"].
  	instructionPointer := self popStack.
  	^self interpretMethodFromMachineCode
  	"NOTREACHED"!

Item was changed:
  ----- Method: Cogit class>>genAndDis:options: (in category 'in-image compilation') -----
  genAndDis: methodOrDoitString options: optionsDictionaryOrArray
  	| tuple |
+ 	methodOrDoitString isCompiledCode ifFalse:
- 	methodOrDoitString isCompiledMethod ifFalse:
  		[^self
  			genAndDis: (Compiler new
  							compiledMethodFor: methodOrDoitString
  							in: nil
  							to: nil
  							notifying: nil
  							ifFail: nil
  							logged: false)
  			 options: optionsDictionaryOrArray].
+ 	tuple := self cog: methodOrDoitString
+ 				selectorOrNumCopied: (methodOrDoitString isCompiledBlock
+ 											ifTrue: [methodOrDoitString numCopiedValues]
+ 											ifFalse: [methodOrDoitString selector])
+ 				options: optionsDictionaryOrArray.
- 	tuple := self cog: methodOrDoitString selectorOrNumCopied: methodOrDoitString selector options: optionsDictionaryOrArray.
  	tuple second disassembleMethod: tuple last.
  	^tuple!

Item was changed:
  ----- Method: Cogit class>>initializeBytecodeTable (in category 'class initialization') -----
  initializeBytecodeTable
  	"SimpleStackBasedCogit initializeBytecodeTableWith: Dictionary new"
  	"StackToRegisterMappingCogit initializeBytecodeTableWith: Dictionary new"
  
  	| initializer |
  	BytecodeSetHasDirectedSuperSend := BytecodeSetHasExtensions := false.
  	initializer := initializationOptions
  					at: #bytecodeTableInitializer
  					ifAbsent:
  						[NewspeakVM
  							ifTrue:
  								[MULTIPLEBYTECODESETS
  									ifTrue: [#initializeBytecodeTableForSqueakV3PlusClosuresNewspeakV4Hybrid]
  									ifFalse: [#initializeBytecodeTableForNewspeakV4]]
  							ifFalse:
+ 								[MULTIPLEBYTECODESETS
+ 									ifTrue: [#initializeBytecodeTableForSqueakV3PlusClosuresSistaV1Hybrid]
+ 									ifFalse: [#initializeBytecodeTableForSqueakV3PlusClosures]]].
- 								[#initializeBytecodeTableForSqueakV3PlusClosures]].
  	"Now make sure all classes in the hierarchy have initialized to the same bytecode table."
  	(self withAllSuperclasses copyUpTo: Cogit) reverseDo: "i.e. exclude Cogit"
  		[:cogitClass|
  		 cogitClass perform: initializer]!

Item was changed:
  ----- Method: CurrentImageCoInterpreterFacade>>fetchPointer:ofObject: (in category 'accessing') -----
  fetchPointer: index ofObject: anOop
  	| obj |
  	obj := (objectMap keyAtValue: anOop).
+ 	^self oopForObject: (obj isCompiledCode
- 	^self oopForObject: (obj isCompiledMethod
  							ifTrue: [obj objectAt: index + 1]
  							ifFalse: [obj instVarAt: index + 1])!

Item was changed:
  ----- Method: CurrentImageCoInterpreterFacade>>isOopCompiledMethod: (in category 'accessing') -----
  isOopCompiledMethod: anOop
+ 	^(objectMap keyAtValue: anOop) isCompiledCode!
- 	^(objectMap keyAtValue: anOop) isCompiledMethod!

Item was removed:
- ----- Method: StackDepthFinder>>pushClosureTemps: (in category 'instruction decoding') -----
- pushClosureTemps: numTemps
- 	"230		11100110	iiiiiiii		PushNClosureTemps iiiiiiii"
- 	stackp := stackp + numTemps!



More information about the Vm-dev mailing list