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

commits at source.squeak.org commits at source.squeak.org
Tue Oct 7 18:23:35 UTC 2014


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

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

Name: VMMaker.oscog-eem.894
Author: eem
Time: 7 October 2014, 11:20:33.469 am
UUID: 7417a203-5178-46d0-951c-b3dd1487a267
Ancestors: VMMaker.oscog-eem.893

Rename "explicit outer" foo to "enclosing object" foo

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

Item was added:
+ ----- Method: CoInterpreter>>ceEnclosingObjectAt: (in category 'stack bytecodes') -----
+ ceEnclosingObjectAt: level
+ 	<api>
+ 	<option: #NewspeakVM>
+ 	^self 
+ 		enclosingObjectAt: level
+ 		withObject: (self mframeReceiver: framePointer)
+ 		withMixin: self mMethodClass!

Item was removed:
- ----- Method: CoInterpreter>>ceExplicitReceiverAt: (in category 'stack bytecodes') -----
- ceExplicitReceiverAt: level
- 	<api>
- 	<option: #NewspeakVM>
- 	^self 
- 		explicitOuterReceiver: level
- 		withObject: (self mframeReceiver: framePointer)
- 		withMixin: self mMethodClass!

Item was changed:
  CogClass subclass: #Cogit
+ 	instanceVariableNames: 'coInterpreter objectMemory objectRepresentation processor threadManager methodZone methodZoneBase codeBase minValidCallAddress lastNInstructions simulatedAddresses simulatedTrampolines simulatedVariableGetters simulatedVariableSetters printRegisters printInstructions compilationTrace clickConfirm breakPC breakBlock singleStep guardPageSize traceFlags traceStores breakMethod methodObj initialPC endPC methodOrBlockNumArgs inBlock needsFrame hasYoungReferent primitiveIndex backEnd callerSavedRegMask postCompileHook primInvokeLabel methodLabel stackCheckLabel blockEntryLabel blockEntryNoContextSwitch blockNoContextSwitchOffset stackOverflowCall sendMiss sendMissCall missOffset entryPointMask checkedEntryAlignment uncheckedEntryAlignment cmEntryOffset entry cmNoCheckEntryOffset noCheckEntry dynSuperEntry dynSuperEntryAlignment cmDynSuperEntryOffset mnuCall interpretCall interpretLabel endCPICCase0 endCPICCase1 numPICCases firstCPICCaseOffset cPICCaseSize cPICEndSize closedPICSize openPICSize fixups abstractOpcodes annotations generatorTable primitiveGeneratorTable byte0 byte1 byte2 byte3 bytecodePC bytecodeSetOffset opcodeIndex numAbstractOpcodes annotationIndex blockStarts blockCount labelCounter cStackAlignment expectedSPAlignment expectedFPAlignment codeModified maxLitIndex ceMethodAbortTrampoline cePICAbortTrampoline ceCheckForInterruptTrampoline ceCPICMissTrampoline ceReturnToInterpreterTrampoline ceBaseFrameReturnTrampoline ceSendMustBeBooleanAddTrueTrampoline ceSendMustBeBooleanAddFalseTrampoline ceCannotResumeTrampoline ceEnterCogCodePopReceiverReg ceCallCogCodePopReceiverReg ceCallCogCodePopReceiverAndClassRegs cePrimReturnEnterCogCode cePrimReturnEnterCogCodeProfiling ceNonLocalReturnTrampoline ceFetchContextInstVarTrampoline ceStoreContextInstVarTrampoline ceImplicitReceiverTrampoline ceEnclosingObjectTrampoline ceCaptureCStackPointers ceFlushICache ceCheckFeaturesFunction ceTraceLinkedSendTrampoline ceTraceBlockActivationTrampoline ceTraceStoreTrampoline ceGetSP sendTrampolines superSendTrampolines dynamicSuperSendTrampolines firstSend lastSend realCEEnterCogCodePopReceiverReg realCECallCogCodePopReceiverReg realCECallCogCodePopReceiverAndClassRegs trampolineTableIndex trampolineAddresses objectReferencesInRuntime runtimeObjectRefIndex cFramePointerInUse debugPrimCallStackOffset ceTryLockVMOwner ceUnlockVMOwner cogMethodSurrogateClass cogBlockMethodSurrogateClass extA extB numIRCs indexOfIRC theIRCs'
- 	instanceVariableNames: 'coInterpreter objectMemory objectRepresentation processor threadManager methodZone methodZoneBase codeBase minValidCallAddress lastNInstructions simulatedAddresses simulatedTrampolines simulatedVariableGetters simulatedVariableSetters printRegisters printInstructions compilationTrace clickConfirm breakPC breakBlock singleStep guardPageSize traceFlags traceStores breakMethod methodObj initialPC endPC methodOrBlockNumArgs inBlock needsFrame hasYoungReferent primitiveIndex backEnd callerSavedRegMask postCompileHook primInvokeLabel methodLabel stackCheckLabel blockEntryLabel blockEntryNoContextSwitch blockNoContextSwitchOffset stackOverflowCall sendMiss sendMissCall missOffset entryPointMask checkedEntryAlignment uncheckedEntryAlignment cmEntryOffset entry cmNoCheckEntryOffset noCheckEntry dynSuperEntry dynSuperEntryAlignment cmDynSuperEntryOffset mnuCall interpretCall interpretLabel endCPICCase0 endCPICCase1 numPICCases firstCPICCaseOffset cPICCaseSize cPICEndSize closedPICSize openPICSize fixups abstractOpcodes annotations generatorTable primitiveGeneratorTable byte0 byte1 byte2 byte3 bytecodePC bytecodeSetOffset opcodeIndex numAbstractOpcodes annotationIndex blockStarts blockCount labelCounter cStackAlignment expectedSPAlignment expectedFPAlignment codeModified maxLitIndex ceMethodAbortTrampoline cePICAbortTrampoline ceCheckForInterruptTrampoline ceCPICMissTrampoline ceReturnToInterpreterTrampoline ceBaseFrameReturnTrampoline ceSendMustBeBooleanAddTrueTrampoline ceSendMustBeBooleanAddFalseTrampoline ceCannotResumeTrampoline ceEnterCogCodePopReceiverReg ceCallCogCodePopReceiverReg ceCallCogCodePopReceiverAndClassRegs cePrimReturnEnterCogCode cePrimReturnEnterCogCodeProfiling ceNonLocalReturnTrampoline ceFetchContextInstVarTrampoline ceStoreContextInstVarTrampoline ceImplicitReceiverTrampoline ceExplicitReceiverTrampoline ceCaptureCStackPointers ceFlushICache ceCheckFeaturesFunction ceTraceLinkedSendTrampoline ceTraceBlockActivationTrampoline ceTraceStoreTrampoline ceGetSP sendTrampolines superSendTrampolines dynamicSuperSendTrampolines firstSend lastSend realCEEnterCogCodePopReceiverReg realCECallCogCodePopReceiverReg realCECallCogCodePopReceiverAndClassRegs trampolineTableIndex trampolineAddresses objectReferencesInRuntime runtimeObjectRefIndex cFramePointerInUse debugPrimCallStackOffset ceTryLockVMOwner ceUnlockVMOwner cogMethodSurrogateClass cogBlockMethodSurrogateClass extA extB numIRCs indexOfIRC theIRCs'
  	classVariableNames: 'AltBlockCreationBytecodeSize AltFirstSpecialSelector AltNSSendIsPCAnnotated AnnotationConstantNames AnnotationShift BlockCreationBytecodeSize Debug DisplacementMask DisplacementX2N EagerInstructionDecoration EncounteredUnknownBytecode FirstAnnotation FirstSpecialSelector HasBytecodePC InsufficientCodeSpace IsAbsPCReference IsDisplacement IsDisplacementX2N IsNSSendCall IsObjectReference IsRelativeCall IsSendCall MapEnd MaxCompiledPrimitiveIndex MaxNegativeErrorCode MaxStackAllocSize MaxUnitDisplacement MaxX2NDisplacement MethodTooBig NSSendIsPCAnnotated NotFullyInitialized NumObjRefsInRuntime NumOopsPerIRC NumSendTrampolines NumTrampolines ProcessorClass ShouldNotJIT UnimplementedPrimitive YoungSelectorInPIC'
  	poolDictionaries: 'CogCompilationConstants CogMethodConstants CogRTLOpcodes VMBasicConstants VMObjectIndices VMStackFrameOffsets'
  	category: 'VMMaker-JIT'!
  Cogit class
  	instanceVariableNames: 'generatorTable primitiveTable'!
  
  !Cogit commentStamp: 'eem 2/13/2013 15:37' prior: 0!
  I am the code generator for the Cog VM.  My job is to produce machine code versions of methods for faster execution and to manage inline caches for faster send performance.  I can be tested in the current image using my class-side in-image compilation facilities.  e.g. try
  
  	StackToRegisterMappingCogit genAndDis: (Integer >> #benchFib)
  
  I have concrete subclasses that implement different levels of optimization:
  	SimpleStackBasedCogit is the simplest code generator.
  
  	StackToRegisterMappingCogit is the current production code generator  It defers pushing operands
  	to the stack until necessary and implements a register-based calling convention for low-arity sends.
  
  	StackToRegisterMappingCogit is an experimental code generator with support for counting
  	conditional branches, intended to support adaptive optimization.
  
  coInterpreter <CoInterpreterSimulator>
  	the VM's interpreter with which I cooperate
  methodZoneManager <CogMethodZoneManager>
  	the manager of the machine code zone
  objectRepresentation <CogObjectRepresentation>
  	the object used to generate object accesses
  processor <BochsIA32Alien|?>
  	the simulator that executes the IA32/x86 machine code I generate when simulating execution in Smalltalk
  simulatedTrampolines <Dictionary of Integer -> MessageSend>
  	the dictionary mapping trap jump addresses to run-time routines used to warp from simulated machine code in to the Smalltalk run-time.
  simulatedVariableGetters <Dictionary of Integer -> MessageSend>
  	the dictionary mapping trap read addresses to variables in run-time objects used to allow simulated machine code to read variables in the Smalltalk run-time.
  simulatedVariableSetters <Dictionary of Integer -> MessageSend>
  	the dictionary mapping trap write addresses to variables in run-time objects used to allow simulated machine code to write variables in the Smalltalk run-time.
  printRegisters printInstructions clickConfirm <Boolean>
  	flags controlling debug printing and code simulation
  breakPC <Integer>
  	machine code pc breakpoint
  cFramePointer cStackPointer <Integer>
  	the variables representing the C stack & frame pointers, which must change on FFI callback and return
  selectorOop <sqInt>
  	the oop of the methodObj being compiled
  methodObj <sqInt>
  	the bytecode method being compiled
  initialPC endPC <Integer>
  	the start and end pcs of the methodObj being compiled
  methodOrBlockNumArgs <Integer>
  	argument count of current method or block being compiled
  needsFrame <Boolean>
  	whether methodObj or block needs a frame to execute
  primitiveIndex <Integer>
  	primitive index of current method being compiled
  methodLabel <CogAbstractOpcode>
  	label for the method header
  blockEntryLabel <CogAbstractOpcode>
  	label for the start of the block dispatch code
  stackOverflowCall <CogAbstractOpcode>
  	label for the call of ceStackOverflow in the method prolog
  sendMissCall <CogAbstractOpcode>
  	label for the call of ceSICMiss in the method prolog
  entryOffset <Integer>
  	offset of method entry code from start (header) of method
  entry <CogAbstractOpcode>
  	label for the first instruction of the method entry code
  noCheckEntryOffset <Integer>
  	offset of the start of a method proper (after the method entry code) from start (header) of method
  noCheckEntry <CogAbstractOpcode>
  	label for the first instruction of start of a method proper
  fixups <Array of <AbstractOpcode Label | nil>>
  	the labels for forward jumps that will be fixed up when reaching the relevant bytecode.  fixup shas one element per byte in methodObj's bytecode
  abstractOpcodes <Array of <AbstractOpcode>>
  	the code generated when compiling methodObj
  byte0 byte1 byte2 byte3 <Integer>
  	individual bytes of current bytecode being compiled in methodObj
  bytecodePointer <Integer>
  	bytecode pc (same as Smalltalk) of the current bytecode being compiled
  opcodeIndex <Integer>
  	the index of the next free entry in abstractOpcodes (this code is translated into C where OrderedCollection et al do not exist)
  numAbstractOpcodes <Integer>
  	the number of elements in abstractOpcocdes
  blockStarts <Array of <BlockStart>>
  	the starts of blocks in the current method
  blockCount
  	the index into blockStarts as they are being noted, and hence eventuakly teh total number of blocks in the current method
  labelCounter <Integer>
  	a nicety for numbering labels not needed in the production system but probably not expensive enough to worry about
  ceStackOverflowTrampoline <Integer>
  ceSend0ArgsTrampoline <Integer>
  ceSend1ArgsTrampoline <Integer>
  ceSend2ArgsTrampoline <Integer>
  ceSendNArgsTrampoline <Integer>
  ceSendSuper0ArgsTrampoline <Integer>
  ceSendSuper1ArgsTrampoline <Integer>
  ceSendSuper2ArgsTrampoline <Integer>
  ceSendSuperNArgsTrampoline <Integer>
  ceSICMissTrampoline <Integer>
  ceCPICMissTrampoline <Integer>
  ceStoreCheckTrampoline <Integer>
  ceReturnToInterpreterTrampoline <Integer>
  ceBaseFrameReturnTrampoline <Integer>
  ceSendMustBeBooleanTrampoline <Integer>
  ceClosureCopyTrampoline <Integer>
  	the various trampolines (system-call-like jumps from machine code to the run-time).
  	See Cogit>>generateTrampolines for the mapping from trampoline to run-time
  	routine and then read the run-time routine for a funcitonal description.
  ceEnterCogCodePopReceiverReg <Integer>
  	the enilopmart (jump from run-time to machine-code)
  methodZoneBase <Integer>
  !
  Cogit class
  	instanceVariableNames: 'generatorTable primitiveTable'!

Item was changed:
  ----- Method: Cogit>>generateNewspeakRuntime (in category 'initialization') -----
  generateNewspeakRuntime
  	<option: #NewspeakVM>
  	| jumpMiss jumpItsTheReceiverStupid retpcReg |
  	<var: #jumpMiss type: #'AbstractInstruction *'>
  	<var: #jumpItsTheReceiverStupid type: #'AbstractInstruction *'>
  	"Generate the non-send runtime support for Newspeak, explicit outer and implicit receiver.
  	 The dynamic frequency of explicit outer is so low we merely call an interpreter routine."
+ 	ceEnclosingObjectTrampoline := self genTrampolineFor: #ceEnclosingObjectAt:
+ 										called: 'ceEnclosingObjectTrampoline'
- 	ceExplicitReceiverTrampoline := self genTrampolineFor: #ceExplicitReceiverAt:
- 										called: 'ceExplicitReceiverTrampoline'
  										arg: SendNumArgsReg
  										result: ReceiverResultReg.
  	"Cached push implicit receiver implementation.  If objectRepresentation doesn't support
  	 pinning then caller looks like
  				mov selector, SendNumArgsReg
  				call ceImplicitReceiver
  				br continue
  		Lclass:	.word
  		Lmixin::	.word
  		continue:
  	 If objectRepresentation supports pinning then caller looks like
  				mov Lclass, Arg1Reg
  				mov selector, SendNumArgsReg
  				call ceImplicitReceiver
  	 and Lclass: .word; Lmixin: .word is somewhere on the heap.
  
  	 If class tag matches class of receiver then mixin contains either 0 or the implicit receiver.
  	 If 0, answer the actual receiver, otherwise the mixin.
  	 Generate the class fetch and cache probe inline for speed.
  	 Smashes Arg1Reg, RegClass and caller-saved regs."
  	opcodeIndex := 0.
  	self MoveMw: FoxMFReceiver r: FPReg R: ReceiverResultReg.
  	objectRepresentation
  		genGetInlineCacheClassTagFrom: ReceiverResultReg
  		into: ClassReg
  		forEntry: false.
  	objectRepresentation canPinObjects
  		ifTrue:
  			[self MoveMw: 0 r: Arg1Reg R: TempReg.
  			 self CmpR: ClassReg R: TempReg.
  			 jumpMiss := self JumpNonZero: 0.
  			 self MoveMw: BytesPerOop r: Arg1Reg R: TempReg.
  			 self CmpCq: 0 R: TempReg.
  			 jumpItsTheReceiverStupid := self JumpZero: 0.
  			 self MoveR: TempReg R: ReceiverResultReg.
  			 jumpItsTheReceiverStupid jmpTarget: (self RetN: 0).
  			 jumpMiss jmpTarget: self Label.
  			 ceImplicitReceiverTrampoline := self
  												genTrampolineFor: #ceImplicitReceiverFor:receiver:cache:
  												called: 'ceImplicitReceiverTrampoline'
  												numArgs: 3
  												arg: SendNumArgsReg
  												arg: ReceiverResultReg
  												arg: Arg1Reg
  												arg: nil
  												saveRegs: false
  												pushLinkReg: true
  												resultReg: ReceiverResultReg
  												appendOpcodes: true]
  		ifFalse:
  			[backEnd hasLinkRegister
  				ifTrue: [retpcReg := LinkReg]
  				ifFalse: [self MoveMw: 0 r: SPReg R: (retpcReg := TempReg)].
  			 self MoveMw: 0 r: SPReg R: retpcReg.
  			 self MoveMw: backEnd jumpShortByteSize r: retpcReg R: Arg1Reg.
  			 self CmpR: ClassReg R: Arg1Reg.
  			 jumpMiss := self JumpNonZero: 0.
  			 self MoveMw: backEnd jumpShortByteSize + BytesPerOop r: retpcReg R: ClassReg.
  			 self CmpCq: 0 R: ClassReg.
  			 jumpItsTheReceiverStupid := self JumpZero: 0.
  			 self MoveR: ClassReg R: ReceiverResultReg.
  			 jumpItsTheReceiverStupid jmpTarget: (self RetN: 0).
  			 jumpMiss jmpTarget: self Label.
  			 ceImplicitReceiverTrampoline := self
  												genTrampolineFor: #ceImplicitReceiverFor:receiver:
  												called: 'ceImplicitReceiverTrampoline'
  												numArgs: 2
  												arg: SendNumArgsReg
  												arg: ReceiverResultReg
  												arg: nil
  												arg: nil
  												saveRegs: false
  												pushLinkReg: true
  												resultReg: ReceiverResultReg
  												appendOpcodes: true]!

Item was changed:
  ----- Method: NewspeakInterpreter class>>initializeBytecodeTable (in category 'initialization') -----
  initializeBytecodeTable
  	"NewspeakInterpreter initializeBytecodeTable"
  	"Note: This table will be used to generate a C switch statement."
  
  	BytecodeTable := Array new: 256.
  	self table: BytecodeTable from:
  	#(
  		(  0  15 pushReceiverVariableBytecode)
  		( 16  31 pushTemporaryVariableBytecode)
  		( 32  63 pushLiteralConstantBytecode)
  		( 64  95 pushLiteralVariableBytecode)
  		( 96 103 storeAndPopReceiverVariableBytecode)
  		(104 111 storeAndPopTemporaryVariableBytecode)
  		(112 pushReceiverBytecode)
  		(113 pushConstantTrueBytecode)
  		(114 pushConstantFalseBytecode)
  		(115 pushConstantNilBytecode)
  		(116 pushConstantMinusOneBytecode)
  		(117 pushConstantZeroBytecode)
  		(118 pushConstantOneBytecode)
  		(119 pushConstantTwoBytecode)
  		(120 returnReceiver)
  		(121 returnTrue)
  		(122 returnFalse)
  		(123 returnNil)
  		(124 returnTopFromMethod)
  		(125 returnTopFromBlock)
  
  		"Newspeak bytecodes"
  		(126 dynamicSuperSendBytecode)
  		(127 pushImplicitReceiverBytecode)
  
  		(128 extendedPushBytecode)
  		(129 extendedStoreBytecode)
  		(130 extendedStoreAndPopBytecode)
  		(131 singleExtendedSendBytecode)
  		(132 doubleExtendedDoAnythingBytecode)
  		(133 singleExtendedSuperBytecode)
  		(134 secondExtendedSendBytecode)
  		(135 popStackBytecode)
  		(136 duplicateTopBytecode)
  		(137 pushActiveContextBytecode)
  
  		"Closure & Newspeak bytecodes"
  		(138 pushNewArrayBytecode)
+ 		(139 pushEnclosingObjectBytecode)
- 		(139 pushExplicitOuterReceiverBytecode)
  		(140 pushRemoteTempLongBytecode)
  		(141 storeRemoteTempLongBytecode)
  		(142 storeAndPopRemoteTempLongBytecode)
  		(143 pushClosureCopyCopiedValuesBytecode)
  
  		(144 151 shortUnconditionalJump)
  		(152 159 shortConditionalJump)
  		(160 167 longUnconditionalJump)
  		(168 171 longJumpIfTrue)
  		(172 175 longJumpIfFalse)
  
  		"176-191 were sendArithmeticSelectorBytecode"
  		(176 bytecodePrimAdd)
  		(177 bytecodePrimSubtract)
  		(178 bytecodePrimLessThan)
  		(179 bytecodePrimGreaterThan)
  		(180 bytecodePrimLessOrEqual)
  		(181 bytecodePrimGreaterOrEqual)
  		(182 bytecodePrimEqual)
  		(183 bytecodePrimNotEqual)
  		(184 bytecodePrimMultiply)
  		(185 bytecodePrimDivide)
  		(186 bytecodePrimMod)
  		(187 bytecodePrimMakePoint)
  		(188 bytecodePrimBitShift)
  		(189 bytecodePrimDiv)
  		(190 bytecodePrimBitAnd)
  		(191 bytecodePrimBitOr)	
  
  		"192-207 were sendCommonSelectorBytecode"
  		(192 bytecodePrimAt)
  		(193 bytecodePrimAtPut)
  		(194 bytecodePrimSize)
  		(195 bytecodePrimNext)
  		(196 bytecodePrimNextPut)
  		(197 bytecodePrimAtEnd)
  		(198 bytecodePrimEquivalent)
  		(199 bytecodePrimClass)
  		(200 bytecodePrimBlockCopy)
  		(201 bytecodePrimValue)
  		(202 bytecodePrimValueWithArg)
  		(203 bytecodePrimDo)
  		(204 bytecodePrimNew)
  		(205 bytecodePrimNewWithArg)
  		(206 bytecodePrimPointX)
  		(207 bytecodePrimPointY)
  
  		(208 223 sendLiteralSelector0ArgsBytecode)
  		(224 239 sendLiteralSelector1ArgBytecode)
  		(240 255 sendLiteralSelector2ArgsBytecode)
  	).!

