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

commits at source.squeak.org commits at source.squeak.org
Sat Feb 13 00:38:39 UTC 2016


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

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

Name: VMMaker.oscog-eem.1676
Author: eem
Time: 13 February 2016, 4:36:28.183629 pm
UUID: 21db194f-99da-4bb8-b89e-3101d8f6f498
Ancestors: VMMaker.oscog-eem.1675

NewspeakVM: Don't use cppIf: #NewspeakVM in VM code.  It is appropriate only in plugin code.  VM code should use the NewspeakVM variable from VMBasicConstants.

Slang:
Fix nilOrBooleanConditionFor: to also work for symbol arguments (such as #Newspeak).  Emit a warning if a symbol is used in VM code when a variable also exists and the symbol/variable is not one that is defined at compile time.

Provide an abstraction for namesDefinedAtCompileTime to avoid the #includes: call that existed in all clients.

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

Item was changed:
  ----- Method: CCodeGenerator>>emitCConstants:on: (in category 'C code generator') -----
  emitCConstants: constList on: aStream
  	"Store the global variable declarations on the given stream."
  	constList isEmpty ifTrue: [^self].
  	aStream cr; nextPutAll: '/*** Constants ***/'; cr.
  	(self sortStrings: constList) do:
  		[:varName| | node default value conditional |
  		node := constants at: varName.
  		node name isEmpty ifFalse:
  			["If the definition includes a C comment, take it as is, otherwise convert the value from Smalltalk to C.
  			  Allow the class to provide an alternative definition, either of just the value or the whole shebang."
  			default := (node value isString and: [node value includesSubString: '/*'])
  							ifTrue: [node value]
  							ifFalse: [self cLiteralFor: node value name: varName].
  			default = #undefined
  				ifTrue: [aStream nextPutAll: '#undef '; nextPutAll: node name; cr]
  				ifFalse:
+ 					[conditional := VMBasicConstants defineAtCompileTime: node name.
- 					[conditional := VMBasicConstants namesDefinedAtCompileTime includes: node name.
  					conditional ifTrue:
  						[aStream nextPutAll: '#if !!defined('; nextPutAll: node name; nextPutAll: ') /* Allow this to be overridden on the compiler command line */'; cr].
  					value := vmClass
  								ifNotNil:
  									[(vmClass specialValueForConstant: node name default: default)
  										ifNotNil: [:specialDef| specialDef]
  										ifNil: [default]]
  								ifNil: [default].
  					value first ~= $# ifTrue:
  						[aStream nextPutAll: (conditional ifTrue: ['# define '] ifFalse: ['#define ']); nextPutAll: node name; space].
  					aStream nextPutAll: value; cr.
  					conditional ifTrue:
  						[aStream nextPutAll: '#endif'; cr]]]].
  	aStream cr!

Item was changed:
  ----- Method: CCodeGenerator>>isConstantNode:valueInto: (in category 'utilities') -----
  isConstantNode: aNode valueInto: aBlock
  	"Answer if aNode evaluates to a constant, and if so, evaluate aBlock with the value of that constant."
  
  	aNode isConstant ifTrue:
  		[(aNode isDefine
+ 		  and: [VMBasicConstants defineAtCompileTime: aNode name]) ifTrue:
- 		 and: [VMBasicConstants namesDefinedAtCompileTime includes: aNode name]) ifTrue:
  			[^false].
  		 aBlock value: aNode value.
  		 ^true].
  	(aNode isVariable
  	 and: [aNode name = #nil]) ifTrue:
  		[aBlock value: nil.
  		 ^true].
  	aNode isSend ifFalse:
  		[^false].
  	(self anyMethodNamed: aNode selector)
  		ifNil:
  			[(VMBasicConstants valueOfBasicSelector: aNode selector) ifNotNil:
  				[:value|
  				 aBlock value: value.
  				 ^true]]
  		ifNotNil:
  			[:m|
  			(m statements size = 1
  			 and: [m statements last isReturn]) ifTrue:
  				[^self isConstantNode: m statements last expression valueInto: aBlock]].
  	^false!

Item was changed:
  ----- Method: CCodeGenerator>>nilOrBooleanConditionFor: (in category 'utilities') -----
  nilOrBooleanConditionFor: nodeOrNil
  	"If nodeOrNil is one of the conditional sends for which we do translation-time dead code elimination
  	 (i.e. cppIf:ifTrue: et al or ifTrue: et al) and the conditional does evaluate to a translation-time
  	 boolean constant, answer that constant, otherwise answer nil.  Used to prune dead code,
+ 	 either for code generaton or dead variable elimination."
+ 	generateDeadCode ifTrue: [^nil].
- 	 either for code egenraton or dead variable elimination."
  	nodeOrNil ifNil:
  		[^nil].
  	nodeOrNil isSend ifFalse:
  		[^nil].
  	(#(cppIf:ifTrue: cppIf:ifTrue:ifFalse:) includes: nodeOrNil selector) ifTrue:
+ 		[(vmClass notNil
+ 		 and: [nodeOrNil args first isConstant
+ 		 and: [nodeOrNil args first value isSymbol
+ 		 and: [(VMBasicConstants defineAtCompileTime: nodeOrNil args first value) not
+ 		 and: [(vmClass bindingOf: nodeOrNil args first value) notNil]]]]) ifTrue:
+ 			[self logger
+ 					nextPutAll: 'Warning: cppIf: reference to ';
+ 					store: nodeOrNil args first value;
+ 					nextPutAll: ' when variable of same name exists.'; cr].
+ 
+ 		 ^(optionsDictionary notNil
- 		[^(optionsDictionary notNil
  		   and: [nodeOrNil args first isConstant
  		   and: [#(true false) includes: (optionsDictionary at: nodeOrNil args first name ifAbsent: [nil])]]) ifTrue:
  			[optionsDictionary at: nodeOrNil args first name]].
  
  	^(#(ifTrue: ifFalse: ifTrue:ifFalse: ifFalse:ifTrue:) includes: nodeOrNil selector) ifTrue:
  		[self nilOrBooleanConstantReceiverOf: nodeOrNil]!

Item was changed:
  ----- Method: CCodeGenerator>>optionIsTrue:in: (in category 'utilities') -----
  optionIsTrue: pragma in: aClass
  	"Answer whether an option: or notOption: pragma is true in the context of aClass.
  	 The argument to the option: pragma is interpreted as either a Cogit class name
  	 or a class variable name or a variable name in VMBasicConstants."
  	| key |
  	key := pragma argumentAt: 1.
  
  	"If the option is one to be defined at compile time we'll generate a
  	 conditional around its declaration and definition."
+ 	(VMBasicConstants defineAtCompileTime: key) ifTrue:
- 	(VMBasicConstants namesDefinedAtCompileTime includes: key) ifTrue:
  		[^true].
  
  	"If the option is the name of a subclass of Cogit, include it if it inherits from the Cogit class."
  	(Smalltalk classNamed: key) ifNotNil:
  		[:optionClass|
  		 aClass cogitClass ifNotNil:
  			[:cogitClass|
  			 (optionClass includesBehavior: Cogit) ifTrue:
  				[^cogitClass includesBehavior: optionClass]].
  		 aClass objectMemoryClass ifNotNil:
  			[:objectMemoryClass|
  			 ((optionClass includesBehavior: ObjectMemory)
  			   or: [optionClass includesBehavior: SpurMemoryManager]) ifTrue:
  				[^objectMemoryClass includesBehavior: optionClass]]].
  	"Lookup options in options, class variables of the defining class, VMBasicConstants, the interpreterClass and the objectMemoryClass"
  	{aClass initializationOptions.
  	  aClass.
  	  VMBasicConstants.
  	  aClass interpreterClass.
  	  aClass objectMemoryClass} do:
  		[:scopeOrNil|
  		 scopeOrNil ifNotNil:
  			[:scope|
  			 (scope bindingOf: key) ifNotNil:
  				[:binding|
  				binding value ~~ false ifTrue: [^true]]]].
  	^false!

Item was changed:
  ----- Method: CoInterpreter>>findNewMethodInClassTag: (in category 'message sending') -----
  findNewMethodInClassTag: classTagArg
  	"Find the compiled method to be run when the current messageSelector is
  	 sent to the given classTag, setting the values of newMethod and primitiveIndex."
  	| ok classTag |
  	<inline: false>
  	ok := self lookupInMethodCacheSel: messageSelector classTag: classTagArg.
  	ok	ifTrue:
  			[self ifAppropriateCompileToNativeCode: newMethod selector: messageSelector]
  		ifFalse:
  			["entry was not found in the cache; perhaps soemthing was forwarded."
  			 classTag := classTagArg.
  			 ((objectMemory isOopForwarded: messageSelector)
  			  or: [objectMemory isForwardedClassTag: classTag]) ifTrue:
  				[(objectMemory isOopForwarded: messageSelector) ifTrue:
  					[messageSelector := self handleForwardedSelectorFaultFor: messageSelector].
  				 (objectMemory isForwardedClassTag: classTag) ifTrue:
  					[classTag := self handleForwardedSendFaultForTag: classTag].
  				ok := self lookupInMethodCacheSel: messageSelector classTag: classTag.
  				ok ifTrue:
  					[^self ifAppropriateCompileToNativeCode: newMethod selector: messageSelector]].
  			 "entry was not found in the cache; look it up the hard way "
  			 lkupClass := objectMemory classForClassTag: classTag.
+ 			 NewspeakVM
- 			 self cppIf: #NewspeakVM
  				ifTrue: [self lookupOrdinarySend]
  				ifFalse: [self lookupMethodInClass: lkupClass].
  			 self addNewMethodToCache: lkupClass]!

Item was changed:
  ----- Method: CoInterpreter>>lookupMNU:receiver: (in category 'cog jit support') -----
  lookupMNU: selector receiver: rcvr
  	<api>
  	"Lookup selector in rcvr, without doing MNU processing, and answer either a
  	 method or an error code if the message was not understood.  Used to populate closed PICs."
  	| classTag inCache erridx |
  	"self printFrame: stackPage headFP WithSP: stackPage headSP"
  	"self printStringOf: selector"
  	classTag := objectMemory fetchClassTagOf: rcvr.
+ 	NewspeakVM
- 	self cppIf: #NewspeakVM
  	  	ifTrue:
+ 			[inCache := self
+ 							inlineLookupInNSMethodCacheSel: selector
+ 							classTag: classTag
+ 							method: 0
+ 							lookupRule: LookupRuleMNU]
- 			[inCache := (self
- 				inlineLookupInNSMethodCacheSel: selector
- 				classTag: classTag
- 				method: 0
- 				lookupRule: LookupRuleMNU)]
  		ifFalse:
  			[inCache := self lookupInMethodCacheSel: selector classTag: classTag].
  	inCache ifFalse:
  		[messageSelector := selector.
  		 erridx := self lookupMNUInClass: (objectMemory classForClassTag: classTag).
  		 erridx ~= 0 ifTrue:
  			[self assert: erridx <= self maxLookupNoMNUErrorCode.
  			 ^erridx]].
  	^newMethod!

Item was changed:
  ----- Method: Cogit>>maybeAllocAndInitIRCs (in category 'newspeak support') -----
  maybeAllocAndInitIRCs
  	"If this is the Newspeak VM and the objectRepresentation supports pinning
  	 then allocate space for the implicit receiver caches on the heap."
+ 	NewspeakVM
- 	self cppIf: #NewspeakVM
  		ifTrue:
  			[indexOfIRC := theIRCs := 0.
  			 (objectRepresentation canPinObjects and: [numIRCs > 0]) ifTrue:
  				[self assert: (self noAssertMethodClassAssociationOf: methodObj) ~= objectMemory nilObject.
  				 theIRCs := objectRepresentation allocateNPinnedSlots: numIRCs * NumOopsPerNSC.
  				 ^theIRCs ~= 0].
  			 ^true]
  		ifFalse:
  			[^true]!

Item was changed:
  ----- Method: Cogit>>maybeMarkIRCsIn: (in category 'newspeak support') -----
  maybeMarkIRCsIn: cogMethod
  	<inline: true>
+ 	NewspeakVM ifTrue:
- 	self cppIf: #NewspeakVM ifTrue:
  		[objectRepresentation canPinObjects ifTrue:
  			[objectRepresentation markIfIRC: cogMethod nextMethodOrIRCs]]!

Item was changed:
  ----- Method: Cogit>>scanMethod (in category 'compile abstract instructions') -----
  scanMethod
  	"Scan the method (and all embedded blocks) to determine
  		- what the last bytecode is; extra bytes at the end of a method are used to encode things like source pointers or temp names
  		- if the method needs a frame or not
  		- what are the targets of any backward branches.
  		- how many blocks it creates
  		- if it contans an unknown bytecode
  	 Answer the block count or on error a negative error code"
  	| latestContinuation nExts descriptor pc numBlocks distance targetPC framelessStackDelta |
  	<var: #descriptor type: #'BytecodeDescriptor *'>
  	needsFrame := false.
  	inBlock := false.
+ 	NewspeakVM ifTrue:
- 	self cppIf: #NewspeakVM ifTrue:
  		[numIRCs := 0].
  	(primitiveIndex > 0
  	 and: [coInterpreter isQuickPrimitiveIndex: primitiveIndex]) ifTrue:
  		[^0].
  	pc := latestContinuation := initialPC.
  	numBlocks := framelessStackDelta := nExts := extA := extB := 0.
  	[pc <= endPC] whileTrue:
  		[byte0 := (objectMemory fetchByte: pc ofObject: methodObj) + bytecodeSetOffset.
  		 descriptor := self generatorAt: byte0.
  		 descriptor isExtension ifTrue:
  			[descriptor opcode = Nop ifTrue: "unknown bytecode tag; see Cogit class>>#generatorTableFrom:"
  				[^EncounteredUnknownBytecode].
  			 self loadSubsequentBytesForDescriptor: descriptor at: pc.
  			 self perform: descriptor generator].
  		 (descriptor isReturn
  		  and: [pc >= latestContinuation]) ifTrue:
  			[endPC := pc].
  		 needsFrame ifFalse:
  			[(descriptor needsFrameFunction isNil
  			  or: [self perform: descriptor needsFrameFunction with: framelessStackDelta])
  				ifTrue: [needsFrame := true]
  				ifFalse: [framelessStackDelta := framelessStackDelta + descriptor stackDelta]].
  		 descriptor isBranch ifTrue:
  			[distance := self spanFor: descriptor at: pc exts: nExts in: methodObj.
  			 targetPC := pc + descriptor numBytes + distance.
  			 (self isBackwardBranch: descriptor at: pc exts: nExts in: methodObj)
  				ifTrue: [self initializeFixupAt: targetPC - initialPC]
  				ifFalse: [latestContinuation := latestContinuation max: targetPC]].
  		 descriptor isBlockCreation ifTrue:
  			[numBlocks := numBlocks + 1.
  			 distance := self spanFor: descriptor at: pc exts: nExts in: methodObj.
  			 targetPC := pc + descriptor numBytes + distance.
  			 latestContinuation := latestContinuation max: targetPC].
+ 		 self cppIf: NewspeakVM ifTrue:
- 		 self cppIf: #NewspeakVM ifTrue:
  			[descriptor hasIRC ifTrue:
  				[numIRCs := numIRCs + 1]].
  		 pc := pc + descriptor numBytes.
  		 descriptor isExtension
  			ifTrue: [nExts := nExts + 1]
  			ifFalse: [nExts := extA := extB := 0]].
  	^numBlocks!

Item was changed:
  ----- Method: SimpleStackBasedCogit>>compileFrameBuild (in category 'compile abstract instructions') -----
  compileFrameBuild
  	"Build a frame for a CogMethod activation.  See CoInterpreter class>>initializeFrameIndices.
  	 		receiver (in ReceiverResultReg)
  			arg0
  			...
  			argN
  			caller's saved ip/this stackPage (for a base frame)
  	fp->	saved fp
  			method
  			context (uninitialized?)
  			receiver
  			first temp
  			...
  	sp->	Nth temp
  	If there is a primitive and an error code the Nth temp is the error code.
  	Ensure SendNumArgsReg is set early on (incidentally to nilObj) because
  	it is the flag determining whether context switch is allowed on stack-overflow."
  	| jumpSkip |
  	<inline: false>
  	<var: #jumpSkip type: #'AbstractInstruction *'>
  	needsFrame ifFalse: [^self].
  	backEnd hasLinkRegister ifTrue: [self PushR: LinkReg].
  	self PushR: FPReg.
  	self MoveR: SPReg R: FPReg.
  	methodLabel addDependent: (self annotateAbsolutePCRef:
  		(self PushCw: methodLabel asInteger)). "method"
  	self genMoveConstant: objectMemory nilObject R: SendNumArgsReg.
  	self PushR: SendNumArgsReg. "context"
  	self PushR: ReceiverResultReg.
  	methodOrBlockNumArgs + 1 to: (coInterpreter temporaryCountOfMethodHeader: methodHeader) do:
  		[:i|
  		self PushR: SendNumArgsReg].
  	(self methodUsesPrimitiveErrorCode: methodObj header: methodHeader) ifTrue:
  		[self compileGetErrorCode].
  	self MoveAw: coInterpreter stackLimitAddress R: TempReg.
  	self CmpR: TempReg R: SPReg. "N.B. FLAGS := SPReg - TempReg"
  	"If we can't context switch for this method, use a slightly
  	 slower overflow check that clears SendNumArgsReg."
  	(coInterpreter canContextSwitchIfActivating: methodObj header: methodHeader)
  		ifTrue:
  			[self JumpBelow: stackOverflowCall.
  			 stackCheckLabel := self Label]
  		ifFalse:
  			[jumpSkip := self JumpAboveOrEqual: 0.
  			 self MoveCq: 0 R: SendNumArgsReg.
  			 self Jump: stackOverflowCall.
  			 jumpSkip jmpTarget: (stackCheckLabel := self Label)].
  	self annotateBytecode: stackCheckLabel.
+ 	NewspeakVM ifTrue:
- 	self cppIf: #NewspeakVM ifTrue:
  		[numIRCs > 0 ifTrue:
  		 	[self PrefetchAw: theIRCs]]!

Item was changed:
  ----- Method: SistaStackToRegisterMappingCogit>>compileBlockBodies (in category 'compile abstract instructions') -----
  compileBlockBodies
  	"override to maintain counterIndex when recompiling blocks; sigh."
  	<inline: false>
  	| result compiledBlocksCount blockStart savedNeedsFrame savedNumArgs savedNumTemps
  	  initialStackPtr initialOpcodeIndex initialCounterIndex initialIndexOfIRC |
  	<var: #blockStart type: #'BlockStart *'>
  	self assert: blockCount > 0.
  	"scanBlock: in compileBlockEntry: sets both of these appropriately for each block."
  	savedNeedsFrame := needsFrame.
  	savedNumArgs := methodOrBlockNumArgs.
  	savedNumTemps := methodOrBlockNumTemps.
  	inBlock := true.
  	compiledBlocksCount := 0.
  	[compiledBlocksCount < blockCount] whileTrue:
  		[blockStart := self blockStartAt: compiledBlocksCount.
  		 self scanBlock: blockStart.
  		 initialOpcodeIndex := opcodeIndex.
  		 initialCounterIndex := counterIndex.
+ 		 NewspeakVM ifTrue:
- 		 self cppIf: #NewspeakVM ifTrue:
  			[initialIndexOfIRC := indexOfIRC].
  		 [self compileBlockEntry: blockStart.
  		  initialStackPtr := simStackPtr.
  		  (result := self compileAbstractInstructionsFrom: blockStart startpc + (self pushNilSize: methodObj numInitialNils: blockStart numInitialNils)
  						through: blockStart startpc + blockStart span - 1) < 0 ifTrue:
  			[^result].
  		  "If the final simStackPtr is less than the initial simStackPtr then scanBlock: over-
  		   estimated the number of initial nils (because it assumed one or more pushNils to
  		   produce an operand were pushNils to initialize temps.  This is very rare, so
  		   compensate by checking, adjusting numInitialNils and recompiling the block body.
  		   N.B.  No need to reinitialize the literalsManager because it answers existing literals."
  		  initialStackPtr = simStackPtr]
  			whileFalse:
  				[self assert: initialStackPtr > simStackPtr.
  				 blockStart numInitialNils: blockStart numInitialNils + simStackPtr - initialStackPtr.
  				 blockStart fakeHeader dependent: nil.
  				 self reinitializeFixupsFrom: blockStart startpc + blockStart numInitialNils
  					through: blockStart startpc + blockStart span - 1.
  				 self cCode: 'bzero(abstractOpcodes + initialOpcodeIndex,
  									(opcodeIndex - initialOpcodeIndex) * sizeof(AbstractInstruction))'
  					inSmalltalk: [initialOpcodeIndex to: opcodeIndex - 1 do:
  									[:i| abstractOpcodes at: i put: (CogCompilerClass for: self)]].
  				 opcodeIndex := initialOpcodeIndex.
  				 counterIndex := initialCounterIndex.
+ 				 NewspeakVM ifTrue:
- 				 self cppIf: #NewspeakVM ifTrue:
  					[indexOfIRC := initialIndexOfIRC]].
  		compiledBlocksCount := compiledBlocksCount + 1].
  	needsFrame := savedNeedsFrame.
  	methodOrBlockNumArgs := savedNumArgs.
  	methodOrBlockNumTemps := savedNumTemps.
  	^0!

Item was changed:
  ----- Method: SistaStackToRegisterMappingCogit>>scanMethod (in category 'compile abstract instructions') -----
  scanMethod
  	"Scan the method (and all embedded blocks) to determine
  		- what the last bytecode is; extra bytes at the end of a method are used to encode things like source pointers or temp names
  		- if the method needs a frame or not
  		- what are the targets of any backward branches.
  		- how many blocks it creates
  		- how many counters it needs/conditional branches it contains
  	 Answer the block count or on error a negative error code"
  	| latestContinuation nExts descriptor pc numBlocks distance targetPC framelessStackDelta |
  	<var: #descriptor type: #'BytecodeDescriptor *'>
  	needsFrame := false.
  	inBlock := false.
  	prevBCDescriptor := nil.
  	numCounters := 0.
+ 	NewspeakVM ifTrue:
- 	self cppIf: #NewspeakVM ifTrue:
  		[numIRCs := 0].
  	(primitiveIndex > 0
  	 and: [coInterpreter isQuickPrimitiveIndex: primitiveIndex]) ifTrue:
  		[^0].
  	pc := latestContinuation := initialPC.
  	numBlocks := framelessStackDelta := nExts := extA := extB := 0.
  	[pc <= endPC] whileTrue:
  		[byte0 := (objectMemory fetchByte: pc ofObject: methodObj) + bytecodeSetOffset.
  		 descriptor := self generatorAt: byte0.
  		 descriptor isExtension ifTrue:
  			[descriptor opcode = Nop ifTrue: "unknown bytecode tag; see Cogit class>>#generatorTableFrom:"
  				[^EncounteredUnknownBytecode].
  			 self loadSubsequentBytesForDescriptor: descriptor at: pc.
  			 self perform: descriptor generator].
  		 (descriptor isReturn
  		  and: [pc >= latestContinuation]) ifTrue:
  			[endPC := pc].
  		 needsFrame ifFalse:
  			[(descriptor needsFrameFunction isNil
  			  or: [self perform: descriptor needsFrameFunction with: framelessStackDelta])
  				ifTrue: [needsFrame := true]
  				ifFalse: [framelessStackDelta := framelessStackDelta + descriptor stackDelta]].
  		 descriptor isBranch ifTrue:
  			[distance := self spanFor: descriptor at: pc exts: nExts in: methodObj.
  			 targetPC := pc + descriptor numBytes + distance.
  			 (self isBackwardBranch: descriptor at: pc exts: nExts in: methodObj)
  				ifTrue: [self initializeFixupAt: targetPC - initialPC]
  				ifFalse:
  					[latestContinuation := latestContinuation max: targetPC.
  					 (descriptor isBranchTrue or: [descriptor isBranchFalse]) ifTrue:
  						[numCounters := numCounters + 1]]].
  		 descriptor isBlockCreation ifTrue:
  			[numBlocks := numBlocks + 1.
  			 distance := self spanFor: descriptor at: pc exts: nExts in: methodObj.
  			 targetPC := pc + descriptor numBytes + distance.
  			 latestContinuation := latestContinuation max: targetPC].
+ 		 NewspeakVM ifTrue:
- 		 self cppIf: #NewspeakVM ifTrue:
  			[descriptor hasIRC ifTrue:
  				[numIRCs := numIRCs + 1]].
  		 pc := pc + descriptor numBytes.
  		 descriptor isExtension
  			ifTrue: [nExts := nExts + 1]
  			ifFalse: [nExts := extA := extB := 0].
  		 prevBCDescriptor := descriptor].
  	^numBlocks!

Item was changed:
  ----- Method: StackInterpreter>>findNewMethodInClassTag: (in category 'message sending') -----
  findNewMethodInClassTag: classTagArg
  	"Find the compiled method to be run when the current 
  	messageSelector is sent to the given class, setting the values 
  	of 'newMethod' and 'primitiveIndex'."
  	| ok classTag |
  	<inline: false>
  	ok := self lookupInMethodCacheSel: messageSelector classTag: classTagArg.
  	ok ifFalse: "entry was not found in the cache; look it up the hard way "
  		[classTag := classTagArg.
  		 ((objectMemory isOopForwarded: messageSelector)
  		  or: [objectMemory isForwardedClassTag: classTag]) ifTrue:
  			[(objectMemory isOopForwarded: messageSelector) ifTrue:
  				[messageSelector := self handleForwardedSelectorFaultFor: messageSelector].
  			 (objectMemory isForwardedClassTag: classTag) ifTrue:
  				[classTag := self handleForwardedSendFaultForTag: classTag].
  			ok := self lookupInMethodCacheSel: messageSelector classTag: classTag.
  			ok ifTrue:
  				[^nil]].
   		 lkupClass := objectMemory classForClassTag: classTag.
+ 		 NewspeakVM
- 		 self cppIf: #NewspeakVM
  				ifTrue: [self lookupOrdinarySend]
  				ifFalse: [self lookupMethodInClass: lkupClass].
  		 self addNewMethodToCache: lkupClass]!

Item was changed:
  ----- Method: StackInterpreter>>lookupMNUInClass: (in category 'message sending') -----
  lookupMNUInClass: class
  	"Lookup messageSelector in class.  Answer 0 on success. Answer the splObj: index
  	 for the error selector to use on failure rather than performing MNU processing etc."
  	| currentClass dictionary found |
  	<inline: false>
  	currentClass := class.
  	[currentClass ~= objectMemory nilObject] whileTrue:
  		[dictionary := objectMemory followObjField: MethodDictionaryIndex ofObject: currentClass.
  		 dictionary = objectMemory nilObject ifTrue:
  			[lkupClass := self superclassOf: currentClass.
  			 ^SelectorCannotInterpret].
  		found := self lookupMethodInDictionary: dictionary.
+ 		NewspeakVM
- 		self cppIf: #NewspeakVM
  			ifTrue: [found ifTrue: [lkupClass := class. self addNewMethodToNSCache: LookupRuleMNU. ^0]]
  			ifFalse: [found ifTrue: [self addNewMethodToCache: class. ^0]].
  		currentClass := self superclassOf: currentClass].
  	lkupClass := class.
  	^SelectorDoesNotUnderstand!

Item was changed:
  ----- Method: StackInterpreter>>lookupOrdinaryNoMNUEtcInClass: (in category 'message sending') -----
  lookupOrdinaryNoMNUEtcInClass: class
  	"Lookup messageSelector in class.  Answer 0 on success. Answer the splObj: index
  	 for the error selector to use on failure rather than performing MNU processing etc."
  	| currentClass dictionary found |
  	<inline: false>
  	currentClass := class.
  	[currentClass ~= objectMemory nilObject] whileTrue:
  		[dictionary := objectMemory followObjField: MethodDictionaryIndex ofObject: currentClass.
  		 dictionary = objectMemory nilObject ifTrue:
  			[lkupClass := self superclassOf: currentClass.
  			 ^SelectorCannotInterpret].
  		found := self lookupMethodInDictionary: dictionary.
+ 		NewspeakVM
- 		self cppIf: #NewspeakVM
  			ifTrue:
  				[found ifTrue:
  					[(self isPublicMethod: newMethod) ifTrue:
  						[self addNewMethodToCache: class. ^0].
  					(self isProtectedMethod: newMethod) ifTrue:
  						[lkupClass := class. ^SelectorDoesNotUnderstand]]]
  			ifFalse:
  				[found ifTrue:
  					[self addNewMethodToCache: class. ^0]].
  		currentClass := self superclassOf: currentClass].
  	lkupClass := class.
  	^SelectorDoesNotUnderstand!

Item was changed:
  ----- Method: StackToRegisterMappingCogit>>compileBlockBodies (in category 'compile abstract instructions') -----
  compileBlockBodies
  	<inline: false>
  	| result compiledBlocksCount blockStart savedNeedsFrame savedNumArgs savedNumTemps
  	  initialStackPtr initialOpcodeIndex initialIndexOfIRC |
  	<var: #blockStart type: #'BlockStart *'>
  	self assert: blockCount > 0.
  	"scanBlock: in compileBlockEntry: sets both of these appropriately for each block."
  	savedNeedsFrame := needsFrame.
  	savedNumArgs := methodOrBlockNumArgs.
  	savedNumTemps := methodOrBlockNumTemps.
  	inBlock := true.
  	compiledBlocksCount := 0.
  	[compiledBlocksCount < blockCount] whileTrue:
  		[blockStart := self blockStartAt: compiledBlocksCount.
  		 self scanBlock: blockStart.
  		 initialOpcodeIndex := opcodeIndex.
  		 literalsManager saveForBlockCompile.
+ 		 NewspeakVM ifTrue:
- 		 self cppIf: #NewspeakVM ifTrue:
  			[initialIndexOfIRC := indexOfIRC].
  		 [self compileBlockEntry: blockStart.
  		  initialStackPtr := simStackPtr.
  		  (result := self compileAbstractInstructionsFrom: blockStart startpc + (self pushNilSize: methodObj numInitialNils: blockStart numInitialNils)
  						through: blockStart startpc + blockStart span - 1) < 0 ifTrue:
  			[^result].
  		  "If the final simStackPtr is less than the initial simStackPtr then scanBlock: over-
  		   estimated the number of initial nils (because it assumed one or more pushNils to
  		   produce an operand were pushNils to initialize temps.  This is very rare, so
  		   compensate by checking, adjusting numInitialNils and recompiling the block body.
  		   N.B.  No need to reinitialize the literalsManager because it answers existing literals."
  		  initialStackPtr = simStackPtr]
  			whileFalse:
  				[self assert: initialStackPtr > simStackPtr.
  				 blockStart numInitialNils: blockStart numInitialNils + simStackPtr - initialStackPtr.
  				 blockStart fakeHeader dependent: nil.
  				 self reinitializeFixupsFrom: blockStart startpc + blockStart numInitialNils
  					through: blockStart startpc + blockStart span - 1.
  				 self cCode: 'bzero(abstractOpcodes + initialOpcodeIndex,
  									(opcodeIndex - initialOpcodeIndex) * sizeof(AbstractInstruction))'
  					inSmalltalk: [initialOpcodeIndex to: opcodeIndex - 1 do:
  									[:i| abstractOpcodes at: i put: (CogCompilerClass for: self)]].
  				 opcodeIndex := initialOpcodeIndex.
  				 literalsManager resetForBlockCompile.
+ 				 NewspeakVM ifTrue:
- 				 self cppIf: #NewspeakVM ifTrue:
  					[indexOfIRC := initialIndexOfIRC]].
  		compiledBlocksCount := compiledBlocksCount + 1].
  	needsFrame := savedNeedsFrame.
  	methodOrBlockNumArgs := savedNumArgs.
  	methodOrBlockNumTemps := savedNumTemps.
  	^0!

Item was changed:
  ----- Method: StackToRegisterMappingCogit>>scanMethod (in category 'compile abstract instructions') -----
  scanMethod
  	"Scan the method (and all embedded blocks) to determine
  		- what the last bytecode is; extra bytes at the end of a method are used to encode things like source pointers or temp names
  		- if the method needs a frame or not
  		- what are the targets of any backward branches.
  		- how many blocks it creates
  	 Answer the block count or on error a negative error code"
  	| latestContinuation nExts descriptor pc numBlocks distance targetPC framelessStackDelta |
  	<var: #descriptor type: #'BytecodeDescriptor *'>
  	needsFrame := false.
  	inBlock := false.
  	prevBCDescriptor := nil.
+ 	NewspeakVM ifTrue:
- 	self cppIf: #NewspeakVM ifTrue:
  		[numIRCs := 0].
  	(primitiveIndex > 0
  	 and: [coInterpreter isQuickPrimitiveIndex: primitiveIndex]) ifTrue:
  		[^0].
  	pc := latestContinuation := initialPC.
  	numBlocks := framelessStackDelta := nExts := extA := extB := 0.
  	[pc <= endPC] whileTrue:
  		[byte0 := (objectMemory fetchByte: pc ofObject: methodObj) + bytecodeSetOffset.
  		 descriptor := self generatorAt: byte0.
  		 descriptor isExtension ifTrue:
  			[descriptor opcode = Nop ifTrue: "unknown bytecode tag; see Cogit class>>#generatorTableFrom:"
  				[^EncounteredUnknownBytecode].
  			 self loadSubsequentBytesForDescriptor: descriptor at: pc.
  			 self perform: descriptor generator].
  		 (descriptor isReturn
  		  and: [pc >= latestContinuation]) ifTrue:
  			[endPC := pc].
  		 needsFrame ifFalse:
  			[(descriptor needsFrameFunction isNil
  			  or: [self perform: descriptor needsFrameFunction with: framelessStackDelta])
  				ifTrue: [needsFrame := true]
  				ifFalse: [framelessStackDelta := framelessStackDelta + descriptor stackDelta]].
  		 descriptor isBranch ifTrue:
  			[distance := self spanFor: descriptor at: pc exts: nExts in: methodObj.
  			 targetPC := pc + descriptor numBytes + distance.
  			 (self isBackwardBranch: descriptor at: pc exts: nExts in: methodObj)
  				ifTrue: [self initializeFixupAt: targetPC - initialPC]
  				ifFalse: [latestContinuation := latestContinuation max: targetPC]].
  		 descriptor isBlockCreation ifTrue:
  			[numBlocks := numBlocks + 1.
  			 distance := self spanFor: descriptor at: pc exts: nExts in: methodObj.
  			 targetPC := pc + descriptor numBytes + distance.
  			 latestContinuation := latestContinuation max: targetPC].
+ 		 NewspeakVM ifTrue:
- 		 self cppIf: #NewspeakVM ifTrue:
  			[descriptor hasIRC ifTrue:
  				[numIRCs := numIRCs + 1]].
  		 pc := pc + descriptor numBytes.
  		 descriptor isExtension
  			ifTrue: [nExts := nExts + 1]
  			ifFalse: [nExts := extA := extB := 0].
  		 prevBCDescriptor := descriptor].
  	^numBlocks!

Item was changed:
  ----- Method: TMethod>>compileTimeOptionPragmas (in category 'accessing') -----
  compileTimeOptionPragmas
  	"Answer the (possibly empty) sequence of option: or notOption: pragmas
  	 whose arguments are values to be defined at compile time."
  	^self compiledMethod pragmas select:
  		[:pragma|
  		 (#option: == pragma keyword or: [#notOption: == pragma keyword])
+ 		 and: [VMBasicConstants defineAtCompileTime: (pragma argumentAt: 1)]]!
- 		 and: [VMBasicConstants namesDefinedAtCompileTime includes: (pragma argumentAt: 1)]]!

Item was changed:
  ----- Method: TMethod>>compiledMethod (in category 'accessing') -----
  compiledMethod
+ 	^definingClass
+ 		compiledMethodAt: selector
+ 		ifAbsent: [definingClass compiledMethodAt: properties selector]!
- 	^definingClass >> selector!

Item was added:
+ ----- Method: VMBasicConstants class>>defineAtCompileTime: (in category 'C translation') -----
+ defineAtCompileTime: aSymbol
+ 	self assert: aSymbol isSymbol.
+ 	^self namesDefinedAtCompileTime includes: aSymbol!

Item was changed:
  ----- Method: VMClass class>>shouldIncludeMethodForSelector: (in category 'translation') -----
  shouldIncludeMethodForSelector: selector
  	"Answer whether a primitive method should be translated.  Emit a warning to the transcript if the method doesn't exist."
  	^(self whichClassIncludesSelector: selector)
  		ifNotNil:
  			[:c|
  			 (c >> selector pragmaAt: #option:)
  				ifNotNil:
  					[:pragma|
+ 					(VMBasicConstants defineAtCompileTime: pragma arguments first)
- 					(VMBasicConstants namesDefinedAtCompileTime includes: pragma arguments first)
  					 or: [initializationOptions
  							at: pragma arguments first
  							ifAbsent: [(self bindingOf: pragma arguments first)
  										ifNil: [false]
  										ifNotNil: [:binding| binding value ~~ #undefined]]]]
  				ifNil: [true]]
  		ifNil:
  			[Transcript nextPutAll: 'Cannot find implementation of '; nextPutAll: selector; nextPutAll: ' in hierarchy of '; print: self; cr; flush.
  			 false]!



More information about the Vm-dev mailing list