[squeak-dev] The Trunk: Kernel-eem.1411.mcz

commits at source.squeak.org commits at source.squeak.org
Fri Oct 8 06:44:22 UTC 2021


Marcel Taeumel uploaded a new version of Kernel to project The Trunk:
http://source.squeak.org/trunk/Kernel-eem.1411.mcz

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

Name: Kernel-eem.1411
Author: eem
Time: 12 September 2021, 10:28:17.307559 pm
UUID: af86266e-67ea-47db-9869-8640e23d9780
Ancestors: Kernel-eem.1410

Proposed fix for CompiledCode>>#allLiteralsDo: by adding pushSpecialConstant:/sendSpecial:numArgs:.

Get the bytecode set specific interpretNextInstructionFor: implementations to send sendSpecial:numArgs: and pushSpecialConstant: for special selector sends and implicit literal bytecodes.  Insulate existing InstructionClient subclasses by introducing ImplicitLiteralInstructionClientHook as InstructionClient's superclass which implements pushSpecialConstant:/sendSpecial:numArgs: as sends of pushConstant:/send:super:numArgs:.  Implement pushSpecialConstant:/sendSpecial:numArgs: in Context. Compiler-eem.460 implements these for the Decompiler.

=============== Diff against Kernel-eem.1410 ===============

Item was changed:
  ----- Method: CompiledCode>>abstractBytecodeMessageAt: (in category 'scanning') -----
  abstractBytecodeMessageAt: pc
  	"Answer the abstract bytecode message at pc in the receiver."
+ 	^[(InstructionStream new method: self pc: pc) interpretNextInstructionFor: ImplicitLiteralInstructionClientHook new]
- 	^[(InstructionStream new method: self pc: pc) interpretNextInstructionFor: nil]
  		on: MessageNotUnderstood
  		do: [:ex| ex message]!

Item was changed:
  ----- Method: CompiledCode>>abstractBytecodeMessagesAndPCs (in category 'scanning') -----
  abstractBytecodeMessagesAndPCs
  	"Answer the receiver's sequence of abstract bytecodes as a sequence of tuples of bytecode message and pc."
  	"(CompiledCode >> #abstractBytecodeMessagesAndPCs) abstractBytecodeMessagesAndPCs"
+ 	| msgs initial endpc pc scanner encoderClass implciitLiteralHook |
- 	| msgs initial endpc pc scanner encoderClass |
  	scanner := InstructionStream new method: self pc: (initial := self initialPC).
  	msgs := OrderedCollection new: (endpc  := self endPC) - initial.
  	encoderClass := self encoderClass.
+ 	implciitLiteralHook := ImplicitLiteralInstructionClientHook new.
  	[(pc := scanner pc) <= endpc] whileTrue:
  		"i.e. nil will not understand any message and so the exception block will collect all of them."