Item was added:
+ ----- Method: NewspeakInterpreter>>enclosingObjectAt:withObject:withMixin: (in category 'stack bytecodes') -----
+ enclosingObjectAt: n withObject: anObject withMixin: mixin 
+ 	"This is used to implement the innards of the pushEnclosingObjectBytecode,
+ 	 used for explicit outer sends in NS2/NS3.  "
+ 	| enclosingObject mixinApplication targetMixin count |
+ 	
+ 	enclosingObject := anObject.
+ 	targetMixin := mixin.
+ 	count := 0.
+ 	[count < n] whileTrue:
+ 		[count := count + 1.
+ 		(targetMixin = nilObj or:[enclosingObject = nilObj]) ifTrue:
+ 			[^nilObj].
+ 		mixinApplication := self
+ 							findApplicationOfTargetMixin: targetMixin
+ 							startingAtNonMetaClass: (self fetchClassOf: enclosingObject).
+ 		mixinApplication == nilObj ifTrue:[^nilObj]. "should never happen!!"
+ 		enclosingObject := self fetchPointer: EnclosingObjectIndex 
+ 								ofObject: mixinApplication.	
+ 		targetMixin := self fetchPointer: EnclosingMixinIndex ofObject: targetMixin].
+ 	
+ 	^enclosingObject!

