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

commits at source.squeak.org commits at source.squeak.org
Wed Jun 1 23:47:26 UTC 2016


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

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

Name: VMMaker.oscog-eem.1877
Author: eem
Time: 1 June 2016, 4:45:31.895746 pm
UUID: 638b0433-98fd-4fdf-8b75-588d6c09081f
Ancestors: VMMaker.oscog-eem.1876

Cogit:
revise Clément's two-path code for immutability to allow it to be used for frameless setters containing more than one inst var store, avoiding multiple store checks by checking once for the receiver being young.  Good for a 4% speedup in the binary tree benchmark.

Rename needsTwoPath to useTwoPaths.  Refactor StackToRegisterMappingCogit>>scanMethod so that it is used by RegisterMappingCogit and SistaCogit without having to duplicate an already large method with very minor varations three times.

Add an isInstVarStore property to CogBytecodeDescriptor and set it in the bytecode tables.

Fix bug in ARM's concretizeSqrtRd.

Fix Slang bug detabbing empty expansions in cppIf:ifTrue:ifFalse:.

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

Item was changed:
  ----- Method: CCodeGenerator>>generateInlineCppIfElse:asArgument:on:indent: (in category 'C translation') -----
  generateInlineCppIfElse: msgNode asArgument: asArgument on: aStream indent: level
  	"Generate the C code for this message onto the given stream."
  	| expr putStatement |
  	"Compile-time expansion for constants set in the options dictionary,
  	 e.g. to cut down on noise for MULTIPLEBYTECODESETS."
  	putStatement := asArgument
  		ifTrue: "emitCCodeAsArgumentOn: doesn't indent, the code needs indenting if it takes multiple lines, so post-process."
  			[[:node| | expansion |
  			  expansion := String streamContents: [:s| node emitCCodeAsArgumentOn: s level: level generator: self].
  			  aStream nextPutAll:
  			  ((expansion includes: Character cr)
  				ifTrue:
  					[(String streamContents:
  							[:s|
  							s position > 0 ifTrue: [s tab: level + 1].
  							node emitCCodeAsArgumentOn: s level: level generator: self])
  						copyReplaceAll: (String with: Character cr)
  						with: (String with: Character cr), (String new: level + 1 withAll: Character tab)]
  				ifFalse: [expansion])]]
  		ifFalse:
  			[[:node| | expansion |
  			  expansion := String streamContents: [:s| node emitCCodeOn: s level: level generator: self].
  			 "Remove tabs from first line to avoid indenting a second time"
+ 			 expansion ifNotEmpty:
+ 				[expansion := expansion allButFirst: (expansion findFirst: [:c| c ~~ Character tab]) - 1].
- 			 expansion := expansion allButFirst: (expansion findFirst: [:c| c ~~ Character tab]) - 1.
  			 aStream nextPutAll: expansion]].
  
  	(self nilOrBooleanConditionFor: msgNode) ifNotNil:
  		[:condition|
  		 condition
  			ifTrue:
  				[putStatement value: msgNode args second]
  			ifFalse:
  				[msgNode args size >= 3 ifTrue:
  					[putStatement value: msgNode args third]].
  		 ^self].
  
  	"Full #if ... #else..."
  	putStatement := asArgument
  		ifTrue: "emitCCodeAsArgumentOn: doesn't indent, the code needs indenting in this case, so post-process."
  			[[:node|
  			  aStream nextPutAll:
  				((String streamContents:
  						[:s|
  						s next: level + 1 put: Character tab.
  						node emitCCodeAsArgumentOn: s level: level generator: self])
  					copyReplaceAll: (String with: Character cr)
  					with: (String with: Character cr), (String new: level + 1 withAll: Character tab))]]
  		ifFalse:
  			[[:node| node emitCCodeOn: aStream level: level generator: self]].
  
  	expr := String streamContents:
  				[:es|
  				msgNode args first
  					emitCCodeAsArgumentOn: es
  					level: 0
  					generator: self].
  	[expr last isSeparator] whileTrue:
  		[expr := expr allButLast].
  	aStream
  		ensureCr;
  		nextPut: $#; next: level * 2 put: Character space; nextPutAll: 'if '; nextPutAll: expr; cr.
  
  	self with: msgNode args first
  		ifAppropriateSetTo: true
  		do: [putStatement value: msgNode args second].
  	expr := ' /* ', expr, ' */'.
  	msgNode args size >= 3 ifTrue:
  		[aStream
  			ensureCr;
  			nextPut: $#; next: level * 2 put: Character space; nextPutAll: 'else'; nextPutAll: expr;
  			cr.
  		self with: msgNode args first
  			ifAppropriateSetTo: false
  			do: [putStatement value: msgNode args third]].
  	aStream
  		ensureCr;
  		nextPut: $#; next: level * 2 put: Character space; nextPutAll: 'endif'; nextPutAll: expr;
  		cr.
  	asArgument ifTrue:
  		[aStream next: level + 1 put: Character tab]!

Item was changed:
  ----- Method: CogARMCompiler>>concretizeSqrtRd (in category 'generate machine code - concretize') -----
  concretizeSqrtRd
  	"Will get inlined into concretizeAt: switch."
  	<inline: true>
  	"Square root of FP regLHS into regLHS"
  	| regLHS  |
+ 	regLHS := operands at: 0.
- 	regLHS := operands at: 1.
  	machineCode at: 0 put:(self fsqrtd: regLHS).
  	^machineCodeSize := 4
  	!

Item was changed:
  VMStructType subclass: #CogBytecodeDescriptor
+ 	instanceVariableNames: 'generator spanFunction needsFrameFunction stackDelta opcode numBytes isBranchTrue isBranchFalse isReturn isBlockCreation isMapped isMappedInBlock isExtension isInstVarRef isInstVarStore hasIRC'
- 	instanceVariableNames: 'generator spanFunction needsFrameFunction stackDelta opcode numBytes isBranchTrue isBranchFalse isReturn isBlockCreation isMapped isMappedInBlock isExtension isInstVarRef hasIRC'
  	classVariableNames: ''
  	poolDictionaries: ''
  	category: 'VMMaker-JIT'!
  
  !CogBytecodeDescriptor commentStamp: 'eem 11/18/2010 06:32' prior: 0!
  I am an entry in the Cogit's dispatch table for bytecodes.  I hold the routine to call to generate code for the partcular bytecode I represent and the number of bytes the bytecode has.  For eliminating temps in frameless blocks I maintain a stack delta for bytecodes that are valid in a frameless block.  The order of my instance variables is chosen for compact struct packing.!

Item was added:
+ ----- Method: CogBytecodeDescriptor>>isInstVarStore (in category 'accessing') -----
+ isInstVarStore
+ 	"Answer the value of isInstVarStore"
+ 
+ 	^ isInstVarStore!

Item was added:
+ ----- Method: CogBytecodeDescriptor>>isInstVarStore: (in category 'accessing') -----
+ isInstVarStore: anObject
+ 	"Set the value of isInstVarStore"
+ 
+ 	^isInstVarStore := anObject!