+ 		[[encoderClass interpretNextInstructionFor: implciitLiteralHook in: scanner]
- 		[[encoderClass interpretNextInstructionFor: nil in: scanner]
  			on: MessageNotUnderstood
  			do: [:ex| msgs addLast: { ex message. pc }]].
  	^msgs!

Item was changed:
  ----- Method: CompiledCode>>abstractBytecodeMessagesFrom:to:do: (in category 'scanning') -----
  abstractBytecodeMessagesFrom: startpc to: endpc do: aBlock
  	"Evaluate aBlock with the sequence of abstract bytecodes from startpc through endpc in the receiver"
+ 	| scanner encoderClass implciitLiteralHook |
- 	| scanner encoderClass |
  	scanner := InstructionStream new method: self pc: startpc.
  	encoderClass := self encoderClass.
+ 	implciitLiteralHook := ImplicitLiteralInstructionClientHook new.
  	[scanner pc <= endpc] whileTrue:
  		"i.e. nil will not understand any message and so the exception block will collect all of them."
+ 		[[encoderClass interpretNextInstructionFor: implciitLiteralHook in: scanner]
- 		[[encoderClass interpretNextInstructionFor: nil in: scanner]
  			on: MessageNotUnderstood
  			do: [:ex| aBlock value: ex message]]
  
  	"| m msgs |
  	 msgs := OrderedCollection new.
  	 (m := CompiledCode >> #abstractBytecodeMessagesFrom:to:do:)
  		abstractBytecodeMessagesFrom: m initialPC
  		to: m endPC
  		do: [:msg| msgs add: msg selector].
  	 msgs"!

Item was changed:
  ----- Method: CompiledCode>>allLiteralsDo: (in category 'literals') -----
  allLiteralsDo: aBlock
  	"Enumerate all literals thoroughly. Follow nested instances of CompiledCode. Do not treat compiled code as literals here."
  	
+ 	self codeLiteralsDo:
+ 		[:compiledCode |
+ 		compiledCode literalsDo:
+ 			[:literal |
+ 			literal isCompiledCode ifFalse:
+ 				[literal allLiteralsDo: aBlock]].
+ 		compiledCode implicitLiteralsDo: aBlock]!
- 	self codeLiteralsDo: [:compiledCode | compiledCode literalsDo: [:literal |
- 		literal isCompiledCode ifFalse: [literal allLiteralsDo: aBlock] ]].
- 
- 	"Enumerate special selectors."
- 	self flag: #todo.
- 	
- 	"Enumerate special literals such as true and false."
- 	self flag: #todo.!

Item was added:
+ ----- Method: CompiledCode>>implicitLiteralsDo: (in category 'literals') -----
+ implicitLiteralsDo: aBlock
+ 	"Enumerate the implicit literals in bytecodes of the receiver."
+ 	
+ 	| stream client encoderClass endPC |
+ 	"Enumerate special selectors & special literals such as true and false."
+ 	stream := InstructionStream on: self.
+ 	encoderClass := self encoderClass.
+ 	"cache endPC for methods with embedded source; finding out the endPC is very slow in this case..."
+ 	endPC := self endPC.
+ 	client := ImplicitLiteralFinder new.
+ 	[stream pc <= endPC] whileTrue:
+ 		[| literalOrClient |
+ 		literalOrClient := encoderClass interpretNextInstructionFor: client in: stream.
+ 		literalOrClient ~~ client ifTrue:
+ 			[aBlock value: literalOrClient]]!

Item was changed:
  ----- Method: CompiledMethod>>allLiteralsDo: (in category 'literals') -----
  allLiteralsDo: aBlock
  	"Overwritten to skip certain (raw) literals."
  		
  	" Exclude method selector (or properties) and the method's class."
  	1 to: self numLiterals - 2 do: [:index |
  		(self literalAt: index) allLiteralsDo: aBlock].
  
+ 	"Enumerate the implicit literals in bytecodes of the receiver."
+ 	self implicitLiteralsDo: aBlock.
+ 
  	"Enumerate method selector only through additional method state."
  	self penultimateLiteral isMethodProperties
+ 		ifTrue: [self penultimateLiteral allLiteralsDo: aBlock]!
- 		ifTrue: [self penultimateLiteral allLiteralsDo: aBlock].
- 	
- 	"Enumerate special selectors."
- 	self flag: #todo.
- 	
- 	"Enumerate special literals such as true and false."
- 	self flag: #todo.!

Item was added:
+ ----- Method: Context>>pushSpecialConstant: (in category 'instruction decoding implicit literals') -----
+ pushSpecialConstant: value 
+ 	"Simulate the action of bytecode that pushes the constant, value, on the 
+ 	top of the stack."
+ 
+ 	self push: value!

Item was added:
+ ----- Method: Context>>sendSpecial:numArgs: (in category 'instruction decoding implicit literals') -----
+ sendSpecial: selector numArgs: numArgs
+ 	"Simulate the action of bytecodes that send a message with selector, 
+ 	 selector. The arguments  of the message are found in the top numArgs
+ 	 locations on the stack and the receiver just below them."
+ 
+ 	| thisReceiver arguments lookupClass |
+ 	arguments := Array new: numArgs.
+ 	numArgs to: 1 by: -1 do: [ :i | arguments at: i put: self pop].
+ 	thisReceiver := self pop.
+ 	lookupClass := self objectClass: thisReceiver.
+ 	QuickStep == self ifTrue:
+ 		[QuickStep := nil.
+ 		^self quickSend: selector to: thisReceiver with: arguments lookupIn: lookupClass].
+ 	^self send: selector to: thisReceiver with: arguments lookupIn: lookupClass!

Item was added:
+ InstructionClient subclass: #ImplicitLiteralFinder
+ 	instanceVariableNames: ''
+ 	classVariableNames: ''
+ 	poolDictionaries: ''
+ 	category: 'Kernel-Methods'!
+ 
+ !ImplicitLiteralFinder commentStamp: 'eem 9/12/2021 14:44' prior: 0!
+ ImplicitLiteralFinder is a means to extract special literals from an instruction stream.  Instances of InstructionClient answer self in response to all bytecode decode messages.  Instances of this class answer the literal itself for implicit literal bytecode messages.
+ 
+ Instance Variables
+ !

Item was added:
+ ----- Method: ImplicitLiteralFinder>>pushSpecialConstant: (in category 'instruction decoding - implicit literals') -----
+ pushSpecialConstant: value
+ 	^value!

Item was added:
+ ----- Method: ImplicitLiteralFinder>>sendSpecial:numArgs: (in category 'instruction decoding - implicit literals') -----
+ sendSpecial: selector numArgs: numArgs
+ 	^selector!

Item was added:
+ Object subclass: #ImplicitLiteralInstructionClientHook
+ 	instanceVariableNames: ''
+ 	classVariableNames: ''
+ 	poolDictionaries: ''
+ 	category: 'Kernel-Methods'!
+ 
+ !ImplicitLiteralInstructionClientHook commentStamp: 'eem 9/12/2021 14:29' prior: 0!
+ ImplicitLiteralInstructionClientHook is a hook to allow clients to intercept bytecodes referencing implicit literals, such as special selector sends which have an implicit selector in Smalltalk specialSelectors.  It implements the messages sent by InstructionStream's interpretNextXXXInstructionFor: methods for bytecodes that reference implicit literals as sends of the relevant explciit literal methods.  This allows clients that want to to intercept implicit literal messages while leaving existing clients unchanged.
+ 
+ Instance Variables!

Item was added:
+ ----- Method: ImplicitLiteralInstructionClientHook>>pushSpecialConstant: (in category 'instruction decoding - implicit literals') -----
+ pushSpecialConstant: value
+ 	"This is a hook to allow clients to intercept implicit literal bytecodes"
+ 	^self pushConstant: value!

Item was added:
+ ----- Method: ImplicitLiteralInstructionClientHook>>sendSpecial:numArgs: (in category 'instruction decoding - implicit literals') -----
+ sendSpecial: selector numArgs: numArgs
+ 	"This is a hook to allow clients to intercept special selector sends (which have an implicit selector)"
+ 	^self send: selector super: false numArgs: numArgs!

Item was changed:
+ ImplicitLiteralInstructionClientHook subclass: #InstructionClient
- Object subclass: #InstructionClient
  	instanceVariableNames: ''
  	classVariableNames: ''
  	poolDictionaries: ''
  	category: 'Kernel-Methods'!
  
  !InstructionClient commentStamp: 'md 4/8/2003 12:50' prior: 0!
  My job is to make it easier to implement clients for InstructionStream. See InstVarRefLocator
  as an example. !

Item was changed:
  ----- Method: InstructionStream>>interpretNext2ByteSistaV1Instruction:for:extA:extB:startPC: (in category 'decoding - private - sista v1') -----
  interpretNext2ByteSistaV1Instruction: bytecode for: client extA: extA extB: extB startPC: startPC
  	"Send to the argument, client, a message that specifies the next instruction.
  	 This method handles the two-byte codes.
  	 For a table of the bytecode set, see EncoderForV1's class comment."
  
  	| byte method |
  	method := self method.
  	byte := self method at: pc.
  	pc := pc + 1.
  	"We do an inline quasi-binary search on bytecode"
  	bytecode < 234 ifTrue: "pushes"
  		[bytecode < 231 ifTrue:
  			[bytecode < 229 ifTrue:
  				[| literal |
  				 bytecode = 226 ifTrue:
  					[^client pushReceiverVariable: (extA bitShift: 8) + byte].
  				 literal := method literalAt: (extA bitShift: 8) + byte + 1.
  				 bytecode = 227 ifTrue:
  					[^client pushLiteralVariable: literal].
  				 ^client pushConstant: literal].
  			bytecode = 229 ifTrue:
  				[^client pushTemporaryVariable: byte].
  			^self unusedBytecode: client at: startPC].
  		bytecode = 231 ifTrue:
  			[^byte < 128
  				ifTrue: [client pushNewArrayOfSize: byte]
  				ifFalse: [client pushConsArrayWithElements: byte - 128]].
  		bytecode = 232 ifTrue:
+ 			[^client pushSpecialConstant: ((extB < 128 ifTrue: [extB] ifFalse: [extB - 256]) bitShift: 8) + byte].
+ 		^client pushSpecialConstant: (Character value: (extB bitShift: 8) + byte)].
- 			[^client pushConstant: ((extB < 128 ifTrue: [extB] ifFalse: [extB - 256]) bitShift: 8) + byte].
- 		^client pushConstant: (Character value: (extB bitShift: 8) + byte)].
  	bytecode < 240 ifTrue: "sends, trap and jump"
  		[bytecode < 236 ifTrue: "sends"
  			[(bytecode = 235 and: [extB >= 64]) ifTrue:
  				[^client
  					directedSuperSend: (method literalAt: (extA bitShift: 5) + (byte // 8) + 1)
  					numArgs: (extB - 64 bitShift: 3) + (byte \\ 8)].
  			 ^client
  				send: (method literalAt: (extA bitShift: 5) + (byte // 8) + 1)
  				super: bytecode = 235
  				numArgs: (extB bitShift: 3) + (byte \\ 8)].
  		 bytecode = 236 ifTrue:
  			[^client callMappedInlinedPrimitive: byte].
  		bytecode = 237 ifTrue:
  			[^client jump: (extB bitShift: 8) + byte].
  		 ^client jump: (extB bitShift: 8) + byte if: bytecode = 238].
  	bytecode < 243 ifTrue:
  		[bytecode = 240 ifTrue:
  			[^client popIntoReceiverVariable: (extA bitShift: 8) + byte].
  		 bytecode = 241 ifTrue:
  			[^client popIntoLiteralVariable: (method literalAt: (extA bitShift: 8) + byte + 1)].
  		 ^client popIntoTemporaryVariable: byte].
  	bytecode = 243 ifTrue:
  		[^client storeIntoReceiverVariable: (extA bitShift: 8) + byte].
  	bytecode = 244 ifTrue:
  		[^client storeIntoLiteralVariable: (method literalAt: (extA bitShift: 8) + byte + 1)].
  	bytecode = 245 ifTrue:
  		[^client storeIntoTemporaryVariable: byte].
  	"246-247	1111011 i	xxxxxxxx	UNASSIGNED"
  	^self unusedBytecode: client at: startPC!

Item was changed:
  ----- Method: InstructionStream>>interpretNextSistaV1InstructionFor: (in category 'decoding - private - sista v1') -----
  interpretNextSistaV1InstructionFor: client
  	"Send to the argument, client, a message that specifies the next instruction."
  
  	| byte div16 offset method extA extB savedPC |
  	method := self method.
  	"For a table of the bytecode set, see EncoderForSistaV1's class comment."
  	"consume and compute any extensions first."
  	extA := extB := 0.
  	savedPC := pc.
  	[byte := self method at: pc.
  	 pc := pc + 1.
  	 byte >= 16rE0 and: [byte <= 16rE1]] whileTrue:
  		[| extByte |
  		 extByte := self method at: pc.
  		 pc := pc + 1.
  		 byte = 16rE0
  			ifTrue:
  				[extA := (extA bitShift: 8) + extByte]
  			ifFalse:
  				[extB := (extB = 0 and: [extByte > 127])
  							ifTrue: [extByte - 256]
  							ifFalse: [(extB bitShift: 8) + extByte]]].
  	div16 := byte // 16.
  	offset := byte \\ 16.
  	"We do an inline quasi-binary search on each of the possible 16 values of div16"
  	div16 < 11 ifTrue:
  		[div16 < 6 ifTrue:
  			[div16 < 4 ifTrue:
  				[div16 < 2 ifTrue:
  					[div16 = 0 ifTrue:
  						 [^client pushReceiverVariable: offset].
  					^client pushLiteralVariable: (method literalAt: offset + 1)]. "div16 = 1"
  				 ^client pushConstant: (method literalAt: byte \\ 32 + 1)].
  			 div16 = 4 ifTrue:
  				[offset < 12 ifTrue:
  					[^client pushTemporaryVariable: offset].
  				 offset = 12 ifTrue:
  					[^client pushReceiver].
  				 offset = 13 ifTrue:
+ 					[^client pushSpecialConstant: true].
- 					[^client pushConstant: true].
  				 offset = 14 ifTrue:
+ 					[^client pushSpecialConstant: false].
- 					[^client pushConstant: false].
  				 offset = 15 ifTrue:
+ 					[^client pushSpecialConstant: nil]].
- 					[^client pushConstant: nil]].
  			"div16 = 5"
  			 offset < 2 ifTrue:
+ 				[^client pushSpecialConstant: offset].
- 				[^client pushConstant: offset].
  			 offset = 2 ifTrue:
  				[^self interpretSistaV1ExtendedPush: extB for: client].
  			 offset = 3 ifTrue:
  				[^client doDup].
  			 offset = 8 ifTrue:
  				[^client methodReturnReceiver].
  			 offset = 9 ifTrue:
  				[^client methodReturnConstant: true].
  			 offset = 10 ifTrue:
  				[^client methodReturnConstant: false].
  			 offset = 11 ifTrue:
  				[^client methodReturnConstant: nil].
  			 offset = 12 ifTrue:
  				[^client methodReturnTop].
  			 offset = 13 ifTrue:
  				[^client blockReturnConstant: nil].
  			 offset = 14 ifTrue:
  				[^client blockReturnTop].
  			 offset = 15 ifTrue:
  				[^client doNop].
  			 ^self unusedBytecode: client at: savedPC].
  		"short sends"
  		div16 = 6 ifTrue:
  			[^client
+ 				sendSpecial: (Smalltalk specialSelectorAt: offset + 1)
- 				send: (Smalltalk specialSelectorAt: offset + 1)
- 				super: false
  				numArgs: (Smalltalk specialNargsAt: offset + 1)].
  		 div16 = 7 ifTrue:
  			[^client
+ 				sendSpecial: (Smalltalk specialSelectorAt: offset + 17)
- 				send: (Smalltalk specialSelectorAt: offset + 17)
- 				super: false
  				numArgs: (Smalltalk specialNargsAt: offset + 17)].
  		^client
  			send: (method literalAt: offset + 1)
  			super: false
  			numArgs: div16 - 8].
  	"div16 >= 11; bytecode >= 176"
  	div16 < 14 ifTrue:
  		[div16 = 11 ifTrue:
  			[offset < 8 ifTrue:
  				[^client jump: offset + 1].
  			 ^client jump: offset - 7 if: true].
  		 div16 = 12 ifTrue:
  			[offset < 8 ifTrue:
  				[^client jump: offset + 1 if: false].
  			 ^client popIntoReceiverVariable: offset - 8].
  		 "div16 = 13"
  		 offset < 8 ifTrue:
  		 	[^client popIntoTemporaryVariable: offset].
  		 offset = 8 ifTrue:
  			[^client doPop].
  		 offset = 9 ifTrue:
  			[^client trap].
  		 ^self unusedBytecode: client at: savedPC].
  	"2 byte and 3 byte codes"
  	byte < 248 ifTrue:
  		[^self interpretNext2ByteSistaV1Instruction: byte for: client extA: extA extB: extB startPC: savedPC].
  	^self interpretNext3ByteSistaV1Instruction: byte for: client extA: extA extB: extB startPC: savedPC!

Item was changed:
  ----- Method: InstructionStream>>interpretNextV3ClosuresInstructionFor: (in category 'decoding - private - v3 plus closures') -----
  interpretNextV3ClosuresInstructionFor: client 
  	"Send to the argument, client, a message that specifies the type of the 
  	 next instruction."
  
  	| byte type offset method |
  	method := self method.  
  	byte := method at: pc.
  	type := byte // 16.  
  	offset := byte \\ 16.  
  	pc := pc+1.
  	"We do an inline binary search on each of the possible 16 values of type."
  	type < 8 ifTrue:
  		[type < 4 ifTrue:
  			[type < 2 ifTrue:
  				[type = 0 ifTrue:
  					[^ client pushReceiverVariable: offset].
  				^ client pushTemporaryVariable: offset].				"type = 1"
  			type = 2 ifTrue: 
  				[^ client pushConstant: (method literalAt: offset + 1)].
  			^ client pushConstant: (method literalAt: offset + 17)].		"type = 3"
  		type < 6 ifTrue:
  			[type = 4 ifTrue:
  				[^ client pushLiteralVariable: (method literalAt: offset + 1)].
  			^ client pushLiteralVariable: (method literalAt: offset + 17)]."type = 5"
  		type = 6 ifTrue:
  			[offset < 8 ifTrue:
  				[^ client popIntoReceiverVariable: offset].
  			^ client popIntoTemporaryVariable: offset - 8].
  		"type = 7"
  		offset = 0 ifTrue: [^ client pushReceiver].
+ 		offset < 8 ifTrue: [^ client pushSpecialConstant: (SpecialConstants at: offset)].
- 		offset < 8 ifTrue: [^ client pushConstant: (SpecialConstants at: offset)].
  		offset = 8 ifTrue: [^ client methodReturnReceiver].
  		offset < 12 ifTrue: [^ client methodReturnConstant: (SpecialConstants at: offset - 8)].
  		offset = 12 ifTrue: [^ client methodReturnTop].
  		offset = 13 ifTrue: [^ client blockReturnTop].
  		^ self unusedBytecode: client at: pc - 1]. "offset = 14 & offset = 15, 126 & 127"
  	type < 12 ifTrue:
  		[type < 10 ifTrue:
  			[type = 8 ifTrue:
  				[^ self
  					interpretV3ClosuresExtension: offset
  					in: method
  					for: client].
  			"type = 9 (short jumps)"
  			offset < 8 ifTrue: [^ client jump: offset + 1].
  			^ client jump: offset - 8 + 1 if: false].
  		type = 10 ifTrue: "(long jumps)"
  			[byte := method at: pc.
  			pc := pc + 1.
  			offset < 8 ifTrue: [^ client jump: offset - 4 * 256 + byte].
  			^ client jump: (offset bitAnd: 3) * 256 + byte if: offset < 12].
  		"type = 11; arithmetic special selector sends"
  		^ client
+ 			sendSpecial: (Smalltalk specialSelectorAt: offset + 1)
- 			send: (Smalltalk specialSelectorAt: offset + 1)
- 			super: false
  			numArgs: (Smalltalk specialNargsAt: offset + 1)].
  		type = 12 ifTrue: "non-arithmetic special selector sends"
  			[^ client
+ 				sendSpecial: (Smalltalk specialSelectorAt: offset + 17)
- 				send: (Smalltalk specialSelectorAt: offset + 17)
- 				super: false
  				numArgs: (Smalltalk specialNargsAt: offset + 17)].
  	"type = 13, 14 or 15"
  	^ client
  		send: (method literalAt: offset + 1)
  		super: false
  		numArgs: type - 13 "0, 1 & 2"!

Item was changed:
  ----- Method: InstructionStream>>interpretNextV3InstructionFor: (in category 'decoding - private - v3 plus closures') -----
  interpretNextV3InstructionFor: client 
  	"Send to the argument, client, a message that specifies the type of the 
  	 next instruction."
  
  	| byte type offset method |
  	method := self method.  
  	byte := method at: pc.
  	type := byte // 16.  
  	offset := byte \\ 16.  
  	pc := pc+1.
  	"We do an inline binary search on each of the possible 16 values of type."
  	type < 8 ifTrue:
  		[type < 4 ifTrue:
  			[type < 2 ifTrue:
  				[type = 0 ifTrue:
  					[^ client pushReceiverVariable: offset].
  				^ client pushTemporaryVariable: offset].				"type = 1"
  			type = 2 ifTrue: 
  				[^ client pushConstant: (method literalAt: offset + 1)].
  			^ client pushConstant: (method literalAt: offset + 17)].		"type = 3"
  		type < 6 ifTrue:
  			[type = 4 ifTrue:
  				[^ client pushLiteralVariable: (method literalAt: offset + 1)].
  			^ client pushLiteralVariable: (method literalAt: offset + 17)]."type = 5"
  		type = 6 ifTrue:
  			[offset < 8 ifTrue:
  				[^ client popIntoReceiverVariable: offset].
  			^ client popIntoTemporaryVariable: offset - 8].
  		"type = 7"
  		offset = 0 ifTrue: [^ client pushReceiver].
+ 		offset < 8 ifTrue: [^ client pushSpecialConstant: (SpecialConstants at: offset)].
- 		offset < 8 ifTrue: [^ client pushConstant: (SpecialConstants at: offset)].
  		offset = 8 ifTrue: [^ client methodReturnReceiver].
  		offset < 12 ifTrue: [^ client methodReturnConstant: (SpecialConstants at: offset - 8)].
  		offset = 12 ifTrue: [^ client methodReturnTop].
  		offset = 13 ifTrue: [^ client blockReturnTop].
  		^ self unusedBytecode: client at: pc - 1]. "offset = 14 & offset = 15, 126 & 127"
  	type < 12 ifTrue:
  		[type < 10 ifTrue:
  			[type = 8 ifTrue:
  				[^ self
  					interpretV3Extension: offset
  					in: method
  					for: client].
  			"type = 9 (short jumps)"
  			offset < 8 ifTrue: [^ client jump: offset + 1].
  			^ client jump: offset - 8 + 1 if: false].
  		type = 10 ifTrue: "(long jumps)"
  			[byte := method at: pc.
  			pc := pc + 1.
  			offset < 8 ifTrue: [^ client jump: offset - 4 * 256 + byte].
  			^ client jump: (offset bitAnd: 3) * 256 + byte if: offset < 12].
  		"type = 11; arithmetic special selector sends"
  		^ client
+ 			sendSpecial: (Smalltalk specialSelectorAt: offset + 1)
- 			send: (Smalltalk specialSelectorAt: offset + 1)
- 			super: false
  			numArgs: (Smalltalk specialNargsAt: offset + 1)].
  		type = 12 ifTrue: "non-arithmetic special selector sends"
  			[^ client
+ 				sendSpecial: (Smalltalk specialSelectorAt: offset + 17)
- 				send: (Smalltalk specialSelectorAt: offset + 17)
- 				super: false
  				numArgs: (Smalltalk specialNargsAt: offset + 17)].
  	"type = 13, 14 or 15"
  	^ client
  		send: (method literalAt: offset + 1)
  		super: false
  		numArgs: type - 13 "0, 1 & 2"!



More information about the Squeak-dev mailing list