Item was removed:
- ----- Method: NewspeakInterpreter>>explicitOuterReceiver:withObject:withMixin: (in category 'stack bytecodes') -----
- explicitOuterReceiver: n withObject: anObject withMixin: mixin 
- 	"This is used to implement the innards of the pushExplicitOuterReceiverBytecode,
- 	 used for explicit outer sends in NS2/NS3.  "
- 	| explicitReceiver mixinApplication  targetMixin  count |
- 	
- 	explicitReceiver := anObject.
- 	targetMixin := mixin.
- 	count := 0.
- 	[count < n] whileTrue:[
- 		count := count + 1.
- 		(targetMixin == nilObj or:[explicitReceiver == nilObj]) ifTrue:
- 		[^nilObj].
- 		mixinApplication := self
- 							findApplicationOfTargetMixin: targetMixin
- 							startingAtNonMetaClass: (self fetchClassOf: explicitReceiver).
- 		mixinApplication == nilObj ifTrue:[^nilObj]. "should never happen!!"
- 		explicitReceiver := self fetchPointer: EnclosingObjectIndex 
- 								ofObject: mixinApplication.	
- 		targetMixin := self fetchPointer: EnclosingMixinIndex ofObject: targetMixin.	
- 	].
- 	
- 	^explicitReceiver!