Item was added:
+ ----- Method: CogObjectRepresentationForSpur>>genJumpInOldSpace: (in category 'compile abstract instructions') -----
+ genJumpInOldSpace: reg
+ 	"Jump if reg is old."
+ 	<inline: true>
+ 	^cogit
+ 		CmpCq: objectMemory storeCheckBoundary R: reg; "N.B. FLAGS := destReg - scratchReg"
+ 		JumpAboveOrEqual: 0!

Item was added:
+ ----- Method: CogObjectRepresentationForSqueakV3>>genJumpInOldSpace: (in category 'compile abstract instructions') -----
+ genJumpInOldSpace: reg
+ 	"Jump if reg is old."
+ 	<inline: true>
+ 	^cogit
+ 		MoveAw: objectMemory youngStartAddress R: TempReg;
+ 		CmpR: TempReg R: reg;	"N.B. FLAGS := destReg - scratchReg"
+ 		JumpBelow: 0!

Item was changed:
  ----- Method: Cogit class>>generatorTableFrom: (in category 'class initialization') -----
  generatorTableFrom: anArray
  	| blockCreationBytecodeSize |
  	generatorTable := CArrayAccessor on: (Array new: 256).
  	anArray do:
  		[:tuple| | descriptor |
  		(descriptor := CogBytecodeDescriptor new)
  						numBytes: tuple first;
  						generator: tuple fourth;
  						isReturn: (tuple includes: #return);
  						isMapped: ((tuple includes: #isMappedIfImmutability)
  										ifTrue: [self bindingOf: #IMMUTABILITY]
  										ifFalse: [tuple includes: #isMapped]);
  						isMappedInBlock: (tuple includes: #isMappedInBlock);
  						isBlockCreation: (tuple includes: #block);
  						spanFunction: (((tuple includes: #block) or: [(tuple includes: #branch)]) ifTrue:
  										[tuple detect: [:thing| thing isSymbol and: [thing numArgs = 4]]]);
  						isBranchTrue: (tuple includes: #isBranchTrue);
  						isBranchFalse: (tuple includes: #isBranchFalse);
  						isExtension: (tuple includes: #extension);
  						isInstVarRef: (tuple includes: #isInstVarRef);	"for Spur"
+ 						isInstVarStore: (tuple includes: #isInstVarStore);	"for Spur"
  						hasIRC: (tuple includes: #hasIRC);			"for Newspeak"
  						yourself.
  		"As a hack to cut down on descriptor flags, use opcode to tag unusedBytecode for scanning.
  		 Currently descriptors are exactly 16 bytes with all 8 flag bits used (in Newspeak at least 17 bytes,
  		 9 flag bits).  As another hack to eliminate a test in scanMethod mark unknowns as extensions."
  		descriptor generator == #unknownBytecode ifTrue:
  			[descriptor opcode: Nop; isExtension: true].
  		descriptor isBlockCreation ifTrue:
  			[blockCreationBytecodeSize
  				ifNil: [blockCreationBytecodeSize := descriptor numBytes]
  				ifNotNil: [self assert: blockCreationBytecodeSize = descriptor numBytes]].
  		tuple do:
  			[:thing|
  			thing isSymbol ifTrue:
  				[(thing beginsWith: #needsFrame) ifTrue:
  					[descriptor needsFrameFunction: thing].
  				 (CogRTLOpcodes classPool at: thing ifAbsent: []) ifNotNil:
  					[:opcode| descriptor opcode: opcode]]].
  		tuple last isInteger
  			ifTrue: [descriptor stackDelta: tuple last]
  			ifFalse:
  				[descriptor needsFrameFunction ifNotNil:
  					[self error: 'frameless block bytecodes must specify a stack delta']].
  		tuple second to: tuple third do:
  			[:index|
  			generatorTable at: index put: descriptor]].
  	BlockCreationBytecodeSize := blockCreationBytecodeSize.
  	^generatorTable!

Item was added:
+ ----- Method: RegisterAllocatingCogit>>maybeCountFixup (in category 'compile abstract instructions') -----
+ maybeCountFixup
+ 	<inline: true>
+ 	numFixups := numFixups + 1!

Item was added:
+ ----- Method: RegisterAllocatingCogit>>maybeInitNumFixups (in category 'compile abstract instructions') -----
+ maybeInitNumFixups
+ 	<inline: true>
+ 	numFixups := 0!

Item was removed:
- ----- Method: RegisterAllocatingCogit>>scanMethod (in category 'compile abstract instructions') -----
- scanMethod
- 	"Overrides to count the number of fixups."
- 	"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.
- 	numFixups := 0.
- 	prevBCDescriptor := nil.
- 	self
- 		cppIf: IMMUTABILITY
- 		ifTrue: [needsTwoPath := false].
- 	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].
- 		  self
- 			cppIf: IMMUTABILITY
- 			ifTrue: [(needsFrame and: [needsTwoPath not])
- 					ifFalse: [(descriptor needsFrameFunction isNil
- 								or: [self perform: descriptor needsFrameFunction with: framelessStackDelta])
- 							ifTrue: [needsFrame := true.
- 								needsTwoPath := descriptor generator == #genStoreAndPopReceiverVariableBytecode]
- 							ifFalse: [framelessStackDelta := framelessStackDelta + descriptor stackDelta]]]
- 			ifFalse: [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.
- 					numFixups := numFixups + 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.
- 			 numFixups := numFixups + 1].
- 		 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 added:
+ ----- Method: SistaCogit>>maybeCountCounter (in category 'compile abstract instructions') -----
+ maybeCountCounter
+ 	<inline: true>
+ 	numCounters := numCounters + 1!

Item was added:
+ ----- Method: SistaCogit>>maybeInitNumCounters (in category 'compile abstract instructions') -----
+ maybeInitNumCounters
+ 	<inline: true>
+ 	numCounters := 0!

Item was removed:
- ----- Method: SistaCogit>>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 numFixups |
- 	<var: #descriptor type: #'BytecodeDescriptor *'>
- 	self flag: 'numFixup should be reverted to inst var when moving back sistaCogit as subclass of RegisterAllocatingCogit'.
- 	needsFrame := false.
- 	numFixups := 0.
- 	prevBCDescriptor := nil.
- 	numCounters := 0.
- 	self
- 		cppIf: IMMUTABILITY
- 		ifTrue: [needsTwoPath := false].
- 	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].
- 		 self
- 			cppIf: IMMUTABILITY
- 			ifTrue: [(needsFrame and: [needsTwoPath not])
- 					ifFalse: [(descriptor needsFrameFunction isNil
- 								or: [self perform: descriptor needsFrameFunction with: framelessStackDelta])
- 							ifTrue: [needsFrame := true.
- 								needsTwoPath := descriptor generator == #genStoreAndPopReceiverVariableBytecode]
- 							ifFalse: [framelessStackDelta := framelessStackDelta + descriptor stackDelta]]]
- 			ifFalse: [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.
- 					numFixups := numFixups + 1.
- 					 (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.
- 			 numFixups := numFixups + 1].
- 		 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:
  SimpleStackBasedCogit subclass: #StackToRegisterMappingCogit
+ 	instanceVariableNames: 'prevBCDescriptor numPushNilsFunction pushNilSizeFunction methodOrBlockNumTemps regArgsHaveBeenPushed simSelf simStack simStackPtr simSpillBase optStatus ceCallCogCodePopReceiverArg0Regs ceCallCogCodePopReceiverArg1Arg0Regs methodAbortTrampolines picAbortTrampolines picMissTrampolines ceCall0ArgsPIC ceCall1ArgsPIC ceCall2ArgsPIC debugStackPointers debugFixupBreaks realCECallCogCodePopReceiverArg0Regs realCECallCogCodePopReceiverArg1Arg0Regs deadCode useTwoPaths'
- 	instanceVariableNames: 'prevBCDescriptor numPushNilsFunction pushNilSizeFunction methodOrBlockNumTemps regArgsHaveBeenPushed simSelf simStack simStackPtr simSpillBase optStatus ceCallCogCodePopReceiverArg0Regs ceCallCogCodePopReceiverArg1Arg0Regs methodAbortTrampolines picAbortTrampolines picMissTrampolines ceCall0ArgsPIC ceCall1ArgsPIC ceCall2ArgsPIC debugStackPointers debugFixupBreaks realCECallCogCodePopReceiverArg0Regs realCECallCogCodePopReceiverArg1Arg0Regs deadCode needsTwoPath'
  	classVariableNames: 'NeedsMergeFixupFlag NeedsNonMergeFixupFlag'
  	poolDictionaries: 'CogCompilationConstants VMMethodCacheConstants VMObjectIndices VMStackFrameOffsets'
  	category: 'VMMaker-JIT'!
  StackToRegisterMappingCogit class
  	instanceVariableNames: 'numPushNilsFunction pushNilSizeFunction'!
  
+ !StackToRegisterMappingCogit commentStamp: 'eem 6/1/2016 14:50' prior: 0!
- !StackToRegisterMappingCogit commentStamp: 'eem 12/19/2010 18:12' prior: 0!
  StackToRegisterMappingCogit is an optimizing code generator that eliminates a lot of stack operations and inlines some special selector arithmetic.  It does so by a simple stack-to-register mapping scheme based on deferring the generation of code to produce operands until operand-consuming operations.  The operations that consume operands are sends, stores and returns.
  
  See methods in the class-side documentation protocol for more detail.
  
  Instance Variables
  	callerSavedRegMask:							<Integer>
  	ceEnter0ArgsPIC:								<Integer>
  	ceEnter1ArgsPIC:								<Integer>
  	ceEnter2ArgsPIC:								<Integer>
  	ceEnterCogCodePopReceiverArg0Regs:		<Integer>
  	ceEnterCogCodePopReceiverArg1Arg0Regs:	<Integer>
  	debugBytecodePointers:						<Set of Integer>
  	debugFixupBreaks:								<Set of Integer>
  	debugStackPointers:							<CArrayAccessor of (Integer|nil)>
  	methodAbortTrampolines:						<CArrayAccessor of Integer>
  	methodOrBlockNumTemps:						<Integer>
  	optStatus:										<Integer>
  	picAbortTrampolines:							<CArrayAccessor of Integer>
  	picMissTrampolines:							<CArrayAccessor of Integer>
  	realCEEnterCogCodePopReceiverArg0Regs:		<Integer>
  	realCEEnterCogCodePopReceiverArg1Arg0Regs:	<Integer>
  	regArgsHaveBeenPushed:						<Boolean>
  	simSelf:											<CogSimStackEntry>
  	simSpillBase:									<Integer>
  	simStack:										<CArrayAccessor of CogSimStackEntry>
  	simStackPtr:									<Integer>
  	traceSimStack:									<Integer>
+ 	useTwoPaths									<Boolean>
  
  callerSavedRegMask
  	- the bitmask of the ABI's caller-saved registers
  
  ceEnter0ArgsPIC ceEnter1ArgsPIC ceEnter2ArgsPIC
  	- the trampoline for entering an N-arg PIC
  
  ceEnterCogCodePopReceiverArg0Regs ceEnterCogCodePopReceiverArg1Arg0Regs
  	- teh trampoline for entering a method with N register args
  	
  debugBytecodePointers
  	- a Set of bytecode pcs for setting breakpoints (simulation only)
  
  debugFixupBreaks
  	- a Set of fixup indices for setting breakpoints (simulation only)
  
  debugStackPointers
  	- an Array of stack depths for each bytecode for code verification
  
  methodAbortTrampolines
  	- a CArrayAccessor of abort trampolines for 0, 1, 2 and N args
  
  methodOrBlockNumTemps
  	- the number of method or block temps (including args) in the current compilation unit (method or block)
  
  optStatus
  	- the variable used to track the status of ReceiverResultReg for avoiding reloading that register with self between adjacent inst var accesses
  
  picAbortTrampolines
  	- a CArrayAccessor of abort trampolines for 0, 1, 2 and N args
  
  picMissTrampolines
  	- a CArrayAccessor of abort trampolines for 0, 1, 2 and N args
  
  realCEEnterCogCodePopReceiverArg0Regs realCEEnterCogCodePopReceiverArg1Arg0Regs
  	- the real trampolines for ebtering machine code with N reg args when in the Debug regime
  
  regArgsHaveBeenPushed
  	- whether the register args have been pushed before frame build (e.g. when an interpreter primitive is called)
  
  simSelf
  	- the simulation stack entry representing self in the current compilation unit
  
  simSpillBase
  	- the variable tracking how much of the simulation stack has been spilled to the real stack
  
  simStack
  	- the simulation stack itself
  
  simStackPtr
  	- the pointer to the top of the simulation stack
+ 
+ useTwoPaths
+ 	- a variable controlling whether to create two paths through a method based on the existence of inst var stores.  With immutability this causes a frameless path to be generated if an otherwise frameless method is frameful simply because of inst var stores.  In this case the test to take the first frameless path is if the receiver is not immutable.  Without immutability, if a frameless method contains two or more inst var stores, the first path will be code with no store check, chosen by a single check for the receiver being in new space.
  !
  StackToRegisterMappingCogit class
  	instanceVariableNames: 'numPushNilsFunction pushNilSizeFunction'!

Item was changed:
  ----- Method: StackToRegisterMappingCogit class>>initializeBytecodeTableForNewspeakV4 (in category 'class initialization') -----
  initializeBytecodeTableForNewspeakV4
  	"StackToRegisterMappingCogit initializeBytecodeTableForNewspeakV4"
  
  	numPushNilsFunction := #v4:Num:Push:Nils:.
  	pushNilSizeFunction := #v4PushNilSize:numInitialNils:.
  	NSSendIsPCAnnotated := true. "IsNSSendCall used by SendAbsentImplicit"
  	FirstSpecialSelector := 80.
  	NumSpecialSelectors := 32.
  	self flag:
  'Special selector send class must be inlined to agree with the interpreter, which
   inlines class.  If class is sent to e.g. a general instance of ProtoObject then unless
   class is inlined there will be an MNU.  It must be that the Cointerpreter and Cogit
   have identical semantics.  We get away with not hardwiring the other special
   selectors either because in the Cointerpreter they are not inlined or because they
   are inlined only to instances of classes for which there will always be a method.'.
  	self generatorTableFrom: #(
  		"1 byte bytecodes"
  		(1    0   15 genPushReceiverVariableBytecode isInstVarRef needsFrameNever: 1)
  		(1  16   31 genPushLiteralVariable16CasesBytecode needsFrameNever: 1)
  		(1  32   63 genPushLiteralConstantBytecode needsFrameNever: 1)
  		(1  64   75 genPushTemporaryVariableBytecode needsFrameIfMod16GENumArgs: 1)
  		(1  76   76 genPushReceiverBytecode needsFrameNever: 1)
  		(1  77   77 genExtPushPseudoVariableOrOuterBytecode needsFrameIfExtBGT2: 1)
  		(1  78   78 genPushConstantZeroBytecode needsFrameNever: 1)
  		(1  79   79 genPushConstantOneBytecode needsFrameNever: 1)
  
  		(1   80   80 genSpecialSelectorArithmetic isMapped AddRR)
  		(1   81   81 genSpecialSelectorArithmetic isMapped SubRR)
  		(1   82   82 genSpecialSelectorComparison isMapped JumpLess)
  		(1   83   83 genSpecialSelectorComparison isMapped JumpGreater)
  		(1   84   84 genSpecialSelectorComparison isMapped JumpLessOrEqual)
  		(1   85   85 genSpecialSelectorComparison isMapped JumpGreaterOrEqual)
  		(1   86   86 genSpecialSelectorComparison isMapped JumpZero)
  		(1   87   87 genSpecialSelectorComparison isMapped JumpNonZero)
  		(1   88   93 genSpecialSelectorSend isMapped)	 " #* #/ #\\ #@ #bitShift: //"
  		(1   94   94 genSpecialSelectorArithmetic isMapped AndRR)
  		(1   95   95 genSpecialSelectorArithmetic isMapped OrRR)
  		(1   96 101 genSpecialSelectorSend isMapped) "#at: #at:put: #size #next #nextPut: #atEnd"
  		(1 102 102 genSpecialSelectorEqualsEquals needsFrameNever: notMapped -1) "not mapped because it is directly inlined (for now)"
  		(1 103 103 genSpecialSelectorClass needsFrameIfStackGreaterThanOne: notMapped 0) "not mapped because it is directly inlined (for now)"
  		(1 104 111 genSpecialSelectorSend isMapped) "#blockCopy: #value #value: #do: #new #new: #x #y"
  
  		(1 112 127 genSendLiteralSelector0ArgsBytecode isMapped)
  		(1 128 143 genSendLiteralSelector1ArgBytecode isMapped)
  		(1 144 159 genSendLiteralSelector2ArgsBytecode isMapped)
  		(1 160 175	genSendAbsentImplicit0ArgsBytecode isMapped hasIRC)
  			
+ 		(1 176 183 genStoreAndPopReceiverVariableBytecode isInstVarRef isInstVarStore isMappedIfImmutability needsFrameIfImmutability: -1)
- 		(1 176 183 genStoreAndPopReceiverVariableBytecode isInstVarRef isMappedIfImmutability needsFrameIfImmutability: -1)
  			
  		(1 184 191 genStoreAndPopTemporaryVariableBytecode)
  
  		(1 192 199 genShortUnconditionalJump	branch v3:ShortForward:Branch:Distance:)
  		(1 200 207 genShortJumpIfTrue			branch isBranchTrue isMapped "because of mustBeBoolean"
  													v3:ShortForward:Branch:Distance:)
  		(1 208 215 genShortJumpIfFalse			branch isBranchFalse isMapped "because of mustBeBoolean"
  													v3:ShortForward:Branch:Distance:)
  
  		(1 216 216 genReturnReceiver				return needsFrameIfInBlock: isMappedInBlock 0)
  		(1 217 217 genReturnTopFromMethod		return needsFrameIfInBlock: isMappedInBlock -1)
  		(1 218 218 genExtReturnTopFromBlock	return needsFrameNever: -1)
  
  		(1 219 219 duplicateTopBytecode			needsFrameNever: 1)
  		(1 220 220 genPopStackBytecode			needsFrameNever: -1)
  		(1 221 221 genExtNopBytecode			needsFrameNever: 0)
  		(1 222 223	unknownBytecode)
  
  		"2 byte bytecodes"
  		(2 224 224 extABytecode extension					needsFrameNever: 0)
  		(2 225 225 extBBytecode extension					needsFrameNever: 0)
  		(2 226 226 genExtPushReceiverVariableBytecode isInstVarRef)
  		(2 227 227 genExtPushLiteralVariableBytecode		needsFrameNever: 1)
  		(2 228 228 genExtPushLiteralBytecode					needsFrameNever: 1)
  		(2 229 229 genExtPushIntegerBytecode				needsFrameNever: 1)
  		(2 230 230 genLongPushTemporaryVariableBytecode)
  		(2 231 231 genPushNewArrayBytecode)
+ 		(2 232 232 genExtStoreReceiverVariableBytecode isInstVarRef isInstVarStore isMappedIfImmutability)
- 		(2 232 232 genExtStoreReceiverVariableBytecode isInstVarRef isMappedIfImmutability)
  		(2 233 233 genExtStoreLiteralVariableBytecode isMappedIfImmutability)
  		(2 234 234 genLongStoreTemporaryVariableBytecode)
+ 		(2 235 235 genExtStoreAndPopReceiverVariableBytecode isInstVarRef isInstVarStore isMappedIfImmutability)
- 		(2 235 235 genExtStoreAndPopReceiverVariableBytecode isInstVarRef isMappedIfImmutability)
  		(2 236 236 genExtStoreAndPopLiteralVariableBytecode isMappedIfImmutability)
  		(2 237 237 genLongStoreAndPopTemporaryVariableBytecode)
  
  		(2 238 238 genExtSendBytecode isMapped)
  		(2 239 239 genExtSendSuperBytecode isMapped)
  		(2 240 240 genExtSendAbsentImplicitBytecode isMapped hasIRC)
  		(2 241 241 genExtSendAbsentDynamicSuperBytecode isMapped hasIRC)
  
  		(2 242 242 genExtUnconditionalJump	branch isMapped "because of interrupt check" v4:Long:Branch:Distance:)
  		(2 243 243 genExtJumpIfTrue			branch isBranchTrue isMapped "because of mustBeBoolean" v4:Long:Branch:Distance:)
  		(2 244 244 genExtJumpIfFalse			branch isBranchFalse isMapped "because of mustBeBoolean" v4:Long:Branch:Distance:)
  
  		(2 245 245	genExtSendAbsentSelfBytecode isMapped hasIRC)
  
  		(2 246 248	unknownBytecode)
  
  		"3 byte bytecodes"
  		(3 249 249 genCallPrimitiveBytecode)
  		(3 250 250 genPushRemoteTempLongBytecode)
  		(3 251 251 genStoreRemoteTempLongBytecode)
  		(3 252 252 genStoreAndPopRemoteTempLongBytecode)
  		(3 253 253 genExtPushClosureBytecode block v4:Block:Code:Size:)
  		(3 254 254	genExtSendAbsentOuterBytecode isMapped hasIRC)
  
  		(3 255 255	unknownBytecode))!

Item was changed:
  ----- Method: StackToRegisterMappingCogit class>>initializeBytecodeTableForSistaV1 (in category 'class initialization') -----
  initializeBytecodeTableForSistaV1
  	"StackToRegisterMappingCogit initializeBytecodeTableForSistaV1"
  
  	numPushNilsFunction := #sistaV1:Num:Push:Nils:.
  	pushNilSizeFunction := #sistaV1PushNilSize:numInitialNils:.
  	BytecodeSetHasDirectedSuperSend := true.
  	FirstSpecialSelector := 96.
  	NumSpecialSelectors := 32.
  	self flag:
  'Special selector send class must be inlined to agree with the interpreter, which
   inlines class.  If class is sent to e.g. a general instance of ProtoObject then unless
   class is inlined there will be an MNU.  It must be that the Cointerpreter and Cogit
   have identical semantics.  We get away with not hardwiring the other special
   selectors either because in the Cointerpreter they are not inlined or because they
   are inlined only to instances of classes for which there will always be a method.'.
  	self generatorTableFrom: #(
  		"1 byte bytecodes"
  		"pushes"
  		(1    0   15 genPushReceiverVariableBytecode isInstVarRef		needsFrameNever: 1)
  		(1  16   31 genPushLitVarDirSup16CasesBytecode				needsFrameNever: 1)
  		(1  32   63 genPushLiteralConstantBytecode					needsFrameNever: 1)
  		(1  64   75 genPushTemporaryVariableBytecode				needsFrameIfMod16GENumArgs: 1)
  		(1  76   76 genPushReceiverBytecode							needsFrameNever: 1)
  		(1  77   77 genPushConstantTrueBytecode						needsFrameNever: 1)
  		(1  78   78 genPushConstantFalseBytecode					needsFrameNever: 1)
  		(1  79   79 genPushConstantNilBytecode						needsFrameNever: 1)
  		(1  80   80 genPushConstantZeroBytecode						needsFrameNever: 1)
  		(1  81   81 genPushConstantOneBytecode						needsFrameNever: 1)
  		(1  82   82 genExtPushPseudoVariable)
  		(1  83   83 duplicateTopBytecode								needsFrameNever: 1)
  
  		(1  84   87 unknownBytecode)
  
  		"returns"
  		(1  88   88 genReturnReceiver				return needsFrameIfInBlock: isMappedInBlock 0)
  		(1  89   89 genReturnTrue					return needsFrameIfInBlock: isMappedInBlock 0)
  		(1  90   90 genReturnFalse					return needsFrameIfInBlock: isMappedInBlock 0)
  		(1  91   91 genReturnNil					return needsFrameIfInBlock: isMappedInBlock 0)
  		(1  92   92 genReturnTopFromMethod		return needsFrameIfInBlock: isMappedInBlock -1)
  		(1  93   93 genReturnNilFromBlock			return needsFrameNever: -1)
  		(1  94   94 genReturnTopFromBlock		return needsFrameNever: -1)
  		(1  95   95 genExtNopBytecode			needsFrameNever: 0)
  
  		"sends"
  		(1  96   96 genSpecialSelectorArithmetic isMapped AddRR)
  		(1  97   97 genSpecialSelectorArithmetic isMapped SubRR)
  		(1  98   98 genSpecialSelectorComparison isMapped JumpLess)
  		(1  99   99 genSpecialSelectorComparison isMapped JumpGreater)
  		(1 100 100 genSpecialSelectorComparison isMapped JumpLessOrEqual)
  		(1 101 101 genSpecialSelectorComparison isMapped JumpGreaterOrEqual)
  		(1 102 102 genSpecialSelectorComparison isMapped JumpZero)
  		(1 103 103 genSpecialSelectorComparison isMapped JumpNonZero)
  		(1 104 109 genSpecialSelectorSend isMapped)	 " #* #/ #\\ #@ #bitShift: //"
  		(1 110 110 genSpecialSelectorArithmetic isMapped AndRR)
  		(1 111 111 genSpecialSelectorArithmetic isMapped OrRR)
  		(1 112 117 genSpecialSelectorSend isMapped) "#at: #at:put: #size #next #nextPut: #atEnd"
  		(1 118 118 genSpecialSelectorEqualsEquals needsFrameNever: notMapped -1) "not mapped because it is directly inlined (for now)"
  		(1 119 119 genSpecialSelectorClass needsFrameIfStackGreaterThanOne: notMapped 0) "not mapped because it is directly inlined (for now)"
  		(1 120 127 genSpecialSelectorSend isMapped) "#blockCopy: #value #value: #do: #new #new: #x #y"
  
  		(1 128 143 genSendLiteralSelector0ArgsBytecode isMapped)
  		(1 144 159 genSendLiteralSelector1ArgBytecode isMapped)
  		(1 160 175 genSendLiteralSelector2ArgsBytecode isMapped)
  
  		"jumps"
  		(1 176 183 genShortUnconditionalJump	branch v3:ShortForward:Branch:Distance:)
  		(1 184 191 genShortJumpIfTrue			branch isBranchTrue isMapped "because of mustBeBoolean"
  													v3:ShortForward:Branch:Distance:)
  		(1 192 199 genShortJumpIfFalse			branch isBranchFalse isMapped "because of mustBeBoolean"
  													v3:ShortForward:Branch:Distance:)
+ 		(1 200 207 genStoreAndPopReceiverVariableBytecode isInstVarRef isInstVarStore isMappedIfImmutability needsFrameIfImmutability: -1)
- 		(1 200 207 genStoreAndPopReceiverVariableBytecode isInstVarRef isMappedIfImmutability needsFrameIfImmutability: -1)
  		
  		(1 208 215 genStoreAndPopTemporaryVariableBytecode)
  
  		(1 216 216 genPopStackBytecode needsFrameNever: -1)
  
  		(1 217 217 genUnconditionalTrapBytecode isMapped)
  
  		(1 218 223 unknownBytecode)
  
  		"2 byte bytecodes"
  		(2 224 224 extABytecode extension)
  		(2 225 225 extBBytecode extension)
  
  		"pushes"
  		(2 226 226 genExtPushReceiverVariableBytecode isInstVarRef)		"Needs a frame for context inst var access"
  		(2 227 227 genExtPushLitVarDirSupBytecode			needsFrameNever: 1)
  		(2 228 228 genExtPushLiteralBytecode					needsFrameNever: 1)
  		(2 229 229 genLongPushTemporaryVariableBytecode)
  		(2 230 230 genPushClosureTempsBytecode)
  		(2 231 231 genPushNewArrayBytecode)
  		(2 232 232 genExtPushIntegerBytecode				needsFrameNever: 1)
  		(2 233 233 genExtPushCharacterBytecode				needsFrameNever: 1)
  
  		"returns"
  		"sends"
  		(2 234 234 genExtSendBytecode isMapped)
  		(2 235 235 genExtSendSuperBytecode isMapped)
  
  		"sista bytecodes"
  		(2 236 236 unknownBytecode)
  
  		"jumps"
  		(2 237 237 genExtUnconditionalJump	branch isMapped "because of interrupt check" v4:Long:Branch:Distance:)
  		(2 238 238 genExtJumpIfTrue			branch isBranchTrue isMapped "because of mustBeBoolean" v4:Long:Branch:Distance:)
  		(2 239 239 genExtJumpIfFalse			branch isBranchFalse isMapped "because of mustBeBoolean" v4:Long:Branch:Distance:)
  
  		"stores"
+ 		(2 240 240 genSistaExtStoreAndPopReceiverVariableBytecode isInstVarRef isInstVarStore isMappedIfImmutability)
- 		(2 240 240 genSistaExtStoreAndPopReceiverVariableBytecode isInstVarRef isMappedIfImmutability)
  		(2 241 241 genSistaExtStoreAndPopLiteralVariableBytecode isMappedIfImmutability)
  		(2 242 242 genLongStoreAndPopTemporaryVariableBytecode)
+ 		(2 243 243 genSistaExtStoreReceiverVariableBytecode isInstVarRef isInstVarStore isMappedIfImmutability)
- 		(2 243 243 genSistaExtStoreReceiverVariableBytecode isInstVarRef isMappedIfImmutability)
  		(2 244 244 genSistaExtStoreLiteralVariableBytecode isMappedIfImmutability)
  		(2 245 245 genLongStoreTemporaryVariableBytecode)
  
  		(2 246 247	unknownBytecode)
  
  		"3 byte bytecodes"
  		(3 248 248 genCallPrimitiveBytecode)
  		(3 249 249 unknownBytecode) "reserved for Push Float"
  		(3 250 250 genExtPushClosureBytecode block v4:Block:Code:Size:)
  		(3 251 251 genExtPushRemoteTempOrInstVarLongBytecode)
  		(3 252 252 genExtStoreRemoteTempOrInstVarLongBytecode isMappedIfImmutability)
  		(3 253 253 genExtStoreAndPopRemoteTempOrInstVarLongBytecode isMappedIfImmutability)
  
  		(3 254 254	genExtJumpIfNotInstanceOfBehaviorsOrPopBytecode branch v4:Long:BranchIfNotInstanceOf:Distance:)
  		
  		(3 255 255	genExtPushFullClosureBytecode))!

Item was changed:
  ----- Method: StackToRegisterMappingCogit class>>initializeBytecodeTableForSqueakV3PlusClosures (in category 'class initialization') -----
  initializeBytecodeTableForSqueakV3PlusClosures
  	"StackToRegisterMappingCogit initializeBytecodeTableForSqueakV3PlusClosures"
  
  	numPushNilsFunction := #v3:Num:Push:Nils:.
  	pushNilSizeFunction := #v3PushNilSize:numInitialNils:.
  	FirstSpecialSelector := 176.
  	NumSpecialSelectors := 32.
  	self flag:
  'Special selector send class must be inlined to agree with the interpreter, which
   inlines class.  If class is sent to e.g. a general instance of ProtoObject then unless
   class is inlined there will be an MNU.  It must be that the Cointerpreter and Cogit
   have identical semantics.  We get away with not hardwiring the other special
   selectors either because in the Cointerpreter they are not inlined or because they
   are inlined only to instances of classes for which there will always be a method.'.
  	self generatorTableFrom: #(
  		(1    0   15 genPushReceiverVariableBytecode isInstVarRef needsFrameNever: 1)
  		(1  16   31 genPushTemporaryVariableBytecode needsFrameIfMod16GENumArgs: 1)
  		(1  32   63 genPushLiteralConstantBytecode needsFrameNever: 1)
  		(1  64   95 genPushLiteralVariableBytecode needsFrameNever: 1)
+ 		(1  96 103 genStoreAndPopReceiverVariableBytecode isInstVarRef isInstVarStore isMappedIfImmutability needsFrameIfImmutability: -1)
- 		(1  96 103 genStoreAndPopReceiverVariableBytecode isInstVarRef isMappedIfImmutability needsFrameIfImmutability: -1)
  		(1 104 111 genStoreAndPopTemporaryVariableBytecode)
  		(1 112 112 genPushReceiverBytecode needsFrameNever: 1)
  		(1 113 113 genPushConstantTrueBytecode needsFrameNever: 1)
  		(1 114 114 genPushConstantFalseBytecode needsFrameNever: 1)
  		(1 115 115 genPushConstantNilBytecode needsFrameNever: 1)
  		(1 116 119 genPushQuickIntegerConstantBytecode needsFrameNever: 1)
  		"method returns in blocks need a frame because of nonlocalReturn:through:"
  		(1 120 120 genReturnReceiver				return needsFrameIfInBlock: isMappedInBlock 0)
  		(1 121 121 genReturnTrue					return needsFrameIfInBlock: isMappedInBlock 0)
  		(1 122 122 genReturnFalse					return needsFrameIfInBlock: isMappedInBlock 0)
  		(1 123 123 genReturnNil					return needsFrameIfInBlock: isMappedInBlock 0)
  		(1 124 124 genReturnTopFromMethod		return needsFrameIfInBlock: isMappedInBlock -1)
  		(1 125 125 genReturnTopFromBlock		return needsFrameNever: -1)
  
  		(1 126 127 unknownBytecode)
  
  		(2 128 128 extendedPushBytecode isInstVarRef) "well, maybe inst var ref"
  		(2 129 129 extendedStoreBytecode isInstVarRef isMappedIfImmutability) "well, maybe inst var ref"
  		(2 130 130 extendedStoreAndPopBytecode isInstVarRef isMappedIfImmutability) "well, maybe inst var ref"
  		(2 131 131 genExtendedSendBytecode isMapped)
  		(3 132 132 doubleExtendedDoAnythingBytecode isMapped) "well, maybe inst var ref"
  		(2 133 133 genExtendedSuperBytecode isInstVarRef isMapped)
  		(2 134 134 genSecondExtendedSendBytecode isMapped)
  		(1 135 135 genPopStackBytecode needsFrameNever: -1)
  		(1 136 136 duplicateTopBytecode needsFrameNever: 1)
  
  		(1 137 137 genPushActiveContextBytecode)
  		(2 138 138 genPushNewArrayBytecode)),
  
  		((initializationOptions at: #SpurObjectMemory ifAbsent: [false])
  			ifTrue: [#((3 139 139 genCallPrimitiveBytecode))]
  			ifFalse: [#((1 139 139 unknownBytecode))]),
  
  	   #(
  		(3 140 140 genPushRemoteTempLongBytecode)
  		(3 141 141 genStoreRemoteTempLongBytecode)
  		(3 142 142 genStoreAndPopRemoteTempLongBytecode)
  		(4 143 143 genPushClosureCopyCopiedValuesBytecode block v3:Block:Code:Size:)
  
  		(1 144 151 genShortUnconditionalJump			branch v3:ShortForward:Branch:Distance:)
  		(1 152 159 genShortJumpIfFalse					branch isBranchFalse isMapped "because of mustBeBoolean"
  															v3:ShortForward:Branch:Distance:)
  		(2 160 163 genLongUnconditionalBackwardJump	branch isMapped "because of interrupt check"
  															v3:Long:Branch:Distance:)
  		(2 164 167 genLongUnconditionalForwardJump		branch v3:Long:Branch:Distance:)
  		(2 168 171 genLongJumpIfTrue					branch isBranchTrue isMapped "because of mustBeBoolean"
  															v3:LongForward:Branch:Distance:)
  		(2 172 175 genLongJumpIfFalse					branch isBranchFalse isMapped "because of mustBeBoolean"
  															v3:LongForward:Branch:Distance:)
  
  		(1 176 176 genSpecialSelectorArithmetic isMapped AddRR)
  		(1 177 177 genSpecialSelectorArithmetic isMapped SubRR)
  		(1 178 178 genSpecialSelectorComparison isMapped JumpLess)
  		(1 179 179 genSpecialSelectorComparison isMapped JumpGreater)
  		(1 180 180 genSpecialSelectorComparison isMapped JumpLessOrEqual)
  		(1 181 181 genSpecialSelectorComparison isMapped JumpGreaterOrEqual)
  		(1 182 182 genSpecialSelectorComparison isMapped JumpZero)
  		(1 183 183 genSpecialSelectorComparison isMapped JumpNonZero)
  		(1 184 189 genSpecialSelectorSend isMapped)	 " #* #/ #\\ #@ #bitShift: //"
  		(1 190 190 genSpecialSelectorArithmetic isMapped AndRR)
  		(1 191 191 genSpecialSelectorArithmetic isMapped OrRR)
  		(1 192 197 genSpecialSelectorSend isMapped) "#at: #at:put: #size #next #nextPut: #atEnd"
  		(1 198 198 genSpecialSelectorEqualsEquals needsFrameNever: notMapped -1) "not mapped because it is directly inlined (for now)"
  		(1 199 199 genSpecialSelectorClass needsFrameIfStackGreaterThanOne: notMapped 0) "not mapped because it is directly inlined (for now)"
  		(1 200 207 genSpecialSelectorSend isMapped) "#blockCopy: #value #value: #do: #new #new: #x #y"
  		(1 208 223 genSendLiteralSelector0ArgsBytecode isMapped)
  		(1 224 239 genSendLiteralSelector1ArgBytecode isMapped)
  		(1 240 255 genSendLiteralSelector2ArgsBytecode isMapped))!

Item was changed:
  ----- Method: StackToRegisterMappingCogit>>compileFrameBuild (in category 'compile abstract instructions') -----
  compileFrameBuild
  	"Build a frame for a CogMethod activation.  See CoInterpreter class>>initializeFrameIndices.
  	 Override to push the register receiver and register arguments, if any."
  	self cppIf: IMMUTABILITY ifTrue: 
+ 		[useTwoPaths ifTrue: 
- 		[needsTwoPath ifTrue: 
  			[self compileTwoPathFrameBuild.
  		 	^self]].
  	needsFrame ifFalse:
+ 		[useTwoPaths ifTrue: 
+ 			[self compileTwoPathFramelessInit].
+ 		 self initSimStackForFramelessMethod: initialPC.
- 		[self initSimStackForFramelessMethod: initialPC.
  		 ^self].
  	self genPushRegisterArgs.
  	super compileFrameBuild.
  	self initSimStackForFramefulMethod: initialPC!

Item was changed:
  ----- Method: StackToRegisterMappingCogit>>compileTwoPathFrameBuild (in category 'compile abstract instructions') -----
  compileTwoPathFrameBuild
- 	<option: #IMMUTABILITY>
  	"We are in a method where the frame is needed *only* for instance variable store, typically a setter method.
  	This case has 20% overhead with Immutability compared to setter without immutability because of the stack
  	frame creation. We compile two path, one where the object is immutable, one where it isn't. At the beginning 
  	of the frame build, we take one path or the other depending on the receiver mutability.
  	
  	Note: this specific case happens only where there are only instance variabel stores. We could do something
  	similar for literal variable stores, but we don't as it's too uncommon."
+ 	<option: #IMMUTABILITY>
+ 	| jumpImmutable |
- 	|jumpImmutable|
  	self assert: needsFrame.
+ 	self assert: useTwoPaths.
- 	self assert: IMMUTABILITY.
- 	self assert: needsTwoPath.
  	self assert: blockCount = 0.
  	jumpImmutable := objectRepresentation genJumpImmutable: ReceiverResultReg scratchReg: TempReg.
  	"first path. The receiver is mutable"
+ 	needsFrame := false.
  	self initSimStackForFramelessMethod: initialPC.
  	self compileMethodBody.
  	"second path. The receiver is mutable"
+ 	useTwoPaths := false. "reset because it impacts inst var store compilation"
+ 	needsFrame := true.
- 	needsTwoPath := false. "reset because it impact inst var store compilation"
  	jumpImmutable jmpTarget: self Label.
  	self genPushRegisterArgs.
  	super compileFrameBuild.
  	self initSimStackForFramefulMethod: initialPC!

Item was added:
+ ----- Method: StackToRegisterMappingCogit>>compileTwoPathFramelessInit (in category 'compile abstract instructions') -----
+ compileTwoPathFramelessInit
+ 	"We are in a frameless method with at least two inst var stores. We compile two paths,
+ 	 one where the object is in new space, and one where it isn't. At the beginning 
+ 	 of the method, we take one path or the other depending on the receiver being in newSpace."
+ 	| jumpOld |
+ 	self deny: IMMUTABILITY.
+ 	self deny: needsFrame.
+ 	self assert: useTwoPaths.
+ 	jumpOld := objectRepresentation genJumpInOldSpace: ReceiverResultReg.
+ 	"first path. The receiver is young"
+ 	self initSimStackForFramelessMethod: initialPC.
+ 	self compileMethodBody.
+ 	"second path. The receiver is old"
+ 	useTwoPaths := false. "reset because it impacts inst var store compilation"
+ 	jumpOld jmpTarget: self Label!

Item was changed:
  ----- Method: StackToRegisterMappingCogit>>genStorePop:slotIndex:destReg:needsStoreCheck:needsRestoreRcvr: (in category 'bytecode generator support') -----
  genStorePop: popBoolean slotIndex: slotIndex destReg: destReg needsStoreCheck: needsStoreCheck needsRestoreRcvr: needsRestoreReceiver
  	<inline: true>
  	"This method expects destReg to hold the object to store into. In practice, it is almost always RcvrResultReg because it is mandatory for the various store checks. We could put any register there if no store check is needed"
  	self 
  		cppIf: IMMUTABILITY
  		ifTrue: 
+ 			[useTwoPaths
- 			[needsTwoPath
  				ifTrue: 
  					[self  "first path, receiver is mutable"
  						genVanillaStorePop: popBoolean 
  						slotIndex: slotIndex 
  						destReg: destReg 
  						needsStoreCheck: needsStoreCheck]
  				ifFalse: 
  					[self 
  						genImmCheckStorePop: popBoolean 
  						slotIndex: slotIndex 
  						destReg: destReg 
  						needsStoreCheck: needsStoreCheck
  						needsRestoreRcvr: needsRestoreReceiver]]
  		ifFalse: 
  			[self 
  				genVanillaStorePop: popBoolean 
  				slotIndex: slotIndex 
  				destReg: destReg 
  				needsStoreCheck: needsStoreCheck].
  		!

Item was changed:
  ----- Method: StackToRegisterMappingCogit>>genUpArrowReturn (in category 'bytecode generators') -----
  genUpArrowReturn
  	"Generate a method return from within a method or a block.
  	 Frameless method activation looks like
  	 CISCs (x86):
  				receiver
  				args
  		sp->	ret pc.
  	 RISCs (ARM):
  				receiver
  				args
  				ret pc in LR.
  	 A fully framed activation is described in CoInterpreter class>initializeFrameIndices.
  	 Return pops receiver and arguments off the stack.  Callee pushes the result."
  	| framelessReturn |
  	deadCode := true. "can't fall through"
  	inBlock ifTrue:
  		[self assert: needsFrame. 
  		 self CallRT: ceNonLocalReturnTrampoline.
  		 self annotateBytecode: self Label.
  		 ^0].
  	self 
  		cppIf: IMMUTABILITY
+ 		ifTrue: [framelessReturn := needsFrame and: [useTwoPaths not]]
- 		ifTrue: [framelessReturn := needsFrame and: [needsTwoPath not]]
  		ifFalse: [framelessReturn := needsFrame].
  	framelessReturn
  		ifTrue:
  			[self MoveR: FPReg R: SPReg.
  			 self PopR: FPReg.
  			 backEnd hasLinkRegister ifTrue:
  				[self PopR: LinkReg].
  			 self RetN: methodOrBlockNumArgs + 1 * objectMemory wordSize]
  		ifFalse:
  			[self RetN: ((methodOrBlockNumArgs > self numRegArgs
  						"A method with an interpreter prim will push its register args for the prim.  If the failure
  						 body is frameless the args must still be popped, see e.g. Behavior>>nextInstance."
  						or: [regArgsHaveBeenPushed])
  							ifTrue: [methodOrBlockNumArgs + 1 * objectMemory wordSize]
  							ifFalse: [0])].
  	^0!

Item was changed:
  ----- Method: StackToRegisterMappingCogit>>genVanillaStorePop:slotIndex:destReg:needsStoreCheck: (in category 'bytecode generator support') -----
  genVanillaStorePop: popBoolean slotIndex: slotIndex destReg: destReg needsStoreCheck: needsStoreCheck
  	<inline: true>
  	| topReg |
+ 
+ 	self cppIf: IMMUTABILITY
+ 		ifTrue: []
+ 		ifFalse: "First path, receiver is in newSpace"
+ 			[(destReg = ReceiverResultReg and: [needsFrame not and: [useTwoPaths]]) ifTrue:
+ 				[topReg := self ssStorePop: popBoolean toPreferredReg: TempReg.
+ 				 self MoveR: topReg
+ 					Mw: slotIndex * objectMemory wordSize + objectMemory baseHeaderSize
+ 					r: ReceiverResultReg.
+ 				 traceStores > 0 ifTrue:
+ 					[topReg ~= TempReg ifTrue:
+ 						[self MoveR: topReg R: TempReg].
+ 					 self CallRT: ceTraceStoreTrampoline].
+ 				 ^0]].
+ 
  	topReg := self 
  		allocateRegForStackEntryAt: 0 
  		notConflictingWith: (self registerMaskFor: destReg). 
  	self ssStorePop: popBoolean toReg: topReg.
  	objectRepresentation
  		genStoreSourceReg: topReg
  		slotIndex: slotIndex
  		destReg: destReg
  		scratchReg: TempReg
  		inFrame: needsFrame
+ 		needsStoreCheck: needsStoreCheck!
- 		needsStoreCheck: needsStoreCheck.!

Item was added:
+ ----- Method: StackToRegisterMappingCogit>>maybeCountCounter (in category 'compile abstract instructions') -----
+ maybeCountCounter
+ 	"This is a hook for SistaCogit"
+ 	<inline: true>!

Item was added:
+ ----- Method: StackToRegisterMappingCogit>>maybeCountFixup (in category 'compile abstract instructions') -----
+ maybeCountFixup
+ 	"This is a hook for RegisterAllocatingCogit"
+ 	<inline: true>!

Item was added:
+ ----- Method: StackToRegisterMappingCogit>>maybeInitNumCounters (in category 'compile abstract instructions') -----
+ maybeInitNumCounters
+ 	"This is a hook for SistaCogit"
+ 	<inline: true>!

Item was added:
+ ----- Method: StackToRegisterMappingCogit>>maybeInitNumFixups (in category 'compile abstract instructions') -----
+ maybeInitNumFixups
+ 	"This is a hook for RegisterAllocatingCogit"
+ 	<inline: true>!

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 seenInstVarStore |
- 	| latestContinuation nExts descriptor pc numBlocks distance targetPC framelessStackDelta |
  	<var: #descriptor type: #'BytecodeDescriptor *'>
+ 	needsFrame := useTwoPaths := seenInstVarStore := false.
+ 	self maybeInitNumFixups.
+ 	self maybeInitNumCounters.
- 	needsFrame := false.
  	prevBCDescriptor := nil.
- 	self cppIf: IMMUTABILITY ifTrue: [ needsTwoPath := false ].
  	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.
+ 						 self cppIf: IMMUTABILITY
+ 							ifTrue: [useTwoPaths := descriptor isInstVarStore]]
+ 					ifFalse:
+ 						[framelessStackDelta := framelessStackDelta + descriptor stackDelta.
+ 						 self cppIf: IMMUTABILITY
+ 							ifTrue: []
+ 							ifFalse:
+ 								[descriptor isInstVarStore ifTrue:
+ 									[seenInstVarStore
+ 										ifTrue: [useTwoPaths := true]
+ 										ifFalse: [seenInstVarStore := true]]]]].
+ 
- 		self cppIf: IMMUTABILITY 
- 			ifTrue: 
- 				[(needsFrame and: [needsTwoPath not]) ifFalse:
- 					[(descriptor needsFrameFunction isNil
- 					  or: [self perform: descriptor needsFrameFunction with: framelessStackDelta])
- 						ifTrue: 
- 							[needsFrame := true.
- 							 needsTwoPath := descriptor generator == #genStoreAndPopReceiverVariableBytecode ]
- 						ifFalse: [framelessStackDelta := framelessStackDelta + descriptor stackDelta]]]
- 			ifFalse: 
- 				[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.
+ 					 self maybeCountFixup.
+ 					 self maybeCountCounter]].
- 				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 maybeCountFixup].
+ 
- 			 latestContinuation := latestContinuation max: targetPC].
  		 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!



More information about the Vm-dev mailing list