Item was added:
+ ----- Method: NewspeakInterpreter>>pushEnclosingObjectBytecode (in category 'stack bytecodes') -----
+ pushEnclosingObjectBytecode
+ 	"Find the enclosing object at level N"
+ 	|  mClassMixin  litIndex  anInt |
+ 	<inline: true>
+ 	litIndex := self fetchByte.
+ 	anInt := self literal: litIndex.
+ 	self fetchNextBytecode.
+ 	mClassMixin := self methodClassOf: method.
+ 	self internalPush: (self 
+ 						enclosingObjectAt: (self integerValueOf: anInt) 
+ 						withObject: receiver 
+ 						withMixin: mClassMixin)
+ !

Item was removed:
- ----- Method: NewspeakInterpreter>>pushExplicitOuterReceiverBytecode (in category 'stack bytecodes') -----
- pushExplicitOuterReceiverBytecode
- 	"Find the appropriate implicit receiver for outer N"
- 	|  mClassMixin  litIndex  n anInt |
- 	<inline: true>
- 	litIndex := self fetchByte.
- 	anInt := self literal: litIndex.
- 	n := self checkedIntegerValueOf: anInt.
- 	self fetchNextBytecode.
- 	mClassMixin := self methodClassOf: method.
- 	self internalPush:(self 
- 		explicitOuterReceiver: n 
- 		withObject: receiver 
- 		withMixin: mClassMixin
- 		)
- !

Item was changed:
  ----- Method: SimpleStackBasedCogit class>>initializeBytecodeTableForNewspeakV3PlusClosures (in category 'class initialization') -----
  initializeBytecodeTableForNewspeakV3PlusClosures
  	"SimpleStackBasedCogit initializeBytecodeTableForNewspeakV3PlusClosures"
  
  	NSSendIsPCAnnotated := true. "IsNSSendCall used by PushImplicitReceiver"
  	FirstSpecialSelector := 176.
  	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)
  		(1  16   31 genPushTemporaryVariableBytecode)
  		(1  32   63 genPushLiteralConstantBytecode needsFrameNever: 1)
  		(1  64   95 genPushLiteralVariableBytecode needsFrameNever: 1)
  		(1  96 103 genStoreAndPopReceiverVariableBytecode needsFrameNever: -1) "N.B. not frameless if immutability"
  		(1 104 111 genStoreAndPopTemporaryVariableBytecode)
  		(1 112 112 genPushReceiverBytecode)
  		(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)
  
  		(3 126 126 genDynamicSuperSendBytecode isMapped)			"Newspeak"
  		(2 127 127 genPushImplicitReceiverBytecode isMapped hasIRC)	"Newspeak"
  
  		(2 128 128 extendedPushBytecode needsFrameNever: 1)
  		(2 129 129 extendedStoreBytecode)
  		(2 130 130 extendedStoreAndPopBytecode)
  		(2 131 131 genExtendedSendBytecode isMapped)
  		(3 132 132 doubleExtendedDoAnythingBytecode isMapped)
  		(2 133 133 genExtendedSuperBytecode 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 callPrimitiveBytecode))]									"V3PlusClosures on Spur"
+ 			ifFalse: [#((2 139 139 genPushEnclosingObjectBytecode isMapped))]),	"Newspeak"
- 			ifFalse: [#((2 139 139 genPushExplicitOuterReceiverBytecode isMapped))]),	"Newspeak"
  
  	  #(
  		(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 197 genSpecialSelectorSend isMapped)
  		(1 198 198 genSpecialSelectorEqualsEquals needsFrameNever: notMapped -1) "not mapped because it is directly inlined (for now)"
  		(1 199 199 genSpecialSelectorClass needsFrameNever: notMapped 0) "not mapped because it is directly inlined (for now)"
  		(1 200 207 genSpecialSelectorSend isMapped)
  		(1 208 223 genSendLiteralSelector0ArgsBytecode isMapped)
  		(1 224 239 genSendLiteralSelector1ArgBytecode isMapped)
  		(1 240 255 genSendLiteralSelector2ArgsBytecode isMapped))!

Item was changed:
  ----- Method: SimpleStackBasedCogit>>genExtPushPseudoVariableOrOuterBytecode (in category 'bytecode generators') -----
  genExtPushPseudoVariableOrOuterBytecode
+ 	"77			01001101		Push false [* 1:true, 2:nil, 3:thisContext, ..., -N: pushEnclosingObjectAt: N, N = Extend B]"
- 	"77			01001101		Push false [* 1:true, 2:nil, 3:thisContext, ..., -N: pushExplicitOuter: N, N = Extend B]"
  	| ext |
  	ext := extB.
  	extB := 0.
  	ext caseOf: {
  		[0]	->	[^self genPushLiteral: objectMemory falseObject].
  		[1]	->	[^self genPushLiteral: objectMemory trueObject].
  		[2]	->	[^self genPushLiteral: objectMemory nilObject].
  		[3]	->	[^self genPushActiveContextBytecode]
  		}
  		otherwise:
  			[ext < 0 ifTrue:
+ 				[^self genPushEnclosingObjectAt: 0 - ext].
- 				[^self genPushExplicitOuterReceiver: 0 - ext].
  			 self warning: 'undefined extension for extPushPseudoVariableOrOuter'.
  			 ^self unknownBytecode].
  	^0!

Item was added:
+ ----- Method: SimpleStackBasedCogit>>genPushEnclosingObjectAt: (in category 'bytecode generators') -----
+ genPushEnclosingObjectAt: level
+ 	"Uncached push enclosing object"
+ 	self MoveCq: level R: SendNumArgsReg.
+ 	self CallRT: ceEnclosingObjectTrampoline.
+ 	self PushR: ReceiverResultReg.
+ 	^0!

Item was added:
+ ----- Method: SimpleStackBasedCogit>>genPushEnclosingObjectBytecode (in category 'bytecode generators') -----
+ genPushEnclosingObjectBytecode
+ 	"Uncached push enclosing object"
+ 	| levelOop |
+ 	levelOop := self getLiteral: byte1.
+ 	self assert: (objectMemory isIntegerObject: levelOop).
+ 	^self genPushEnclosingObjectAt: (objectMemory integerValueOf: levelOop)!

Item was removed:
- ----- Method: SimpleStackBasedCogit>>genPushExplicitOuterReceiver: (in category 'bytecode generators') -----
- genPushExplicitOuterReceiver: level
- 	"Uncached push explicit outer send receiver"
- 	self assert: needsFrame. "because this should always be followed by a send"
- 	self MoveCq: level R: SendNumArgsReg.
- 	self CallRT: ceExplicitReceiverTrampoline.
- 	self PushR: ReceiverResultReg.
- 	^0!

Item was removed:
- ----- Method: SimpleStackBasedCogit>>genPushExplicitOuterReceiverBytecode (in category 'bytecode generators') -----
- genPushExplicitOuterReceiverBytecode
- 	"Uncached push explicit outer send receiver"
- 	| levelOop |
- 	levelOop := self getLiteral: byte1.
- 	self assert: (objectMemory isIntegerObject: levelOop).
- 	^self genPushExplicitOuterReceiver: (objectMemory integerValueOf: levelOop)!

Item was changed:
  ----- Method: StackInterpreter class>>initializeBytecodeTableForNewspeakV3PlusClosures (in category 'initialization') -----
  initializeBytecodeTableForNewspeakV3PlusClosures
  	"StackInterpreter initializeBytecodeTableForNewspeakV3PlusClosures"
  	"Note: This table will be used to generate a C switch statement."
  
  	BytecodeTable := Array new: 256.
  	BytecodeEncoderClassName := #EncoderForNewsqueakV3.
  	LongStoreBytecode := 129.
  	self table: BytecodeTable from:
  	#(
  		(  0  15 pushReceiverVariableBytecode)
  		( 16  31 pushTemporaryVariableBytecode)
  		( 32  63 pushLiteralConstantBytecode)
  		( 64  95 pushLiteralVariableBytecode)
  		( 96 103 storeAndPopReceiverVariableBytecode)
  		(104 111 storeAndPopTemporaryVariableBytecode)
  		(112 pushReceiverBytecode)
  		(113 pushConstantTrueBytecode)
  		(114 pushConstantFalseBytecode)
  		(115 pushConstantNilBytecode)
  		(116 pushConstantMinusOneBytecode)
  		(117 pushConstantZeroBytecode)
  		(118 pushConstantOneBytecode)
  		(119 pushConstantTwoBytecode)
  		(120 returnReceiver)
  		(121 returnTrue)
  		(122 returnFalse)
  		(123 returnNil)
  		(124 returnTopFromMethod)
  		(125 returnTopFromBlock)
  
  		"2 of the 3 Newspeak bytecodes"
  		(126 dynamicSuperSendBytecode)
  		(127 pushImplicitReceiverBytecode)
  
  		(128 extendedPushBytecode)
  		(129 extendedStoreBytecode)
  		(130 extendedStoreAndPopBytecode)
  		(131 singleExtendedSendBytecode)
  		(132 doubleExtendedDoAnythingBytecode)
  		(133 singleExtendedSuperBytecode)
  		(134 secondExtendedSendBytecode)
  		(135 popStackBytecode)
  		(136 duplicateTopBytecode)
  
  		(137 pushActiveContextBytecode)
  		(138 pushNewArrayBytecode)),
  
  	((initializationOptions at: #SpurObjectMemory ifAbsent: [false])
  		ifTrue: [#((139 callPrimitiveBytecode))]					"V3PlusClosures on Spur"
+ 		ifFalse: [#((139 pushEnclosingObjectBytecode))]),	"Newspeak on V3"
- 		ifFalse: [#((139 pushExplicitOuterReceiverBytecode))]),	"Newspeak on V3"
  
  	  #(
  		(140 pushRemoteTempLongBytecode)
  		(141 storeRemoteTempLongBytecode)
  		(142 storeAndPopRemoteTempLongBytecode)
  		(143 pushClosureCopyCopiedValuesBytecode)
  
  		(144 151 shortUnconditionalJump)
  		(152 159 shortConditionalJumpFalse)
  		(160 167 longUnconditionalJump)
  		(168 171 longJumpIfTrue)
  		(172 175 longJumpIfFalse)
  
  		"176-191 were sendArithmeticSelectorBytecode"
  		(176 bytecodePrimAdd)
  		(177 bytecodePrimSubtract)
  		(178 bytecodePrimLessThan)
  		(179 bytecodePrimGreaterThan)
  		(180 bytecodePrimLessOrEqual)
  		(181 bytecodePrimGreaterOrEqual)
  		(182 bytecodePrimEqual)
  		(183 bytecodePrimNotEqual)
  		(184 bytecodePrimMultiply)
  		(185 bytecodePrimDivide)
  		(186 bytecodePrimMod)
  		(187 bytecodePrimMakePoint)
  		(188 bytecodePrimBitShift)
  		(189 bytecodePrimDiv)
  		(190 bytecodePrimBitAnd)
  		(191 bytecodePrimBitOr)
  
  		"192-207 were sendCommonSelectorBytecode"
  		(192 bytecodePrimAt)
  		(193 bytecodePrimAtPut)
  		(194 bytecodePrimSize)
  		(195 bytecodePrimNext)
  		(196 bytecodePrimNextPut)
  		(197 bytecodePrimAtEnd)
  		(198 bytecodePrimIdentical)
  		(199 bytecodePrimClass)
  		(200 bytecodePrimSpecialSelector24)
  		(201 bytecodePrimValue)
  		(202 bytecodePrimValueWithArg)
  		(203 bytecodePrimDo)
  		(204 bytecodePrimNew)
  		(205 bytecodePrimNewWithArg)
  		(206 bytecodePrimPointX)
  		(207 bytecodePrimPointY)
  
  		(208 223 sendLiteralSelector0ArgsBytecode)
  		(224 239 sendLiteralSelector1ArgBytecode)
  		(240 255 sendLiteralSelector2ArgsBytecode)
  	)!

Item was added:
+ ----- Method: StackInterpreter>>enclosingObjectAt:withObject:withMixin: (in category 'newspeak bytecode support') -----
+ enclosingObjectAt: n withObject: anObject withMixin: mixin 
+ 	"This is used to implement the innards of the pushEnclosingObjectBytecode,
+ 	 used for explicit outer sends in NS2/NS3.  "
+ 	| enclosingObject mixinApplication targetMixin count |
+ 	
+ 	enclosingObject := anObject.
+ 	targetMixin := mixin.
+ 	count := 0.
+ 	[count < n] whileTrue:
+ 		[count := count + 1.
+ 		(targetMixin = objectMemory nilObject or:[enclosingObject = objectMemory nilObject]) ifTrue:
+ 			[^objectMemory nilObject].
+ 		mixinApplication := self
+ 								findApplicationOfTargetMixin: targetMixin
+ 								startingAtNonMetaClass: (objectMemory fetchClassOf: enclosingObject).
+ 		mixinApplication = objectMemory nilObject ifTrue:
+ 			[^objectMemory nilObject]. "should never happen!!"
+ 		enclosingObject := objectMemory fetchPointer: EnclosingObjectIndex ofObject: mixinApplication.	
+ 		targetMixin := objectMemory fetchPointer: EnclosingMixinIndex ofObject: targetMixin].
+ 	
+ 	^enclosingObject!

Item was removed:
- ----- Method: StackInterpreter>>explicitOuterReceiver:withObject:withMixin: (in category 'newspeak bytecode support') -----
- explicitOuterReceiver: n withObject: anObject withMixin: mixin 
- 	"This is used to implement the innards of the pushExplicitOuterReceiverBytecode,
- 	 used for explicit outer sends in NS2/NS3.  "
- 	| explicitReceiver mixinApplication  targetMixin  count |
- 	
- 	explicitReceiver := anObject.
- 	targetMixin := mixin.
- 	count := 0.
- 	[count < n] whileTrue:
- 		[count := count + 1.
- 		(targetMixin = objectMemory nilObject or:[explicitReceiver = objectMemory nilObject]) ifTrue:
- 			[^objectMemory nilObject].
- 		mixinApplication := self
- 								findApplicationOfTargetMixin: targetMixin
- 								startingAtNonMetaClass: (objectMemory fetchClassOf: explicitReceiver).
- 		mixinApplication = objectMemory nilObject ifTrue:
- 			[^objectMemory nilObject]. "should never happen!!"
- 		explicitReceiver := objectMemory fetchPointer: EnclosingObjectIndex ofObject: mixinApplication.	
- 		targetMixin := objectMemory fetchPointer: EnclosingMixinIndex ofObject: targetMixin].
- 	
- 	^explicitReceiver!

Item was changed:
  ----- Method: StackInterpreter>>extPushPseudoVariableOrOuterBytecode (in category 'stack bytecodes') -----
  extPushPseudoVariableOrOuterBytecode
  	"77			01001101		Push false [* 1:true, 2:nil, 3:thisContext, ..., -N: pushExplicitOuter: N, N = Extend B]"
  	| thing |
  	self fetchNextBytecode.
  	thing := extB
  				caseOf: {
  					[0]	->	[^self internalPush: objectMemory falseObject].
  					[1]	->	[objectMemory trueObject].
  					[2]	->	[objectMemory nilObject].
  					[3]	->	[| context |
  							 context := self ensureFrameIsMarried: localFP SP: localSP.
  							 context]
  				}
  				otherwise:
  					[extB < 0
  						ifTrue:
  							[self 
+ 								enclosingObjectAt: 0 - extB 
- 								explicitOuterReceiver: 0 - extB 
  								withObject: self receiver 
  								withMixin: (self methodClassOf: method)]
  						ifFalse:
  							[self error: 'undefined extension for extPushPseudoVariableOrOuter'.
  							 objectMemory nilObject]].
  	extB := 0.
  	self internalPush: thing!

Item was added:
+ ----- Method: StackInterpreter>>pushEnclosingObjectBytecode (in category 'stack bytecodes') -----
+ pushEnclosingObjectBytecode
+ 	"Find the enclosing object at level N"
+ 	| litIndex  n anIntOop |
+ 	<inline: true>
+ 	litIndex := self fetchByte.
+ 	anIntOop := self literal: litIndex.
+ 	n := (objectMemory isIntegerObject: anIntOop)
+ 			ifTrue: [objectMemory integerValueOf: anIntOop]
+ 			ifFalse: [0].
+ 	self fetchNextBytecode.
+ 	self internalPush:(self 
+ 						enclosingObjectAt: n 
+ 						withObject: self receiver 
+ 						withMixin: (self methodClassOf: method))!

Item was removed:
- ----- Method: StackInterpreter>>pushExplicitOuterReceiverBytecode (in category 'stack bytecodes') -----
- pushExplicitOuterReceiverBytecode
- 	"Find the appropriate implicit receiver for outer N"
- 	| litIndex  n anIntOop |
- 	<inline: true>
- 	litIndex := self fetchByte.
- 	anIntOop := self literal: litIndex.
- 	n := (objectMemory isIntegerObject: anIntOop)
- 			ifTrue: [objectMemory integerValueOf: anIntOop]
- 			ifFalse: [0].
- 	self fetchNextBytecode.
- 	self internalPush:(self 
- 						explicitOuterReceiver: n 
- 						withObject: self receiver 
- 						withMixin: (self methodClassOf: method))!

Item was changed:
  ----- Method: StackToRegisterMappingCogit class>>initializeBytecodeTableForNewspeakV3PlusClosures (in category 'class initialization') -----
  initializeBytecodeTableForNewspeakV3PlusClosures
  	"StackToRegisterMappingCogit initializeBytecodeTableForNewspeakV3PlusClosures"
  
  	numPushNilsFunction := #v3:Num:Push:Nils:.
  	pushNilSizeFunction := #v3PushNilSize:.
  	NSSendIsPCAnnotated := true. "IsNSSendCall used by PushImplicitReceiver"
  	FirstSpecialSelector := 176.
  	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 needsFrameNever: 1)
  		(1  16   31 genPushTemporaryVariableBytecode needsFrameIfMod16GENumArgs: 1)
  		(1  32   63 genPushLiteralConstantBytecode needsFrameNever: 1)
  		(1  64   95 genPushLiteralVariableBytecode needsFrameNever: 1)
  		(1  96 103 genStoreAndPopReceiverVariableBytecode needsFrameNever: -1) "N.B. not frameless if immutability"
  		(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)
  
  		(3 126 126 genDynamicSuperSendBytecode isMapped)			"Newspeak"
  		(2 127 127 genPushImplicitReceiverBytecode isMapped hasIRC)	"Newspeak"
  
  		(2 128 128 extendedPushBytecode needsFrameNever: 1)
  		(2 129 129 extendedStoreBytecode)
  		(2 130 130 extendedStoreAndPopBytecode)
  		(2 131 131 genExtendedSendBytecode isMapped)
  		(3 132 132 doubleExtendedDoAnythingBytecode isMapped)
  		(2 133 133 genExtendedSuperBytecode 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 callPrimitiveBytecode))]									"V3PlusClosures on Spur"
+ 			ifFalse: [#((2 139 139 genPushEnclosingObjectBytecode isMapped))]),	"Newspeak"
- 			ifFalse: [#((2 139 139 genPushExplicitOuterReceiverBytecode isMapped))]),	"Newspeak"
  
  	  #(
  		(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 added:
+ ----- Method: StackToRegisterMappingCogit>>genPushEnclosingObjectAt: (in category 'bytecode generators') -----
+ genPushEnclosingObjectAt: level
+ 	"Uncached push enclosing object"
+ 	optStatus isReceiverResultRegLive: false.
+ 	self ssAllocateCallReg: SendNumArgsReg.
+ 	self MoveCq: level R: SendNumArgsReg.
+ 	self CallRT: ceEnclosingObjectTrampoline.
+ 	^self ssPushRegister: ReceiverResultReg!

Item was removed:
- ----- Method: StackToRegisterMappingCogit>>genPushExplicitOuterReceiver: (in category 'bytecode generators') -----
- genPushExplicitOuterReceiver: level
- 	"Uncached push explicit outer send receiver"
- 	self assert: needsFrame. "because this should always be followed by a send"
- 	optStatus isReceiverResultRegLive: false.
- 	self ssAllocateCallReg: SendNumArgsReg.
- 	self MoveCq: level R: SendNumArgsReg.
- 	self CallRT: ceExplicitReceiverTrampoline.
- 	^self ssPushRegister: ReceiverResultReg!



More information about the Vm-dev mailing list