The Trunk: Compiler-nice.355.mcz

Previous Topic Next Topic
 
classic Classic list List threaded Threaded
1 message Options
Reply | Threaded
Open this post in threaded view
|

The Trunk: Compiler-nice.355.mcz

commits-2
Nicolas Cellier uploaded a new version of Compiler to project The Trunk:
http://source.squeak.org/trunk/Compiler-nice.355.mcz

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

Name: Compiler-nice.355
Author: nice
Time: 5 May 2017, 10:21:50.023997 pm
UUID: 3678dcdc-13c7-467e-a8f1-878f8fbabd80
Ancestors: Compiler-eem.341, Compiler-eem.354, Compiler-nice.354

Merge

Compiler-eem.354:
        Provide a proper comment for BlockNode and eliminate an unused variable and an unused method; this in prelude to implementing full blocks.

Eliminate obsolete binding machinery (literalScannedAs:notifying:).  The current compiler deals with Undeclared in a more direct way earlier in compilation.

Nuke the unnecessary identical override of generateMethodOfClass:trailer:from: in EncoderForSistaV1.

 Correct a spelling error.

Compiler-nice.354:
        Don't decompile obsolete compiled forms for braces {} (braceWith: & friends) nor blocks [] (closureCopy:copiedValues:)

=============== Diff against Compiler-eem.341 ===============

Item was changed:
+ ----- Method: AssignmentNode>>analyseTempsWithin:rootNode:assignmentPools: (in category 'closure analysis') -----
- ----- Method: AssignmentNode>>analyseTempsWithin:rootNode:assignmentPools: (in category 'code generation (closures)') -----
  analyseTempsWithin: scopeBlock "<BlockNode>"  rootNode: rootNode "<MethodNode>" assignmentPools: assignmentPools "<Dictionary>"
  "N.B.  since assigment happens _after_ the value is evaluated the value is sent the message _first_."
  value analyseTempsWithin: scopeBlock rootNode: rootNode assignmentPools: assignmentPools.
  variable beingAssignedToAnalyseTempsWithin: scopeBlock rootNode: rootNode assignmentPools: assignmentPools!

Item was changed:
  ----- Method: AssignmentNode>>toDoIncrement: (in category 'initialize-release') -----
  toDoIncrement: var
+ ^(var = variable
+   and: [value isMessageNode]) ifTrue:
+ [value toDoIncrement: var]!
- var = variable ifFalse: [^ nil].
- (value isMemberOf: MessageNode)
- ifTrue: [^ value toDoIncrement: var]
- ifFalse: [^ nil]!

Item was added:
+ ----- Method: BlockLocalTempCounter>>blockReturnConstant: (in category 'instruction decoding') -----
+ blockReturnConstant: value
+ "Return Constant From Block bytecode."
+ scanner pc < blockEnd ifTrue:
+ [self doJoin]!

Item was added:
+ ----- Method: BlockLocalTempCounter>>directedSuperSend:numArgs: (in category 'instruction decoding') -----
+ directedSuperSend: selector numArgs: numArgs
+ "Send Message Above Specific Class With Selector, selector, bytecode.
+ Start the lookup above the class that is the value of the association on
+ top of stack. The arguments  of the message are found in the top numArgs
+ stack locations beneath the association, and the receiver just below them."
+
+ stackPointer := stackPointer - (numArgs + 1)!

Item was changed:
  ----- Method: BlockLocalTempCounter>>tempCountForBlockAt:in: (in category 'initialize-release') -----
  tempCountForBlockAt: pc in: method
  "Compute the number of local temporaries in a block.
  If the block begins with a sequence of push: nil bytecodes then some of
  These could be initializing local temps.  We can only reliably disambuguate
  them from other uses of nil by parsing the stack and seeing what the offset
  of the stack pointer is at the end of the block.
 
  There are short-cuts.  The ones we take here are
  - if there is no sequence of push nils there can be no local temps
  - we follow forward jumps to shorten the amount of scanning"
  stackPointer := 0.
  scanner := InstructionStream new method: method pc: pc.
  scanner interpretNextInstructionFor: self.
  blockEnd ifNil:
  [self error: 'pc is not that of a block'].
+ scanner nextByte = method encoderClass pushNilCode ifTrue:
- scanner nextByte = Encoder pushNilCode ifTrue:
  [joinOffsets := Dictionary new.
  [scanner pc < blockEnd] whileTrue:
  [scanner interpretNextInstructionFor: self]].
  ^stackPointer!

Item was changed:
  ----- Method: BlockLocalTempCounter>>testTempCountForBlockAt:in: (in category 'initialize-release') -----
  testTempCountForBlockAt: startPc in: method
  "Compute the number of local temporaries in a block.
  If the block begins with a sequence of push: nil bytecodes then some of
  These could be initializing local temps.  We can only reliably disambuguate
  them from other uses of nil by parsing the stack and seeing what the offset
  of the stack pointer is at the end of the block.There are short-cuts.  The only
  one we take here is
  - if there is no sequence of push nils there can be no local temps"
 
  | symbolicLines line prior thePc |
  symbolicLines := Dictionary new.
  method symbolicLinesDo:
  [:pc :lineForPC| symbolicLines at: pc put: lineForPC].
  stackPointer := 0.
  scanner := InstructionStream new method: method pc: startPc.
  scanner interpretNextInstructionFor: self.
  blockEnd ifNil:
  [self error: 'pc is not that of a block'].
+ scanner nextByte = method encoderClass pushNilCode ifTrue:
- scanner nextByte = Encoder pushNilCode ifTrue:
  [joinOffsets := Dictionary new.
  [scanner pc < blockEnd] whileTrue:
  [line := symbolicLines at: scanner pc.
  prior := stackPointer.
  thePc := scanner pc.
  scanner interpretNextInstructionFor: self.
  Transcript cr; print: prior; nextPutAll: '->'; print: stackPointer;  tab; print: thePc; tab; nextPutAll: line; flush]].
  ^stackPointer!

Item was changed:
  ParseNode subclass: #BlockNode
+ instanceVariableNames: 'arguments statements returns nArgsNode size temporaries optimized optimizedMessageNode actualScopeIfOptimized blockExtent remoteTempNode copiedValues closureCreationNode startOfLastStatement tempsMark'
- instanceVariableNames: 'arguments statements returns nArgsNode size remoteCopyNode temporaries optimized optimizedMessageNode actualScopeIfOptimized blockExtent remoteTempNode copiedValues closureCreationNode startOfLastStatement tempsMark'
  classVariableNames: ''
  poolDictionaries: ''
  category: 'Compiler-ParseNodes'!
 
+ !BlockNode commentStamp: 'eem 5/4/2017 17:26' prior: 0!
+ I represent a bracketed block with 0 or more arguments and 1 or more statements. If I am initialized with no statements, I create one. I have a flag to tell whether my last statement returns a value from the enclosing method. I can emit for value in the usual way, in which case I create a BlockClosure to be evaluated by sending it value: at run time. Or I can emit code to be evaluated in line; this only happens at the top level of a method and in certain optimized control structures (see MessageNode class>>initialize MacroSelectors).
+
+ Instance Variables
+ actualScopeIfOptimized: <nil | BlockNode>
+ arguments: <SequencableCollection of: TempVariableNode>
+ blockExtent: <nil | Interval>
+ closureCreationNode: <LeafNode>
+ copiedValues: <nil | (SequencableCollection of: TempVariableNode)>
+ nArgsNode: <nil | Integer>
+ optimized: <Boolean>
+ optimizedMessageNode: <nil | MessageNode>
+ remoteTempNode: <nil | RemoteTempVectorNode>
+ returns: <Boolean>
+ size: <nil | Integer>
+ startOfLastStatement: <nil | Integer>
+ statements: <SequencableCollection of: ParseNode>
+ temporaries: <SequencableCollection of: TempVariableNode>
+ tempsMark: <nil | Integer>
+
+ actualScopeIfOptimized
+ - if the receiver has been inlined this is the non-optimized BlockNode the receiver is inlined into.
+
+ arguments
+ - the sequence of arguments to the block (or method if a top-level block)
+
+ blockExtent
+ - the interval defining the range of block scopes the receiver comprises, which is itself and any blokcs it may contain.  See #analyseArguments:temporaries:rootNode:
+
+ closureCreationNode
+ - a place-holder representing the body of the block.
+
+ copiedValues
+ - blocks do not reference the temporary variables of their outer context they cose over directly; instead temporary variables which won't change value are collected and copied into the block, and temporary variables that are modified either within the block or after it has closed over the variales are allocated in a remote temp vector that again becomes one of the block's copied values.  In this way, a block refers to the outer teporaries it closes over only throguh copiedValues.  copiedValues is the sequence of these TempVariableNodes.
+
+ nArgsNode
+ - a place holder for the encoder to allow it to number block temporaries
+
+ optimized
+ - true if the receiver is inlined, false if a true block
+
+ optimizedMessageNode
+ - the MessageNode in which the receiver is optimized, if it is optimized.
+
+ remoteTempNode
+ - if any of the blocks nested into the receiver either modify a temp or access a temp that is modified after the block is created, then this temp is allocated remotely in a remote temp vector that allows the temp's location to be shared between blocks.  This is the node that creates the remote temp vector.
+
+ returns
+ - true if the receiver contains a method return.
+
+ size
+ - the size of the block's bytecodes if it is generated by embedding its bytecodes within an enclosing CompiledMethod.
+
+ startOfLastStatement
+ - the index in the source of the start of the last statement in the block.
+
+ statements
+ - the sequence of statements comprising the receiver
+
+ temporaries
+ - the sequence of temporaries (including the remoteTempNode if any) of block-local temporaries
+
+ tempsMark
+ - the index in the source of the last block-local temporary, used to auto-insert temps declared during compilation!
- !BlockNode commentStamp: '<historical>' prior: 0!
- I represent a bracketed block with 0 or more arguments and 1 or more statements. If I am initialized with no statements, I create one. I have a flag to tell whether my last statement returns a value from the enclosing method. My last three fields remember data needed for code generation. I can emit for value in the usual way, in which case I create a literal method (actually a context remotely copied) to be evaluated by sending it value: at run time. Or I can emit code to be evaluated in line; this only happens at the top level of a method and in conditionals and while-loops, none of which have arguments.!

Item was changed:
+ ----- Method: BlockNode>>actualScope (in category 'closure analysis') -----
- ----- Method: BlockNode>>actualScope (in category 'code generation (closures)') -----
  actualScope
  "Answer the actual scope for the receiver.  If this is an unoptimized block then it is its
  actual scope, but if this is an optimized block then the actual scope is some outer block."
  ^actualScopeIfOptimized ifNil: [self]!

Item was changed:
+ ----- Method: BlockNode>>addHoistedTemps: (in category 'closure analysis') -----
- ----- Method: BlockNode>>addHoistedTemps: (in category 'code generation (closures)') -----
  addHoistedTemps: additionalTemporaries "<SequenceableCollection>"
  | tempsToBeMerged additionalTempsToAdd |
  additionalTemporaries do:
  [:temp|
  temp definingScope ifNil:
  [temp definingScope: self]].
  (temporaries isNil or: [temporaries isEmpty]) ifTrue:
  [temporaries := additionalTemporaries copy.
  ^self].
  tempsToBeMerged := additionalTemporaries select:
  [:t|
  t isBlockArg
  and: [temporaries anySatisfy: [:existing| existing isBlockArg and: [existing key = t key]]]].
  additionalTempsToAdd := tempsToBeMerged isEmpty
  ifTrue: [additionalTemporaries copy]
  ifFalse: [additionalTemporaries reject: [:temp| tempsToBeMerged identityIncludes: temp]].
  temporaries := (temporaries isNil or: [temporaries isEmpty])
  ifTrue: [additionalTempsToAdd]
  ifFalse:
  [temporaries last isIndirectTempVector
  ifTrue: [temporaries allButLast, additionalTempsToAdd, { temporaries last }]
  ifFalse: [temporaries, additionalTempsToAdd]].
  tempsToBeMerged do:
  [:t| | merge |
  merge := temporaries detect: [:existing| existing isBlockArg and: [existing key = t key]].
  merge absorbHoistedTemp: t]!

Item was changed:
+ ----- Method: BlockNode>>addRemoteTemp:rootNode: (in category 'closure analysis') -----
- ----- Method: BlockNode>>addRemoteTemp:rootNode: (in category 'code generation (closures)') -----
  addRemoteTemp: aTempVariableNode rootNode: rootNode "<MethodNode>"
  "Add aTempVariableNode to my actualScope's sequence of
  remote temps.  If I am an optimized block then the actual
  scope is my actualScopeIfOptimized, otherwise it is myself."
  remoteTempNode == nil ifTrue:
  [remoteTempNode := RemoteTempVectorNode new
  name: self remoteTempNodeName
  index: arguments size + temporaries size
  type: LdTempType
  scope: 0.
  actualScopeIfOptimized
  ifNil:
  [self addTempNode: remoteTempNode.
  remoteTempNode definingScope: self]
  ifNotNil: [actualScopeIfOptimized addHoistedTemps: { remoteTempNode }]].
  remoteTempNode addRemoteTemp: aTempVariableNode encoder: rootNode encoder.
  "use remove:ifAbsent: because the deferred analysis for optimized
  loops can result in the temp has already been hoised into the root."
  self removeTempNode: aTempVariableNode ifAbsent: [
  self actualScope removeTempNode: aTempVariableNode ifAbsent: ["should not happen"]].
  ^remoteTempNode!

Item was changed:
+ ----- Method: BlockNode>>addTempNode: (in category 'closure analysis') -----
- ----- Method: BlockNode>>addTempNode: (in category 'code generation (closures)') -----
  addTempNode: aTempVariableNode
  "Utilities for when we want to add some temporaries."
 
  self makeTemporariesRemovable.
  ^temporaries add: aTempVariableNode!

Item was changed:
+ ----- Method: BlockNode>>analyseArguments:temporaries:rootNode: (in category 'closure analysis') -----
- ----- Method: BlockNode>>analyseArguments:temporaries:rootNode: (in category 'code generation (closures)') -----
  analyseArguments: methodArguments temporaries: methodTemporaries rootNode: rootNode "<MethodNode>" "^<Sequence of: <TempVarNade>>"
  "Top level entry-point for analysing temps within the hierarchy of blocks in the receiver's method.
  Answer the (possibly modified) sequence of temp vars.
  Need to hoist temps out of macro-optimized blocks into their actual blocks.
  Need to note reads and writes to temps from blocks other than their actual blocks to determine
  whether blocks can be local (simple slots within a block/method context) or remote (slots in
  indirection vectors that are shared between contexts by sharing indirection vectors).
 
  The algorithm is based on numbering temporary reads and writes and block extents.
  The index used for numbering starts at zero and is incremented on every block entry
  and block exit.  So the following
  | a b blk r1 r2 t |
  a := 1. b := 2. t := 0.
  blk := [ | s | s := a + b. t := t + s].
  r1 := blk value.
  b := -100.
  r2 := blk value.
  r1 -> r2 -> t
  is numbered as
  method block 0 to: 6:
  | a b blk r1 r2 t |
  a w@1 := 1. b w@1 := 2. t w@1 := 0.
  blk w@5 := [entry@2 | s |
  t  w@3 := t r@3 + a r@3 + b r@3
  ] exit@4.
  r1 w@5 := blk r@5 value.
  b w@5 := nil.
  r2 w@5 := blk r@5 value.
  r1 r@5 -> r2 r@5 -> t r@5
  So:
  b and blk cannot be copied because for both there exists a write @5 that follows a
  read @4 within block 2 through 4
  t must be remote because there exists a write @3 within block (2 to: 4)
  Complications are introduced by optimized blocks.  In the following temp is written to
  after it is closed over by [ temp ] since the inlined block is executed more than once.
  | temp coll |
  coll := OrderedCollection new.
  1 to: 5 do: [ :index |
  temp := index.
  coll add: [ temp ] ].
  self assert: (coll collect: [:ea| ea value]) asArray = #(5 5 5 5 5)
  In the following i is local to the block and must be initialized each time around the loop
  but if the block is inlined it must be declared at method level.
  | col |
  col := OrderedCollection new.
  1 to: 3 do: [ :each | | i | i := each. col add: [ i ]. i := i + 1 ].
  self assert: (col collect: [ :each | each value ]) asArray = #(2 3 4)"
  self assert: (arguments isEmpty or: [arguments hasEqualElements: methodArguments]).
  arguments := methodArguments asArray. "won't change"
  self assert: (temporaries isNil or: [temporaries isEmpty or: [temporaries hasEqualElements: methodTemporaries]]).
  temporaries := OrderedCollection withAll: methodTemporaries.
 
  self assert: optimized not. "the top-level block should not be optimized."
  self analyseTempsWithin: self rootNode: rootNode assignmentPools: Dictionary new.
 
  "The top-level block needs to reindex temporaries since analysis may have rearranged them.
  This happens when temps are made remote and/or a remote node is added."
  temporaries withIndexDo:
  [:temp :offsetPlusOne| temp index: arguments size + offsetPlusOne - 1].
 
  "Answer the (possibly modified) sequence of temps."
  ^temporaries asArray!

Item was changed:
+ ----- Method: BlockNode>>analyseTempsWithin:rootNode:assignmentPools: (in category 'closure analysis') -----
- ----- Method: BlockNode>>analyseTempsWithin:rootNode:assignmentPools: (in category 'code generation (closures)') -----
  analyseTempsWithin: scopeBlock "<BlockNode>" rootNode: rootNode "<MethodNode>" assignmentPools: assignmentPools "<Dictionary>"
  | effectiveScope blockStart |
  effectiveScope := optimized
  ifTrue: [actualScopeIfOptimized := scopeBlock]
  ifFalse: [self].
 
  arguments ifNotNil:
  [arguments do: [:temp| temp definingScope: self]].
  temporaries ifNotNil:
  [temporaries do: [:temp| temp definingScope: self]].
 
  optimized ifFalse: "if optimized this isn't an actual scope"
  [rootNode noteBlockEntry:
  [:entryNumber|
  blockExtent := (blockStart := entryNumber) to: 0]].
 
  "Need to enumerate a copy because closure analysis can add a statement
  via ifHasRemoteTempNodeEnsureInitializationStatementExists:."
  statements copy do:
  [:statement|
  statement analyseTempsWithin: effectiveScope rootNode: rootNode assignmentPools: assignmentPools].
 
  optimized
  ifTrue: "if optimized loop need to add nils for any temps read before written"
  [optimizedMessageNode isOptimizedLoop ifTrue:
  [self nilReadBeforeWrittenTemps]]
  ifFalse: "if optimized this isn't an actual scope"
  [rootNode noteBlockExit:
  [:exitNumber|
  blockExtent := blockStart to: exitNumber]].
 
  "Now that the analysis is done move any temps that need to be moved."
  self postNumberingProcessTempsWithin: effectiveScope rootNode: rootNode.
 
  "This is simply a nicety for compiler developers..."
  temporaries do:
  [:temp|
  (temp isIndirectTempVector and: [temp name includes: $?]) ifTrue:
  [temp name: temp definingScope remoteTempNodeName]]!

Item was changed:
+ ----- Method: BlockNode>>blockExtent (in category 'closure analysis') -----
- ----- Method: BlockNode>>blockExtent (in category 'code generation (closures)') -----
  blockExtent "^<Interval>"
  ^blockExtent!

Item was removed:
- ----- Method: BlockNode>>closureCreationNode (in category 'accessing') -----
- closureCreationNode
- closureCreationNode ifNil:
- [closureCreationNode := LeafNode new
- key: #closureCreationNode
- code: nil].
- ^closureCreationNode!

Item was changed:
+ ----- Method: BlockNode>>computeCopiedValues: (in category 'closure analysis') -----
- ----- Method: BlockNode>>computeCopiedValues: (in category 'code generation (closures)') -----
  computeCopiedValues: rootNode
  | referencedValues |
  referencedValues := rootNode referencedValuesWithinBlockExtent: blockExtent.
  ^(referencedValues reject: [:temp| temp isDefinedWithinBlockExtent: blockExtent])
  asArray sort: ParseNode tempSortBlock!

Item was changed:
+ ----- Method: BlockNode>>constructClosureCreationNode: (in category 'code generation') -----
- ----- Method: BlockNode>>constructClosureCreationNode: (in category 'code generation (closures)') -----
  constructClosureCreationNode: encoder
  copiedValues := self computeCopiedValues: encoder rootNode.
+ ^self ensureClosureCreationNode!
- encoder supportsClosureOpcodes ifTrue:
- [^self closureCreationNode].
- "Without the bytecode we can still get by."
- ^MessageNode new
- receiver: (encoder encodeVariable: 'thisContext')
- selector: #closureCopy:copiedValues:
- arguments: (Array
- with: (encoder encodeLiteral: arguments size)
- with: (copiedValues isEmpty
- ifTrue: [NodeNil]
- ifFalse: [BraceNode new elements: copiedValues]))
- precedence: 3
- from: encoder!

Item was changed:
+ ----- Method: BlockNode>>deoptimize (in category 'closure analysis') -----
- ----- Method: BlockNode>>deoptimize (in category 'code generation (closures)') -----
  deoptimize
  optimized := false.
  optimizedMessageNode := nil!

Item was removed:
- ----- Method: BlockNode>>emitCodeForClosureValue:encoder: (in category 'code generation (closures)') -----
- emitCodeForClosureValue: stack encoder: encoder
- "if not supportsClosureOpcodes closureCreationSupportNode is the
- node for thisContext closureCopy: numArgs [ copiedValues: { values } ]"
- encoder supportsClosureOpcodes
- ifTrue:
- [copiedValues do:
- [:copiedValue| copiedValue emitCodeForValue: stack encoder: encoder].
- closureCreationNode pc: encoder methodStreamPosition + 1.
- encoder
- genPushClosureCopyNumCopiedValues: copiedValues size
- numArgs: arguments size
- jumpSize: size.
- stack
- pop: copiedValues size;
- push: 1]
- ifFalse:
- [closureCreationNode emitCodeForValue: stack encoder: encoder.
- encoder genJumpLong: size]. "Force a two byte jump."
- "Emit the body of the block"
- self emitCodeForEvaluatedClosureValue: stack encoder: encoder!

Item was changed:
+ ----- Method: BlockNode>>emitCodeForEvaluatedClosureValue:encoder: (in category 'code generation') -----
- ----- Method: BlockNode>>emitCodeForEvaluatedClosureValue:encoder: (in category 'code generation (closures)') -----
  emitCodeForEvaluatedClosureValue: stack encoder: encoder
  | position |
  position := stack position.
  stack position: arguments size + temporaries size + copiedValues size.
  encoder genPushNClosureTemps: temporaries size.
  self
  reindexingLocalsDo: [self emitCodeForEvaluatedValue: stack encoder: encoder]
  encoder: encoder.
  self returns ifFalse:
  [encoder genReturnTopToCaller.
  pc := encoder methodStreamPosition].
  stack position: position!

Item was changed:
  ----- Method: BlockNode>>emitCodeForValue:encoder: (in category 'code generation') -----
  emitCodeForValue: stack encoder: encoder
+ copiedValues do:
+ [:copiedValue| copiedValue emitCodeForValue: stack encoder: encoder].
+ closureCreationNode pc: encoder methodStreamPosition + 1.
+ encoder
+ genPushClosureCopyNumCopiedValues: copiedValues size
+ numArgs: arguments size
+ jumpSize: size.
+ stack
+ pop: copiedValues size;
+ push: 1.
+ "Emit the body of the block"
+ self emitCodeForEvaluatedClosureValue: stack encoder: encoder!
-
- self generateAsClosure ifTrue:
- [^self emitCodeForClosureValue: stack encoder: encoder].
- encoder genPushThisContext.
- stack push: 1.
- nArgsNode emitCodeForValue: stack encoder: encoder.
- remoteCopyNode
- emitCode: stack
- args: 1
- encoder: encoder.
- "Force a two byte jump."
- encoder genJumpLong: size.
- stack push: arguments size.
- arguments reverseDo: [:arg | arg emitCodeForStorePop: stack encoder: encoder].
- self emitCodeForEvaluatedValue: stack encoder: encoder.
- self returns ifFalse:
- [encoder genReturnTopToCaller.
- pc := encoder methodStreamPosition].
- stack pop: 1!

Item was added:
+ ----- Method: BlockNode>>ensureClosureCreationNode (in category 'accessing') -----
+ ensureClosureCreationNode
+ closureCreationNode ifNil:
+ [closureCreationNode := LeafNode new
+ key: #closureCreationNode
+ code: nil].
+ ^closureCreationNode!

Item was removed:
- ----- Method: BlockNode>>generateAsClosure (in category 'testing') -----
- generateAsClosure
- "Answer if we're compiling under the closure regime.  If blockExtent has been set by
- analyseTempsWithin:rootNode: et al then we're compiling under the closure regime."
- ^blockExtent ~~ nil!

Item was changed:
+ ----- Method: BlockNode>>ifHasRemoteTempNodeEnsureInitializationStatementExists: (in category 'closure analysis') -----
- ----- Method: BlockNode>>ifHasRemoteTempNodeEnsureInitializationStatementExists: (in category 'code generation (closures)') -----
  ifHasRemoteTempNodeEnsureInitializationStatementExists: rootNode
  "If a remoteTempNode has been added ensure a statement exists to initialize it."
  remoteTempNode ~~ nil ifTrue:
  [(statements notEmpty
   and: [statements first isAssignmentNode
   and: [statements first variable isTemp
   and: [statements first variable isIndirectTempVector]]])
  ifTrue: "If this is a decompiled tree, or if a temporary has been added later in
  the analysis then there already is a temp vector initialization node."
  [(statements first variable ~~ remoteTempNode) ifTrue:
  [statements first variable become: remoteTempNode].
  statements first value numElements: remoteTempNode remoteTemps size]
  ifFalse:
  [statements addFirst: (remoteTempNode nodeToInitialize: rootNode encoder)]].!

Item was changed:
+ ----- Method: BlockNode>>makeTemporariesRemovable (in category 'closure analysis') -----
- ----- Method: BlockNode>>makeTemporariesRemovable (in category 'code generation (closures)') -----
  makeTemporariesRemovable
  "Utilities for when we want to remove some temporaries."
 
  temporaries isArray ifTrue:
  [temporaries := temporaries asOrderedCollection].!

Item was changed:
+ ----- Method: BlockNode>>nilReadBeforeWrittenTemps (in category 'closure analysis') -----
- ----- Method: BlockNode>>nilReadBeforeWrittenTemps (in category 'code generation (closures)') -----
  nilReadBeforeWrittenTemps
  | visitor readBeforeWritten |
  temporaries isEmpty ifTrue:
  [^self].
  self accept: (visitor := OptimizedBlockLocalTempReadBeforeWrittenVisitor new).
  readBeforeWritten := visitor readBeforeWritten.
  temporaries reverseDo:
  [:temp|
  ((readBeforeWritten includes: temp)
  and: [temp isRemote not]) ifTrue:
  [statements addFirst: (AssignmentNode new variable: temp value: NodeNil)]]!

Item was changed:
+ ----- Method: BlockNode>>noteOptimizedIn: (in category 'closure analysis') -----
- ----- Method: BlockNode>>noteOptimizedIn: (in category 'code generation (closures)') -----
  noteOptimizedIn: anOptimizedMessageNode
  optimized := true.
  optimizedMessageNode := anOptimizedMessageNode!

Item was changed:
  ----- Method: BlockNode>>noteSourceRangeStart:end:encoder: (in category 'initialize-release') -----
  noteSourceRangeStart: start end: end encoder: encoder
  "Note two source ranges for this node.  One is for the debugger
  and is of the last expression, the result of the block.  One is for
  source analysis and is for the entire block."
  encoder
  noteSourceRange: (start to: end)
+ forNode: self ensureClosureCreationNode.
- forNode: self closureCreationNode.
  startOfLastStatement
  ifNil:
  [encoder
  noteSourceRange: (start to: end)
  forNode: self]
  ifNotNil:
  [encoder
  noteSourceRange: (startOfLastStatement to: end - 1)
  forNode: self]!

Item was changed:
+ ----- Method: BlockNode>>optimizedBlockHoistTempsInto: (in category 'closure analysis') -----
- ----- Method: BlockNode>>optimizedBlockHoistTempsInto: (in category 'code generation (closures)') -----
  optimizedBlockHoistTempsInto: scopeBlock "<BlockNode>"
  "This is a No-op for all nodes except non-optimized BlockNodes."
  "Let's assume the special > 0 guard in MessageNode>>analyseTempsWithin:forValue:encoder: is correct.
  Then we can simply hoist our temps up."
  self assert: (arguments isNil or: [arguments size <= 1]).
  (arguments notNil and: [arguments notEmpty]) ifTrue:
  [scopeBlock addHoistedTemps: arguments.
  arguments := #()].
  temporaries notEmpty ifTrue:
  [scopeBlock addHoistedTemps: temporaries.
  temporaries := #()]!

Item was changed:
+ ----- Method: BlockNode>>postNumberingProcessTempsWithin:rootNode: (in category 'closure analysis') -----
- ----- Method: BlockNode>>postNumberingProcessTempsWithin:rootNode: (in category 'code generation (closures)') -----
  postNumberingProcessTempsWithin: scopeBlock "<BlockNode>" rootNode: rootNode "<MethodNode>"
  "A temp can be local (and copied) if it is not written to after it is captured.
  A temp cannot be local if it is written to remotely.
  Need to enumerate a copy of the temporaries because any temps becoming remote
  will be removed from temporaries in analyseClosure: (and a single remote temp node
  will get added)"
  temporaries copy do:
  [:each|
  each isIndirectTempVector ifFalse:
  [each analyseClosure: rootNode]].
 
  "If this is an optimized node we need to hoist temporaries up into the relevant block scope."
  optimized ifTrue:
  [self optimizedBlockHoistTempsInto: scopeBlock].
 
  "Now we may have added a remoteTempNode.  So we need a statement to initialize it."
  self ifHasRemoteTempNodeEnsureInitializationStatementExists: rootNode.
 
  "Now add all arguments and locals to the pool so that copiedValues can be computed during sizing."
  rootNode
  addLocalsToPool: arguments;
  addLocalsToPool: temporaries!

Item was changed:
+ ----- Method: BlockNode>>reindexingLocalsDo:encoder: (in category 'closure analysis') -----
- ----- Method: BlockNode>>reindexingLocalsDo:encoder: (in category 'code generation (closures)') -----
  reindexingLocalsDo: aBlock encoder: encoderOrNil
  "Evaluate aBlock wih arguments, temporaries and copiedValues reindexed for
  their positions within the receiver's block, restoring the correct indices afterwards.
  If encoder is not nil remember the temps for this block's extent."
  | tempIndices result tempsToReindex |
  self assert: copiedValues notNil.
  tempsToReindex := arguments asArray, copiedValues, temporaries.
  tempIndices := tempsToReindex collect: [:temp| temp index].
  tempsToReindex withIndexDo:
  [:temp :newIndex| temp index: newIndex - 1. self assert: temp index + 1 = newIndex].
  encoderOrNil ifNotNil:
  [encoderOrNil noteBlockExtent: blockExtent hasLocals: tempsToReindex].
  result := aBlock ensure:
  ["Horribly pragmatic hack.  The copiedValues will have completely
   unrelated indices within the closure method and sub-method.
   Avoiding the effort of rebinding temps in the inner scope simply
   update the indices to their correct ones during the generation of
   the closure method and restore the indices immedately there-after."
  tempsToReindex with: tempIndices do:
  [:temp :oldIndex| temp index: oldIndex. self assert: temp index = oldIndex]].
  ^result!

Item was changed:
+ ----- Method: BlockNode>>remoteTempNodeName (in category 'closure analysis') -----
- ----- Method: BlockNode>>remoteTempNodeName (in category 'code generation (closures)') -----
  remoteTempNodeName
  "Answer a useful name for a RemoteTempVectorNode in the receiver."
  | prefix scope extent |
  prefix := actualScopeIfOptimized ifNil: ['<'] ifNotNil: [ '<...'].
  scope := self.
  [extent := scope blockExtent.
  extent == nil
  and: [scope actualScope ~~ scope]] whileTrue:
  [scope := scope actualScope].
  ^extent
  ifNil: [prefix, '?-?>']
  ifNotNil:
  [prefix, extent first printString, '-',
  (extent last isZero
  ifTrue: ['?']
  ifFalse: [extent last printString]), '>']!

Item was changed:
+ ----- Method: BlockNode>>removeTempNode:ifAbsent: (in category 'closure analysis') -----
- ----- Method: BlockNode>>removeTempNode:ifAbsent: (in category 'code generation (closures)') -----
  removeTempNode: aTempVariableNode ifAbsent: aBlock
  "Utilities for when we want to remove some temporaries."
 
  self makeTemporariesRemovable.
  ^temporaries remove: aTempVariableNode ifAbsent: aBlock
  !

Item was removed:
- ----- Method: BlockNode>>sizeCodeForClosureValue: (in category 'code generation (closures)') -----
- sizeCodeForClosureValue: encoder
- "Compute the size for the creation of the block and its code."
- "If we have the closure bytecodes constructClosureCreationNode: will note
- the copied values in the copiedValues inst var and answer #pushCopiedValues."
- closureCreationNode := self constructClosureCreationNode: encoder.
- "Remember size of body for emit time so we know the size of the jump around it."
- size := self sizeCodeForEvaluatedClosureValue: encoder.
- ^encoder supportsClosureOpcodes
- ifTrue:
- [(copiedValues inject: 0 into: [:sum :node| sum + (node sizeCodeForValue: encoder)])
- + (encoder sizePushClosureCopyNumCopiedValues: copiedValues size numArgs: arguments size jumpSize: size)
- + size]
- ifFalse:
- ["closureCreationSupportNode is send closureCopy:copiedValues:"
- (closureCreationNode sizeCodeForValue: encoder)
- + (encoder sizeJumpLong: size)
- + size]!

Item was changed:
+ ----- Method: BlockNode>>sizeCodeForEvaluatedClosureValue: (in category 'code generation') -----
- ----- Method: BlockNode>>sizeCodeForEvaluatedClosureValue: (in category 'code generation (closures)') -----
  sizeCodeForEvaluatedClosureValue: encoder
  "The closure value primitives push the arguments and the copied values.
  The compiler guarantees that any copied values come before all local temps.
  So on closure activation we only need to push nils for the remaining temporaries."
  ^(encoder sizePushNClosureTemps: temporaries size)
  + (self
  reindexingLocalsDo: [self sizeCodeForEvaluatedValue: encoder]
  encoder: nil "don't store temps yet")
  + (self returns ifTrue: [0] ifFalse: [encoder sizeReturnTopToCaller])!

Item was changed:
  ----- Method: BlockNode>>sizeCodeForValue: (in category 'code generation') -----
  sizeCodeForValue: encoder
+ "Compute the size for the creation of the block and its code."
+ copiedValues := self computeCopiedValues: encoder rootNode.
+ self ensureClosureCreationNode.
+ "Remember size of body for emit time so we know the size of the jump around it."
+ size := self sizeCodeForEvaluatedClosureValue: encoder.
+ ^(copiedValues inject: 0 into: [:sum :node| sum + (node sizeCodeForValue: encoder)])
+  + (encoder sizePushClosureCopyNumCopiedValues: copiedValues size numArgs: arguments size jumpSize: size)
+  + size!
- self generateAsClosure ifTrue:
- [^self sizeCodeForClosureValue: encoder].
-
- nArgsNode := encoder encodeLiteral: arguments size.
- remoteCopyNode := encoder encodeSelector: #blockCopy:.
- size := self sizeCodeForEvaluatedValue: encoder.
- self returns ifFalse:
- [size := size + encoder sizeReturnTopToCaller]. "endBlock"
- arguments := arguments collect:  "Chance to prepare debugger remote temps"
- [:arg | arg asStorableNode: encoder].
- arguments do: [:arg | size := size + (arg sizeCodeForStorePop: encoder)].
- ^encoder sizePushThisContext
- + (nArgsNode sizeCodeForValue: encoder)
- + (remoteCopyNode sizeCode: encoder args: 1 super: false)
- + (encoder sizeJumpLong: size)
- + size!

Item was changed:
+ ----- Method: BraceNode>>analyseTempsWithin:rootNode:assignmentPools: (in category 'closure analysis') -----
- ----- Method: BraceNode>>analyseTempsWithin:rootNode:assignmentPools: (in category 'code generation (closures)') -----
  analyseTempsWithin: scopeBlock "<BlockNode>" rootNode: rootNode "<MethodNode>" assignmentPools: assignmentPools "<Dictionary>"
  elements do:
  [:node|
  node analyseTempsWithin: scopeBlock rootNode: rootNode assignmentPools: assignmentPools]!

Item was changed:
+ ----- Method: BraceNode>>elements (in category 'code generation') -----
- ----- Method: BraceNode>>elements (in category 'code generation (closures)') -----
  elements
  ^elements!

Item was changed:
  ----- Method: BraceNode>>emitCodeForValue:encoder: (in category 'code generation') -----
  emitCodeForValue: stack encoder: encoder
+ "Hack; when sizing we have no way of knowing how much stack space is available."
+ elements size <= self maxElementsForConsArray ifTrue:
-
- (encoder supportsClosureOpcodes
- "Hack; we have no way of knowing how much stack space is available"
- and: [elements size <= self maxElementsForConsArray]) ifTrue:
  [elements do: [:node| node emitCodeForValue: stack encoder: encoder].
  encoder genPushConsArray: elements size.
  stack
  pop: elements size;
  push: 1.
  ^self].
  ^emitNode emitCodeForValue: stack encoder: encoder!

Item was removed:
- ----- Method: BraceNode>>matchBraceWithReceiver:selector:arguments: (in category 'initialize-release') -----
- matchBraceWithReceiver: receiver selector: selector arguments: arguments
-
- selector = (self selectorForShortForm: arguments size)
- ifFalse: [^ nil "no match"].
-
- "Appears to be a short form brace construct"
- self elements: arguments!

Item was changed:
+ ----- Method: BraceNode>>maxElementsForConsArray (in category 'code generation') -----
- ----- Method: BraceNode>>maxElementsForConsArray (in category 'code generation (closures)') -----
  maxElementsForConsArray
  "Hack; we have no way of knowing how much stack space is available during sizing"
  ^8!

Item was removed:
- ----- Method: BraceNode>>selectorForShortForm: (in category 'code generation') -----
- selectorForShortForm: nElements
-
- nElements > 4 ifTrue: [^ nil].
- ^ #(braceWithNone braceWith: braceWith:with:
- braceWith:with:with: braceWith:with:with:with:) at: nElements + 1!

Item was changed:
  ----- Method: BraceNode>>sizeCodeForValue: (in category 'code generation') -----
  sizeCodeForValue: encoder
 
+ "Hack; we have no way of knowing how much stack space is available."
+ elements size <= self maxElementsForConsArray ifTrue:
- (encoder supportsClosureOpcodes
- "Hack; we have no way of knowing how much stack space is available"
- and: [elements size <= self maxElementsForConsArray]) ifTrue:
  [^(elements inject: 0 into: [:sum :node| sum + (node sizeCodeForValue: encoder)])
   + (encoder sizePushConsArray: elements size)].
+ "Long form: (Array braceStream: N) nextPut: a; nextPut: b; ...; braceArray"
+ emitNode := CascadeNode new
- emitNode := elements size <= 4
- ifTrue: ["Short form: Array braceWith: a with: b ... "
- MessageNode new
- receiver: (encoder encodeVariable: #Array)
- selector: (self selectorForShortForm: elements size)
- arguments: elements precedence: 3 from: encoder]
- ifFalse: ["Long form: (Array braceStream: N) nextPut: a; nextPut: b; ...; braceArray"
- CascadeNode new
  receiver: (MessageNode new
  receiver: (encoder encodeVariable: #Array)
  selector: #braceStream:
+ arguments: {encoder encodeLiteral: elements size}
- arguments: (Array with: (encoder encodeLiteral: elements size))
  precedence: 3 from: encoder)
+ messages: ((elements collect: [:elt |
+ MessageNode new
+ receiver: nil
+ selector: #nextPut:
+ arguments: {elt}
+ precedence: 3
+ from: encoder])
+ copyWith: (MessageNode new
+ receiver: nil
+ selector: #braceArray
+ arguments: #()
+ precedence: 1
+ from: encoder)).
- messages: ((elements collect: [:elt | MessageNode new receiver: nil
- selector: #nextPut:
- arguments: (Array with: elt)
- precedence: 3 from: encoder])
- copyWith: (MessageNode new receiver: nil
- selector: #braceArray
- arguments: (Array new)
- precedence: 1 from: encoder))].
  ^emitNode sizeCodeForValue: encoder!

Item was changed:
  ----- Method: BytecodeEncoder class>>pushNewArrayCode (in category 'bytecode decoding') -----
  pushNewArrayCode
+ "Answer the pushNewArray bytecode, if it exists in the encoder's bytecode set, or nil if not."
- "Answer the pushNewArray bytecode, if it exists in the encoder's byetcode set, or nil if not."
  ^nil!

Item was added:
+ ----- Method: BytecodeEncoder class>>pushNilCode (in category 'bytecode decoding') -----
+ pushNilCode
+ "Answer the pushNil bytecode."
+ ^self subclassResponsibility!

Item was added:
+ ----- Method: BytecodeEncoder class>>stackDeltaForPrimitive:in: (in category 'bytecode decoding') -----
+ stackDeltaForPrimitive: primitiveIndex in: method
+ "This is the default implementation.  Subclasses with inline primitives will need to override."
+ ^0!

Item was changed:
  ----- Method: BytecodeEncoder>>bindBlockArg:within: (in category 'temps') -----
  bindBlockArg: name within: aBlockNode
- "Read the comment in the superclass's method.
- If we have closures we should check the argument
- count against the block, not the method.
-
- (Note that this isn't entirely adequate either since optimized blocks
- will slip through the cracks (their arguments (i.e. ifNotNil: [:expr|)
- are charged against their enclosing block, not themselves))."
  | nArgs |
- self supportsClosureOpcodes ifFalse:
- [^super bindBlockArg: name within: aBlockNode].
  (nArgs := aBlockNode nArgsSlot) isNil ifTrue:
  [aBlockNode nArgsSlot: (nArgs := 0)].
+ nArgs >= 15 ifTrue:
- nArgs  >= 15 ifTrue:
  [^self notify: 'Too many arguments'].
  aBlockNode nArgsSlot: nArgs + 1.
  ^(self bindTemp: name)
  beBlockArg;
  nowHasDef;
  nowHasRef;
  yourself!

Item was changed:
  ----- Method: BytecodeEncoder>>bindBlockTemp:within: (in category 'temps') -----
  bindBlockTemp: name within: aBlockNode
- "Read the comment in the superclass's bindBlockArg:within: method.
- If we have closures we should check the argument
- count against the block, not the method.
-
- (Note that this isn't entirely adequate either since optimized blocks
- will slip through the cracks (their arguments (i.e. ifNotNil: [:expr|)
- are charged against their enclosing block, not themselves))."
  | nArgs |
+ (nArgs := aBlockNode nArgsSlot) ifNil:
- self supportsClosureOpcodes ifFalse:
- [^super bindBlockTemp: name within: aBlockNode].
- (nArgs := aBlockNode nArgsSlot) isNil ifTrue:
  [aBlockNode nArgsSlot: (nArgs := 0)].
  nArgs >= (CompiledMethod fullFrameSize - 1) ifTrue:
  [^self notify: 'Too many temporaries'].
  aBlockNode nArgsSlot: nArgs + 1.
  ^self bindTemp: name!

Item was changed:
  ----- Method: BytecodeEncoder>>bindTemp: (in category 'temps') -----
  bindTemp: name
+ "Declare a temporary; error not if a field or class variable or out-of-scope temp."
- "Declare a temporary; error not if a field or class variable or out-of-scope temp.
- Read the comment in Encoder>>bindBlockArg:within: and subclass implementations."
- self supportsClosureOpcodes ifFalse:
- [^super bindTemp: name].
  scopeTable at: name ifPresent:
  [:node|
  "When non-interactive raise the error only if it is a duplicate"
  node isTemp
  ifTrue:[node scope >= 0 ifTrue:
  [^self notify: 'Name already used in this method']]
  ifFalse:[self warnAboutShadowed: name]].
  ^self reallyBind: name!

Item was added:
+ ----- Method: BytecodeEncoder>>genPushNClosureTemps: (in category 'bytecode generation') -----
+ genPushNClosureTemps: numTemps
+ "To reduce the number of bytecodes required, the embedded
+ block closure implementation uses explicit push nil instructions
+ to create block-local temps.  In bytecode sets supporting
+ FullBlockClosure/CompiledBlock this isn't needed and the
+ number of temps is derived from the block method header."
+ numTemps timesRepeat: [self genPushSpecialLiteral: nil]!

Item was added:
+ ----- Method: BytecodeEncoder>>sizeSendDirectedSuper:numArgs: (in category 'opcode sizing') -----
+ sizeSendDirectedSuper: selectorLiteralIndex numArgs: numArgs
+ ^self sizeOpcodeSelector: #genSendDirectedSuper:numArgs: withArguments: {selectorLiteralIndex. numArgs}!

Item was added:
+ ----- Method: BytecodeEncoder>>sizeTrapIfNotInstanceOf: (in category 'opcode sizing') -----
+ sizeTrapIfNotInstanceOf: litIndex
+ ^self sizeOpcodeSelector: #genTrapIfNotInstanceOf: withArguments: {litIndex}!

Item was removed:
- ----- Method: BytecodeEncoder>>supportsClosureOpcodes (in category 'testing') -----
- supportsClosureOpcodes
- "Answer if the receiver supports the
- genPushNewArray:/genPushConsArray:
- genPushRemoteTemp:inVectorAt:
- genStoreRemoteTemp:inVectorAt:
- genStorePopRemoteTemp:inVectorAt:
- genPushClosureCopyCopiedValues:numArgs:jumpSize:
- opcodes"
- ^false!

Item was added:
+ ----- Method: BytecodeEncoder>>supportsFullBlocks (in category 'testing') -----
+ supportsFullBlocks
+ "Answer if the instruction set supports full closures (closure creation from
+ specfic methods instead of bytecodes embedded in an outer home method)."
+
+ ^self subclassResponsibility!

Item was changed:
+ ----- Method: CascadeNode>>analyseTempsWithin:rootNode:assignmentPools: (in category 'closure analysis') -----
- ----- Method: CascadeNode>>analyseTempsWithin:rootNode:assignmentPools: (in category 'code generation (closures)') -----
  analyseTempsWithin: scopeBlock "<BlockNode>" rootNode: rootNode "<MethodNode>" assignmentPools: assignmentPools "<Dictionary>"
  { receiver }, messages do:
  [:node| node analyseTempsWithin: scopeBlock rootNode: rootNode assignmentPools: assignmentPools]!

Item was removed:
- ----- Method: CompilationCue>>literalScannedAs:notifying: (in category 'binding') -----
- literalScannedAs: anObject notifying: anEncoder
- ^ class literalScannedAs: anObject environment: environment notifying: anEncoder!

Item was changed:
  InstructionStream subclass: #Decompiler
+ instanceVariableNames: 'constructor method instVars tempVars constTable stack statements lastPc exit caseExits lastJumpPc lastReturnPc limit hasValue blockStackBase numLocalTemps blockStartsToTempVars tempVarCount lastJumpIfPcStack tempReadCounts'
- instanceVariableNames: 'constructor method instVars tempVars constTable stack statements lastPc exit caseExits lastJumpPc lastReturnPc limit hasValue blockStackBase numLocalTemps blockStartsToTempVars tempVarCount lastJumpIfPcStack'
  classVariableNames: 'ArgumentFlag CascadeFlag CaseFlag IfNilFlag'
  poolDictionaries: ''
  category: 'Compiler-Kernel'!
 
  !Decompiler commentStamp: 'nice 2/3/2011 22:54' prior: 0!
  I decompile a method in three phases:
  Reverser: postfix byte codes -> prefix symbolic codes (nodes and atoms)
  Parser: prefix symbolic codes -> node tree (same as the compiler)
  Printer: node tree -> text (done by the nodes)
 
 
  instance vars:
 
  constructor <DecompilerConstructor> an auxiliary knowing how to generate Abstract Syntax Tree (node tree)
  method <CompiledMethod> the method being decompiled
  instVars <Array of: String> the instance variables of the class implementing method
  tempVars <String | (OrderedCollection of: String)> hold the names of temporary variables (if known)
  NOTE: POLYMORPHISM WILL BE RESOLVED IN #initSymbols:
  constTable <Collection of: ParseNode> parse node associated with byte encoded constants (nil true false 0 1 -1 etc...)
  stack <OrderedCollection of: (ParseNode | String | Integer) > multipurpose...
  statements <OrderedCollection of: ParseNode> the statements of the method being decompiled
  lastPc <Integer>
  exit <Integer>
  caseExits <OrderedCollection of: Integer> - stack of exit addresses that have been seen in the branches of caseOf:'s
  lastJumpPc <Integer>
  lastReturnPc <Integer>
  limit <Integer>
  hasValue <Boolean>
  blockStackBase <Integer>
  numLocaltemps <Integer | Symbol> - number of temps local to a block; also a flag indicating decompiling a block
  blockStartsToTempVars <Dictionary key: Integer value: (OrderedCollection of: String)>
  tempVarCount <Integer> number of temp vars used by the method
  lastJumpIfPcStack <OrderedCollection of: Integer> the value of program counter just before the last encountered conditional jumps!

Item was added:
+ ----- Method: Decompiler>>blockReturnConstant: (in category 'instruction decoding') -----
+ blockReturnConstant: value
+
+ self pushConstant: value; blockReturnTop!

Item was removed:
- ----- Method: Decompiler>>blockScopeRefersOnlyOnceToTemp: (in category 'private') -----
- blockScopeRefersOnlyOnceToTemp: offset
- | nRefs byteCode extension scanner scan |
- scanner := InstructionStream on: method.
- nRefs := 0.
- scan := offset <= 15
- ifTrue:
- [byteCode := 16 + offset.
- [:instr |
-  instr = byteCode ifTrue:
- [nRefs := nRefs + 1].
-  nRefs > 1]]
- ifFalse:
- [extension := 64 + offset.
- [:instr |
-  (instr = 128 and: [scanner followingByte = extension]) ifTrue:
- [nRefs := nRefs + 1].
-   nRefs > 1]].
- self scanBlockScopeFor: pc from: method initialPC to: method endPC with: scan scanner: scanner.
- ^nRefs = 1!

Item was removed:
- ----- Method: Decompiler>>convertToDoLoop (in category 'private') -----
- convertToDoLoop
- "If statements contains the pattern
- var := startExpr.
- [var <= limit] whileTrue: [...statements... var := var + incConst]
- then replace this by
- startExpr to: limit by: incConst do: [:var | ...statements...]"
- | leaveOnStack initStmt toDoStmt limitStmt |
- leaveOnStack := false.
- (stack notEmpty
- and: [stack last isAssignmentNode])
- ifTrue:
- [initStmt := stack last.
- (toDoStmt := statements last toDoFromWhileWithInit: initStmt) ifNil:
- [^self].
- stack removeLast.
- statements removeLast; addLast: toDoStmt.
- leaveOnStack := true]
- ifFalse:
- [statements size < 2 ifTrue:
- [^self].
- initStmt := statements at: statements size-1.
- (toDoStmt := statements last toDoFromWhileWithInit: initStmt) ifNil:
- [^self].
- statements removeLast; removeLast; addLast: toDoStmt].
- initStmt variable scope: -1.  "Flag arg as block temp"
-
- "Attempt further conversion of the pattern
- limitVar := limitExpr.
- startExpr to: limitVar by: incConst do: [:var | ...statements...]
- to
- startExpr to: limitExpr by: incConst do: [:var | ...statements...].
- The complication here is that limitVar := limitExpr's value may be used, in which case it'll
- be statements last, or may not be used, in which case it'll be statements nextToLast."
- statements size < 2 ifTrue:
- [leaveOnStack ifTrue:
- [stack addLast: statements removeLast].
- ^self].
- limitStmt := statements last.
- ((limitStmt isMemberOf: AssignmentNode)
- and: [limitStmt variable isTemp
- and: [limitStmt variable == toDoStmt arguments first]]) ifFalse:
- [limitStmt := statements at: statements size-1.
- ((limitStmt isMemberOf: AssignmentNode)
- and: [limitStmt variable isTemp
- and: [limitStmt variable == toDoStmt arguments first]]) ifFalse:
- [leaveOnStack ifTrue:
- [stack addLast: statements removeLast].
- ^self]].
-
- (self blockScopeRefersOnlyOnceToTemp: limitStmt variable fieldOffset) ifFalse:
- [^self].
- toDoStmt arguments at: 1 put: limitStmt value.
- limitStmt variable scope: -2.  "Flag limit var so it won't print"
- statements last == limitStmt
- ifTrue: [statements removeLast]
- ifFalse: [statements removeLast; removeLast; addLast: toDoStmt]!

Item was added:
+ ----- Method: Decompiler>>convertToDoLoop: (in category 'private') -----
+ convertToDoLoop: blockBodyTempCounts
+ "If statements contains the pattern
+ var := startExpr.
+ [var <= limit] whileTrue: [...statements... var := var + incConst]
+ or
+ var := startExpr.
+ limit := limitExpr.
+ [var <= limit] whileTrue: [...statements... var := var + incConst]
+ then replace this by
+ startExpr to: limit by: incConst do: [:var | ...statements...]
+ and answer true."
+ | whileStmt incrStmt initStmt limitStmt toDoStmt |
+ whileStmt := statements last.
+ incrStmt := whileStmt arguments first statements last.
+ incrStmt isAssignmentNode ifFalse:
+ [^false].
+ (self startAndLimitFor: incrStmt variable from: stack into:
+ [:startExpr :limitExpr| initStmt := startExpr. limitStmt := limitExpr])
+ ifTrue:
+ [| limitInStatements |
+ limitInStatements := limitStmt isNil
+    and: [statements size > 1
+    and: [self startAndLimitFor: incrStmt variable from: { stack last. (statements last: 2) first } into:
+ [:startExpr :limitExpr| limitStmt := limitExpr]]].
+ (toDoStmt := statements last toDoFromWhileWithCounts: blockBodyTempCounts init: initStmt limit: limitStmt) ifNil:
+ [^false].
+ limitInStatements
+ ifTrue:
+ [stack
+ removeLast;
+ addLast: toDoStmt.
+ statements removeLast: 2]
+ ifFalse:
+ [stack
+ removeLast: (limitStmt ifNil: [1] ifNotNil: [2]);
+ addLast: toDoStmt.
+ statements removeLast]]
+ ifFalse:
+ [(self startAndLimitFor: incrStmt variable from: statements allButLast into:
+ [:startExpr :limitExpr| initStmt := startExpr. limitStmt := limitExpr]) ifFalse:
+ [^false].
+ (toDoStmt := statements last toDoFromWhileWithCounts: blockBodyTempCounts init: initStmt limit: limitStmt) ifNil:
+ [^false].
+ statements
+ removeLast: (limitStmt ifNil: [2] ifNotNil: [3]);
+ addLast: toDoStmt].
+ self markTemp: initStmt variable asOutOfScope: -1. "Flag arg as out of scope"
+ initStmt variable beBlockArg.
+ limitStmt ifNotNil:
+ [self markTemp: limitStmt variable asOutOfScope: -2.
+ toDoStmt arguments at: 1 put: limitStmt value]. "Flag limit as hidden"
+ ^true!

Item was changed:
  ----- Method: Decompiler>>decompileBlock: (in category 'public access') -----
  decompileBlock: aBlock
  "Decompile aBlock, returning the result as a BlockNode.  
  Show temp names from source if available."
  "Decompiler new decompileBlock: [3 + 4]"
  | startpc end homeClass blockNode methodNode home |
+ (home := aBlock home) ifNil: [^nil].
+ (homeClass := home methodClass) == #unknown ifTrue: [^nil].
+ method := aBlock method.
- (home := aBlock home) ifNil: [^ nil].
- method := home method.
- (homeClass := home methodClass) == #unknown ifTrue: [^ nil].
  aBlock isClosure ifTrue:
  [(methodNode := method decompileWithTemps)
  ifNil: [^nil]
  ifNotNil: [methodNode nodesDo: [:node| node pc = aBlock startpc ifTrue: [^node]]].
  ^self error: 'cannot find block node matching aBlock'].
  constructor := self constructorForMethod: aBlock method.
 
  self withTempNames: method methodNode tempNames.
 
  self initSymbols: homeClass.
  startpc := aBlock startpc.
  end := aBlock endPC.
  stack := OrderedCollection new: method frameSize.
  lastJumpIfPcStack := OrderedCollection new.
  caseExits := OrderedCollection new.
  statements := OrderedCollection new: 20.
  super method: method pc: startpc - 5.
  blockNode := self blockTo: end.
  stack isEmpty ifFalse: [self error: 'stack not empty'].
  ^blockNode statements first!

Item was changed:
  ----- Method: Decompiler>>initSymbols: (in category 'initialize-release') -----
  initSymbols: aClass
  constructor method: method class: aClass literals: method literals.
  constTable := constructor codeConstants.
  instVars := Array new: aClass instSize.
  tempVarCount := method numTemps.
  "(tempVars isNil
  and: [method holdsTempNames]) ifTrue:
  [tempVars := method tempNamesString]."
  tempVars isString
  ifTrue:
  [blockStartsToTempVars := self mapFromBlockStartsIn: method
  toTempVarsFrom: tempVars
  constructor: constructor.
  tempVars := blockStartsToTempVars at: method initialPC]
  ifFalse:
  [| namedTemps |
  namedTemps := tempVars ifNil: [(1 to: tempVarCount) collect: [:i| 't', i printString]].
  tempVars := (1 to: tempVarCount) collect:
  [:i | i <= namedTemps size
  ifTrue: [constructor codeTemp: i - 1 named: (namedTemps at: i)]
  ifFalse: [constructor codeTemp: i - 1]]].
  1 to: method numArgs do:
  [:i|
+ (tempVars at: i) beMethodArg].
+ tempReadCounts := Dictionary new!
- (tempVars at: i) beMethodArg]!

Item was changed:
  ----- Method: Decompiler>>jump:if: (in category 'instruction decoding') -----
  jump: dist if: condition
 
  | savePc sign elsePc elseStart end cond ifExpr thenBlock elseBlock
+  thenJump elseJump condHasValue isIfNil saveStack |
-  thenJump elseJump condHasValue isIfNil saveStack blockBody blockArgs |
  lastJumpIfPcStack addLast: lastPc.
  stack last == CascadeFlag ifTrue: [^ [self case: dist] ensure: [lastJumpIfPcStack removeLast]].
  elsePc := lastPc.
  elseStart := pc + dist.
  end := limit.
  "Check for bfp-jmp to invert condition.
  Don't be fooled by a loop with a null body."
  sign := condition.
  savePc := pc.
  self interpretJump ifNotNil:
  [:elseDist|
  (elseDist >= 0 and: [elseStart = pc]) ifTrue:
  [sign := sign not.  elseStart := pc + elseDist]].
  pc := savePc.
  ifExpr := stack removeLast.
  (isIfNil := stack size > 0 and: [stack last == IfNilFlag]) ifTrue:
  [stack removeLast].
  saveStack := stack.
  stack := OrderedCollection new.
  thenBlock := self blockTo: elseStart.
  condHasValue := hasValue or: [isIfNil].
  "ensure jump is within block (in case thenExpr returns)"
  thenJump := exit <= end ifTrue: [exit] ifFalse: [elseStart].
  "if jump goes back, then it's a loop"
  thenJump < elseStart
  ifTrue:
+ [| blockBody blockArgs savedReadCounts blockBodyReadCounts selector |
+ "Must be a while loop...
- ["Must be a while loop...
   thenJump will jump to the beginning of the while expr.  In the case of while's
   with a block in the condition, the while expr should include more than just
+  the last expression: find all the statements needed by searching for the node
+  with the relevant pc."
-  the last expression: find all the statements needed by re-decompiling."
  stack := saveStack.
+ savedReadCounts := tempReadCounts copy.
  pc := thenJump.
  blockBody := self statementsTo: elsePc.
+ blockBodyReadCounts := tempReadCounts.
+ savedReadCounts keysAndValuesDo:
+ [:temp :count|
+ blockBodyReadCounts at: temp put: (blockBodyReadCounts at: temp) - count].
+ tempReadCounts := savedReadCounts.
  "discard unwanted statements from block"
  blockBody size - 1 timesRepeat: [statements removeLast].
  blockArgs := thenBlock statements = constructor codeEmptyBlock statements
  ifTrue: [#()]
  ifFalse: [{ thenBlock }].
+ selector := blockArgs isEmpty
+ ifTrue: [sign ifTrue: [#whileFalse] ifFalse: [#whileTrue]]
+ ifFalse: [sign ifTrue: [#whileFalse:] ifFalse: [#whileTrue:]].
  statements addLast:
  (constructor
  codeMessage: (constructor codeBlock: blockBody returns: false)
+ selector: (constructor codeSelector: selector code: #macro)
- selector: (constructor
- codeSelector: (blockArgs isEmpty
- ifTrue:
- [sign
- ifTrue: [#whileFalse]
- ifFalse: [#whileTrue]]
- ifFalse:
- [sign
- ifTrue: [#whileFalse:]
- ifFalse: [#whileTrue:]])
- code: #macro)
  arguments: blockArgs).
  pc := elseStart.
+ selector == #whileTrue: ifTrue:
+ [self convertToDoLoop: blockBodyReadCounts]]
- self convertToDoLoop]
  ifFalse:
  ["Must be a conditional..."
  elseBlock := self blockTo: thenJump.
  elseJump := exit.
  "if elseJump is backwards, it is not part of the elseExpr"
  elseJump < elsePc ifTrue:
  [pc := lastPc].
  cond := isIfNil
  ifTrue:
  [constructor
  codeMessage: ifExpr ifNilReceiver
  selector: (constructor
  codeSelector: (sign ifTrue: [#ifNotNil:] ifFalse: [#ifNil:])
  code: #macro)
  arguments: (Array with: thenBlock)]
  ifFalse:
  [constructor
  codeMessage: ifExpr
  selector: (constructor codeSelector: #ifTrue:ifFalse: code: #macro)
  arguments: (sign
  ifTrue: [{elseBlock. thenBlock}]
  ifFalse: [{thenBlock. elseBlock}])].
  stack := saveStack.
  condHasValue
  ifTrue: [stack addLast: cond]
  ifFalse: [statements addLast: cond]].
  lastJumpIfPcStack removeLast.!

Item was added:
+ ----- Method: Decompiler>>markTemp:asOutOfScope: (in category 'private') -----
+ markTemp: tempVarNode asOutOfScope: scopeFlag
+ tempVarNode scope: scopeFlag.
+ tempReadCounts removeKey: tempVarNode ifAbsent: []!

Item was changed:
  ----- Method: Decompiler>>popIntoTemporaryVariable: (in category 'instruction decoding') -----
  popIntoTemporaryVariable: offset
  | maybeTVTag tempVector start |
  maybeTVTag := stack last.
  ((maybeTVTag isMemberOf: Association)
  and: [maybeTVTag key == #pushNewArray]) ifTrue:
  [blockStartsToTempVars notNil "implies we were intialized with temp names."
  ifTrue: "Use the provided temps"
  [self assert: ((tempVector := tempVars at: offset + 1 ifAbsent: [ParseNode basicNew]) isTemp
  and: [tempVector isIndirectTempVector
  and: [tempVector remoteTemps size = maybeTVTag value size]])]
  ifFalse: "Synthesize some remote temps"
  [tempVector := maybeTVTag value.
  offset + 1 <= tempVars size
  ifTrue:
  [start := 2.
  tempVector at: 1 put: (tempVars at: offset + 1)]
  ifFalse:
  [tempVars := (Array new: offset + 1)
  replaceFrom: 1
  to: tempVars size
  with: tempVars.
  start := 1].
  start to: tempVector size do:
  [:i|
  tempVector
  at: i
  put: (constructor
  codeTemp: numLocalTemps + offset + i - 1
  named: 't', (tempVarCount + i) printString)].
  tempVars at: offset + 1 put: (constructor codeRemoteTemp: offset + 1 remoteTemps: tempVector)].
  tempVarCount := tempVarCount + maybeTVTag value size.
  stack removeLast.
  ^self].
+ stack addLast: (offset >= tempVars size
+ ifTrue: "Handle the case of chained LiteralVariableBinding assigments"
+ [stack at: (offset + 1 - tempVars size)]
+ ifFalse: "A regular argument or temporary"
+ [tempVars at: offset + 1]).
+ self doStore: statements!
- self pushTemporaryVariable: offset; doStore: statements!

Item was changed:
  ----- Method: Decompiler>>pushTemporaryVariable: (in category 'instruction decoding') -----
  pushTemporaryVariable: offset
+ | node |
+ offset >= tempVars size
+ ifTrue: "Handle the case of chained LiteralVariableBinding assigments"
+ [self halt.
+ node := stack at: offset + 1 - tempVars size]
+ ifFalse: "A regular argument or temporary"
+ [node := tempVars at: offset + 1.
+ node isArg ifFalse: "count temp reads for the whileTrue: => to:do: transformation."
+ [tempReadCounts at: node put: (tempReadCounts at: node ifAbsent: [0]) + 1]].
+ stack addLast: node!
-
- stack addLast: (offset >= tempVars size
- ifTrue:
- ["Handle the case of chained LiteralVariableBinding assigments"
- stack at: (offset + 1 - tempVars size)]
- ifFalse:
- ["A regular argument or temporary"
- tempVars at: offset + 1])!

Item was removed:
- ----- Method: Decompiler>>scanBlockScopeFor:from:to:with:scanner: (in category 'private') -----
- scanBlockScopeFor: refpc from: startpc to: endpc with: scan scanner: scanner
- | bsl maybeBlockSize |
- bsl := BlockStartLocator new.
- scanner pc: startpc.
- [scanner pc <= endpc] whileTrue:
- [refpc = scanner pc ifTrue:
- [scanner pc: startpc.
- [scanner pc <= endpc] whileTrue:
- [(scan value: scanner firstByte) ifTrue:
- [^endpc].
- (maybeBlockSize := scanner interpretNextInstructionFor: bsl) isInteger ifTrue:
- [scanner pc: scanner pc + maybeBlockSize]].
-   ^self].
- (maybeBlockSize := scanner interpretNextInstructionFor: bsl) isInteger ifTrue:
- [refpc <= (scanner pc + maybeBlockSize)
- ifTrue: [^self scanBlockScopeFor: refpc from: scanner pc to: scanner pc + maybeBlockSize with: scan scanner: scanner]
- ifFalse: [scanner pc: scanner pc + maybeBlockSize]]]!

Item was changed:
  ----- Method: Decompiler>>send:super:numArgs: (in category 'instruction decoding') -----
  send: selector super: superFlag numArgs: numArgs
 
  | args rcvr selNode msgNode messages |
  args := Array new: numArgs.
  (numArgs to: 1 by: -1) do:
  [:i | args at: i put: stack removeLast].
  rcvr := stack removeLast.
  superFlag ifTrue: [rcvr := constructor codeSuper].
+ selNode := constructor codeAnySelector: selector.
+ rcvr == CascadeFlag
+ ifTrue:
+ ["May actually be a cascade or an ifNil: for value."
+ self willJumpIfFalse
+ ifTrue: "= generated by a case macro"
+ [selector == #= ifTrue:
+ [" = signals a case statement..."
+ statements addLast: args first.
+ stack addLast: rcvr. "restore CascadeFlag"
+ ^ self].
+ selector == #== ifTrue:
+ [" == signals an ifNil: for value..."
+ stack removeLast; removeLast.
+ rcvr := stack removeLast.
+ stack addLast: IfNilFlag;
+ addLast: (constructor
+ codeMessage: rcvr
+ selector: selNode
+ arguments: args).
+ ^ self]]
+ ifFalse:
+ [(self willJumpIfTrue and: [selector == #==]) ifTrue:
+ [" == signals an ifNotNil: for value..."
+ stack removeLast; removeLast.
+ rcvr := stack removeLast.
+ stack addLast: IfNilFlag;
+ addLast: (constructor
+ codeMessage: rcvr
+ selector: selNode
+ arguments: args).
+ ^ self]].
+ msgNode := constructor
+ codeCascadedMessage: selNode
+ arguments: args.
+ stack last == CascadeFlag ifFalse:
+ ["Last message of a cascade"
+ statements addLast: msgNode.
+ messages := self popTo: stack removeLast.  "Depth saved by first dup"
- (#closureCopy:copiedValues: == selector
- and: [self checkForClosureCopy: rcvr arguments: args]) ifFalse:
- [selNode := constructor codeAnySelector: selector.
- rcvr == CascadeFlag
- ifTrue:
- ["May actually be a cascade or an ifNil: for value."
- self willJumpIfFalse
- ifTrue: "= generated by a case macro"
- [selector == #= ifTrue:
- [" = signals a case statement..."
- statements addLast: args first.
- stack addLast: rcvr. "restore CascadeFlag"
- ^ self].
- selector == #== ifTrue:
- [" == signals an ifNil: for value..."
- stack removeLast; removeLast.
- rcvr := stack removeLast.
- stack addLast: IfNilFlag;
- addLast: (constructor
- codeMessage: rcvr
- selector: selNode
- arguments: args).
- ^ self]]
- ifFalse:
- [(self willJumpIfTrue and: [selector == #==]) ifTrue:
- [" == signals an ifNotNil: for value..."
- stack removeLast; removeLast.
- rcvr := stack removeLast.
- stack addLast: IfNilFlag;
- addLast: (constructor
- codeMessage: rcvr
- selector: selNode
- arguments: args).
- ^ self]].
  msgNode := constructor
+ codeCascade: stack removeLast
+ messages: messages]]
+ ifFalse:
+ [msgNode := constructor
+ codeMessage: rcvr
+ selector: selNode
+ arguments: args].
+ stack addLast: msgNode!
- codeCascadedMessage: selNode
- arguments: args.
- stack last == CascadeFlag ifFalse:
- ["Last message of a cascade"
- statements addLast: msgNode.
- messages := self popTo: stack removeLast.  "Depth saved by first dup"
- msgNode := constructor
- codeCascade: stack removeLast
- messages: messages]]
- ifFalse:
- [msgNode := constructor
- codeMessage: rcvr
- selector: selNode
- arguments: args].
- stack addLast: msgNode]!

Item was added:
+ ----- Method: Decompiler>>startAndLimitFor:from:into: (in category 'private') -----
+ startAndLimitFor: incrVar from: aStack into: binaryBlock
+ "If incrVar matches the increment of a whileLoop at the end of statements
+ evaluate binaryBlock with the init statement for incrVar and the init statement
+ for the block's limit, if any, and answer true.  Otherwise answer false.  Used to
+ help convert whileTrue: loops into to:[by:]do: loops."
+ | guard initExpr limitInit size |
+ ((size := aStack size) >= 1
+ and: [(initExpr := aStack at: size) isAssignmentNode]) ifFalse:
+ [^false].
+ initExpr variable == incrVar ifTrue:
+ [binaryBlock value: initExpr value: nil.
+ ^true].
+ limitInit := initExpr.
+ (size >= 2
+ and: [(initExpr := aStack at: size - 1) isAssignmentNode
+ and: [initExpr variable == incrVar
+ and: [(guard := statements last receiver) isBlockNode
+ and: [guard statements size = 1
+ and: [(guard := guard statements first) isMessageNode
+ and: [guard receiver == incrVar
+ and: [guard arguments first == limitInit variable]]]]]]]) ifTrue:
+ [binaryBlock value: initExpr value: limitInit.
+ ^true].
+ ^false!

Item was changed:
  ----- Method: Decompiler>>statementsTo: (in category 'control') -----
  statementsTo: end
  "Decompile the method from pc up to end and return an array of
  expressions. If at run time this block will leave a value on the stack,
  set hasValue to true. If the block ends with a jump or return, set exit
  to the destination of the jump, or the end of the method; otherwise, set
  exit = end. Leave pc = end."
 
+ | encoderClass blockPos stackPos |
+ encoderClass := method encoderClass.
- | blockPos stackPos t |
  blockPos := statements size.
  stackPos := stack size.
  [pc < end]
  whileTrue:
  [lastPc := pc.  limit := end.  "for performs"
+ "If you want instrumentation replace the following statement with this one,
+  and edit the implementation:
+ self interpretNextInstructionFor: self"
+ encoderClass interpretNextInstructionFor: self in: self].
- self interpretNextInstructionFor: self].
  "If there is an additional item on the stack, it will be the value
  of this block."
  (hasValue := stack size > stackPos)
  ifTrue:
  [statements addLast: stack removeLast].
  lastJumpPc = lastPc ifFalse: [exit := pc].
  ^self popTo: blockPos!

Item was changed:
  ----- Method: Decompiler>>storeIntoTemporaryVariable: (in category 'instruction decoding') -----
  storeIntoTemporaryVariable: offset
+ stack addLast: (offset >= tempVars size
+ ifTrue: "Handle the case of chained LiteralVariableBinding assigments"
+ [stack at: (offset + 1 - tempVars size)]
+ ifFalse: "A regular argument or temporary"
+ [tempVars at: offset + 1]).
+ self doStore: stack!
-
- self pushTemporaryVariable: offset; doStore: stack!

Item was removed:
- ----- Method: DecompilerConstructor>>codeArguments:block: (in category 'constructor') -----
- codeArguments: args block: block
-
- ^block arguments: args!

Item was changed:
  ----- Method: DecompilerConstructor>>codeMessage:selector:arguments: (in category 'constructor') -----
  codeMessage: receiver selector: selector arguments: arguments
  | symbol |
  symbol := selector key.
- (BraceNode new
- matchBraceWithReceiver: receiver
- selector: symbol
- arguments: arguments) ifNotNil: [:node| ^node].
  (self
  decodeLiteralVariableValueDereferenceWithReceiver: receiver
  selector: symbol
  arguments: arguments) ifNotNil: [:node| ^node].
  (self decodeIfNilWithReceiver: receiver
  selector: symbol
  arguments: arguments) ifNotNil: [:node| ^node].
  ^MessageNode new
  receiver: receiver selector: selector
  arguments: arguments
  precedence: symbol precedence!

Item was changed:
  ----- Method: Encoder>>encodeLiteral: (in category 'encoding') -----
  encodeLiteral: object
-
  ^self
  name: object
+ key: object
- key: (cue  literalScannedAs: object notifying: self)
  class: LiteralNode
  type: LdLitType
  set: litSet!

Item was added:
+ BytecodeEncoder subclass: #EncoderForSistaV1
+ instanceVariableNames: ''
+ classVariableNames: ''
+ poolDictionaries: ''
+ category: 'Compiler-Kernel'!
+
+ !EncoderForSistaV1 commentStamp: 'eem 4/6/2017 10:34' prior: 0!
+ EncoderForSistaV1 encodes a bytecode set for Smalltalk that lifts limits on the number of literals and branch distances, and provides extended push integer and push character bytecodes.  The bytecode set also supports creating FullBlockClosures, closures whose method is separate from their home method's.  Bytecodes are ordered by length to make decoding easier.  Bytecodes marked with an * are extensible via a prefix bytecode.
+
+ N.B.  Extension bytecodes can only come before extensible bytecodes, and only if valid (one cannot extend a bytecode extensible by Ext A with an Ext B).  An extensible bytecode consumes (and zeros) its extension(s).  Hence the hidden implicit variables holding extensions are always zero except after a valid sequence of extension bytecodes.
+
+ EncoderForSistaV1 also includes an extended set of bytecodes for Sista, the Speculative Inlining Smalltalk Architecture, a project by Clément Bera and Eliot Miranda.  Scorch is an optimizer that exists in the Smalltalk image, /not/ in the VM,  and optimizes by substituting normal bytecoded methods by optimized bytecoded methods that may use special bytecodes for which the Cogit can generate faster code.  These bytecodes eliminate overheads such as bounds checks or polymorphic code (indexing Array, ByteArray, String etc).  But the bulk of the optimization performed is in inlining blocks and sends for the common path.  This bytecode set therefore differs from a normal Smalltalk set in providing a set of inlined primitives that do not validate their arguments that the compiler generates only when it can prove that the primitives' arguments are valid.
+
+ The basic scheme is that the Cogit generates code containing performance counters.  When these counters trip, a callback into the image is performed, at which point Scorch analyses some portion of the stack, looking at performance data for the methods on the stack, and optimises based on the stack and performance data.  Execution then resumes in the optimized code.
+
+ The Sista Cogit (e.g. SistaStackToRegisterMappingCogit) adds counters to conditional branches.  Each branch has an executed and a taken count.  On execution the executed count is decremented and if the count goes below zero the VM sends a message at a special index in the specialObjectsArray (as of writing, conditionalCounterTrippedOn:).  Then if the branch is taken the taken count is decremented.  The two counter values allow the Sista optimizer to collect basic block execution paths and to know what are the "hot" paths through execution that are worth agressively optimizing.  Since conditional branches are about 1/6 as frequent as sends, and since they can be used to determine the hot path through code, they are a better choice to count than, for example, method or block entry.
+
+ The VM provides a primitive that fills an Array with the state of the counters, and the state of each linked send in a method.  The optimizer obtains the branch and send data for a method via this primitive.
+
+ Instance Variables (inherited)
+
+ 1 Byte Bytecodes
+ code (note) binary name
+ 0-15 0000 iiii Push Receiver Variable #iiii
+ 16-31 0001 iiii Push Literal Variable #iiii
+ 32-63 001 iiiii Push Literal #iiiii
+ 64-71 01000 iii Push Temp #iii
+ 72-75 010010 ii Push Temp #ii + 8
+ 76 01001100 Push Receiver
+ 77 01001101 Push true
+ 78 01001110 Push false
+ 79 01001111 Push nil
+ 80 01010000 Push 0
+ 81 01010001 Push 1
+ * 82 01010010 Push thisContext, (then Extend B = 1 => push thisProcess)
+ 83 01010011 Duplicate Stack Top
+ 84-87 010101 ii UNASSIGNED
+ 88-91 010110 ii Return Receiver/true/false/nil
+ 92 01011100 Return top
+ 93 01011101 BlockReturn nil
+ * 94 01011110 BlockReturn Top [* return from enclosing block N, N = Extend A, then jump by Ext B ]
+ * 95 01011111 Nop
+ 96-111 0110 iiii Send Arithmetic Message #iiii (+ - < > <= >= = ~= * / \\ @ bitShift: // bitAnd: bitOr:)
+ 112-119 01110 iii Send Special Message #iii + 0 (at: at:put: size next nextPut: atEnd == class)
+ 120-127 01111 iii Send Special Message #iii + 8 (~~ value value: do: new new: x y)
+ 128-143 1000 iiii Send Literal Selector #iiii With 0 Argument
+ 144-159 1001 iiii Send Literal Selector #iiii With 1 Arguments
+ 160-175 1010 iiii Send Literal Selector #iiii With 2 Arguments
+ 176-183 10110 iii Jump iii + 1 (i.e., 1 through 8)
+ 184-191 10111 iii Pop and Jump 0n True iii +1 (i.e., 1 through 8)
+ 192-199 11000 iii Pop and Jump 0n False iii +1 (i.e., 1 through 8)
+ 200-207 11001 iii Pop and Store Receiver Variable #iii
+ 208-215 11010 iii Pop and Store Temporary Variable #iii
+ 216 11011000 Pop Stack Top
+ 217 11011001 Unconditional trap
+ 218-219 1101101 i UNASSIGNED
+ 220-223 110111 ii UNASSIGNED
+
+ 2 Byte Bytecodes
+ * 224 11100000 aaaaaaaa Extend A (Ext A = Ext A prev * 256 + Ext A) A is an unsigned extension.
+ * 225 11100001 bbbbbbbb Extend B (Ext B = Ext B prev * 256 + Ext B) B is a signed extension.
+ * 226 11100010 iiiiiiii Push Receiver Variable #iiiiiiii (+ Extend A * 256)
+ * 227 11100011 iiiiiiii Push Literal Variable #iiiiiiii (+ Extend A * 256)
+ * 228 11100100 iiiiiiii Push Literal #iiiiiiii (+ Extend A * 256)
+ 229 11100101 iiiiiiii Push Temporary Variable #iiiiiiii
+ 230 11100110 iiiiiiii UNASSIGNED (was pushNClosureTemps)
+ 231 11100111 jkkkkkkk Push (Array new: kkkkkkk) (j = 0)
+ & Pop kkkkkkk elements into: (Array new: kkkkkkk) (j = 1)
+ * 232 11101000 iiiiiiii Push Integer #iiiiiiii (+ Extend B * 256, where bbbbbbbb = sddddddd, e.g. -32768 = i=0, d=0, s=1)
+ * 233 11101001 iiiiiiii Push Character #iiiiiiii (+ Extend B * 256)
+ ** 234 11101010 iiiiijjj Send Literal Selector #iiiii (+ Extend A * 32) with jjj (+ Extend B * 8) Arguments
+ ** 235 (1) 11101011 iiiiijjj ExtendB < 64
+ ifTrue: [Send To Superclass Literal Selector #iiiii (+ Extend A * 32) with jjj (+ Extend B * 8) Arguments]
+ ifFalse: [Send To Superclass of Stacked Class Literal Selector #iiiii (+ Extend A * 32) with jjj (+ (Extend B bitAnd: 63) * 8) Arguments]
+ * 236 11101100 iiiiiiii UNASSIGNED
+ * 237 11101101 iiiiiiii Jump #iiiiiiii (+ Extend B * 256, where bbbbbbbb = sddddddd, e.g. -32768 = i=0, d=0, s=1)
+ ** 238 11101110 iiiiiiii Pop and Jump 0n True #iiiiiiii (+ Extend B * 256, where Extend B >= 0) (4)
+ ** 239 11101111 iiiiiiii Pop and Jump 0n False #iiiiiiii (+ Extend B * 256, where Extend B >= 0) (4)
+ ** 240 (3) 11110000 iiiiiiii Pop and Store Receiver Variable #iiiiiii (+ Extend A * 256)
+ ** 241 (3) 11110001 iiiiiiii Pop and Store Literal Variable #iiiiiiii (+ Extend A * 256)
+ 242 11110010 iiiiiiii Pop and Store Temporary Variable #iiiiiiii
+ ** 243 (3) 11110011 iiiiiiii Store Receiver Variable #iiiiiii (+ Extend A * 256)
+ ** 244 (3) 11110100 iiiiiiii Store Literal Variable #iiiiiiii (+ Extend A * 256)
+ 245 11110110 iiiiiiii Store Temporary Variable #iiiiiiii
+ 246-247 1111011 i xxxxxxxx UNASSIGNED
+
+ 3 Byte Bytecodes
+ ** 248 (2) 11111000 iiiiiiii mssjjjjj Call Primitive #iiiiiiii + (jjjjj * 256)
+ m=1 means inlined primitive, no hard return after execution.
+ ss defines the unsafe operation set used to encode the operations.
+ (ss = 0 means sista unsafe operations, ss = 01 means lowcode operations, other numbers are not used)
+ Lowcode inlined primitives may have extensions.
+ 249 11111001 xxxxxxxx siyyyyyy push Closure Compiled block literal index xxxxxxxx (+ Extend A * 256) numCopied yyyyyy receiverOnStack: s = 1 ignoreOuterContext: i = 1
+ ** 250 11111010 eeiiikkk jjjjjjjj Push Closure Num Copied iii (+ExtA//16*8) Num Args kkk (+ ExtA\\16*8) BlockSize jjjjjjjj (+ExtB*256). ee = num extensions
+ 251 11111011 kkkkkkkk sjjjjjjj Push Temp At kkkkkkkk In Temp Vector At: jjjjjjj, s = 1 implies remote inst var access instead of remote temp vector access
+ * 252 (3) 11111100 kkkkkkkk sjjjjjjj Store Temp At kkkkkkkk In Temp Vector At: jjjjjjj s = 1 implies remote inst var access instead of remote temp vector access
+ * 253 (3) 11111101 kkkkkkkk sjjjjjjj Pop and Store Temp At kkkkkkkk In Temp Vector At: jjjjjjj s = 1 implies remote inst var access instead of remote temp vector access
+ ** 254 11111110 kkkkkkkk jjjjjjjj branch If Not Instance Of Behavior/Array Of Behavior literal kkkkkkkk (+ Extend A * 256, where Extend A >= 0) distance jjjjjjjj (+ Extend B * 256, where Extend B >= 0 and <= 127)
+ ** 254 11111110 kkkkkkkk jjjjjjjj branch If Instance Of Behavior/Array Of Behavior literal kkkkkkkk (+ Extend A * 256, where Extend A >= 0) distance jjjjjjjj (+ (Extend B bitAnd: 127) * 256, where Extend B >= 128 and <= 255)
+ * 255 11111111 xxxxxxxx jjjjjjjj UNASSIGNED
+
+ (1) Bytecode 235 is a super send bytecode that starts the lookup in the superclass of some class.  It has two forms, "normal" and "directed". In the normal form, the class is the value of the method's methodClassAssociation which must be the last literal.  In the directed form the class is the class on top of stack.
+
+ (2) The Call Primitive Bytecode specifies either a primitive in the primitive table (m=0) or an inlined primitive (m=1). Non-inlined primitives from the primitive table have index (jjjjjjj * 256) + iiiiiiii and return from the method if they succeed.  This bytecode is only valid as the first bytecode of a method.  Inline primitives have index (jjjjjjj * 256) + iiiiiiii, cannot fail, and do not return when they succeed, yielding a result (typically on top of stack after popping their arguments, but possibly in a byte data stack, for example for unboxed floating-point primitives).
+
+ (3) ExtB lowest bit implies no store check is needed, ExtB second bit implies the object may be a context, ExtB third bit implies no immutability/read-only check is needed, other bits in the extension are unused.
+
+ (4) ExtA = 1 implies no mustBeBoolean trampoline is needed, other bits in the extension are unused
+
+
+ Here is the specification of the Sista unsafe instructions (unsafe operations, set 00). The lowcode set uses external specifications.
+ We sort the inline primitive operations by arity.  Nullary primitives occupy the 0-999 range. Unary primitives occupy the 1-1999 range, up until 8 args. 8191 instructions can be encoded in each unsafe operation set, instructions from 0 to 7 arguments can have 1000 different instructions each, while 8 args instructions can have 192 different instructions.
+
+ Sista defines the following inlined primitives (CallPrimitive iiiiiiii 100jjjjj, n = jjjjjiiiiiiii)
+ 1000 class
+ 1001 pointer numSlots
+ 1002 pointer basicSize
+ 1003 byte8Type format numBytes (includes CompiledMethod)
+ 1004 short16Type format numShorts
+ 1005 word32Type format numWords
+ 1006 doubleWord64Type format numDoubleWords
+
+ 1010 ensure number of bytes available.
+ 1011 fixed-sized new. (objects with 0 to n inst vars)
+
+ 1020 identityHash (non-immediate, non-Behavior)
+ 1021 identityHash (SmallInteger)
+ 1022 identityHash (Character)
+ 1023 identityHash (SmallFloat64)
+ 1024 identityHash (Behavior, has hash?)
+
+ 1030 immediateAsInteger (Character)
+ 1031 immediateAsInteger (SmallFloat64)
+ 1035 immediateAsFloat (Smallinteger)
+
+ 2000 SmallInteger #+.  Both arguments are SmallIntegers and the result fits in a SmallInteger (* depends on word size)
+ 2001 SmallInteger #-.  Both arguments are SmallIntegers and the result fits in a SmallInteger (* depends on word size)
+ 2002 SmallInteger #*.  Both arguments are SmallIntegers and the result fits in a SmallInteger (* depends on word size)
+ 2003 SmallInteger #/.  Both arguments are SmallIntegers and the result fits in a SmallInteger (* depends on word size)
+ 2004 SmallInteger #//.  Both arguments are SmallIntegers and the result fits in a SmallInteger (* depends on word size)
+ 2005 SmallInteger #\\.  Both arguments are SmallIntegers and the result fits in a SmallInteger (* depends on word size)
+ 2006 SmallInteger #quo:.  Both arguments are SmallIntegers and the result fits in a SmallInteger (* depends on word size)
+
+ 2011 Variable-sized pointers new (new:). Array, etc.
+ 2012 Variable-sized byte new (new:). ByteArray, ByteString, etc.
+ 2013 Variable-sized 16-bit new (new:). DoubleByteArray, etc.
+ 2014 Variable-sized 32-bit new (new:). Bitmap, FloatArray, etc.
+ 2015 Variable-sized 64-bit new (new:). DoubleWordArray, etc.
+
+ 2016 SmallInteger #bitAnd:.  Both arguments are SmallIntegers and the result fits in a SmallInteger (* depends on word size)
+ 2017 SmallInteger #bitOr:.  Both arguments are SmallIntegers and the result fits in a SmallInteger (* depends on word size)
+ 2018 SmallInteger #bitXor:.  Both arguments are SmallIntegers and the result fits in a SmallInteger (* depends on word size)
+ 2019 SmallInteger #bitShiftLeft:.  Both arguments are SmallIntegers and the result fits in a SmallInteger (* depends on word size)
+ 2020 SmallInteger #bitShiftRight:.  Both arguments are SmallIntegers and the result fits in a SmallInteger (* depends on word size)
+
+ 2032 SmallInteger #>.  Both arguments are SmallIntegers
+ 2033 SmallInteger #<.  Both arguments are SmallIntegers
+ 2034 SmallInteger #>=.  Both arguments are SmallIntegers
+ 2035 SmallInteger #<=.  Both arguments are SmallIntegers
+ 2036 SmallInteger #=.  Both arguments are SmallIntegers
+ 2037 SmallInteger #~=.  Both arguments are SmallIntegers
+
+ 2064 Pointer Object>>at:. The receiver is guaranteed to be a pointer object.  The 0-relative (1-relative?) index is an in-range SmallInteger
+ 2065 Byte Object>>at:. The receiver is guaranteed to be a non-pointer object.  The 0-relative (1-relative?) index is an in-range SmallInteger.  The result is a SmallInteger.
+ 2066 16-bit Word Object>>at:. The receiver is guaranteed to be a non-pointer object.  The 0-relative (1-relative?) index is an in-range SmallInteger.  The result is a SmallInteger.
+ 2067 32-bit DoubleWord Object>>at:. The receiver is guaranteed to be a non-pointer object.  The 0-relative (1-relative?) index is an in-range SmallInteger.  The result is a SmallInteger or a LargePositiveInteger.
+ 2068 64-bit QuadWord Object>>at:. The receiver is guaranteed to be a non-pointer object.  The 0-relative (1-relative?) index is an in-range SmallInteger.  The result is a SmallInteger or a LargePositiveInteger.
+
+ The following instructions can have the ExtB check flag (See (3)).
+ 3000 Pointer Object>>at:put:. The receiver is guaranteed to be a pointer object.  The 0-relative (1-relative?) index is an in-range SmallInteger
+ 3001 Byte Object>>at:put:. The receiver is guaranteed to be a non-pointer object.  The 0-relative (1-relative?) index is an in-range SmallInteger.  The argument is a SmallInteger.  The primitive stores the least significant 8 bits.
+ 3002 Word Object>>at:put:. The receiver is guaranteed to be a non-pointer object.  The 0-relative (1-relative?) index is an in-range SmallInteger.  The argument is a SmallInteger.  The primitive stores the least significant 16 bits.
+ 3003 DoubleWord Object>>at:put:. The receiver is guaranteed to be a non-pointer object.  The 0-relative (1-relative?) index is an in-range SmallInteger.  The argument is a SmallInteger.  The primitive stores the least significant 32 bits.
+ 3004 QuadWord Object>>at:put:. The receiver is guaranteed to be a non-pointer object.  The 0-relative (1-relative?) index is an in-range SmallInteger.  The argument is a SmallInteger.  The primitive stores the least significant 64 bits.
+
+ 3021 Byte Object >> equals:length: The receiver and the arguments are both byte objects and have both the same size (length). The length argument is a smallinteger. Answers true if all fields are equal, false if not. Comparison is bulked to word comparison.
+
+ 4000 Pointer Object>> fillFrom:to:with: The receiver is a Pointer object. the middle two arguments are smallintegers. Last argument is any object. Fills the object in between the two indexes with last argument. Receiver is guaranteed to be mutable. The pointer accesses are raw (no inst var check). If ExtB is set to 1, no store check is present. Else a single store check is done for the bulk operation. Answers the receiver.
+
+ 5000 Pointer Object>> replaceFrom:to:with:startingAt: Src and dest are pointer objects. ScrPos, scrLast and destLast are smallintegers. Receiver is guaranteed to be mutable.  Both ranges are in-bounds. The pointer accesses are raw (no inst var check). As for the normal primitive, the copy is linear. Answers the receiver.
+
+
+ Lowcode defines inlined primitives for the range CallPrimitive iiiiiiii 101jjjjj, n = jjjjjiiiiiiii.!

Item was added:
+ ----- Method: EncoderForSistaV1 class>>bindingReadScanBlockFor:using: (in category 'compiled method support') -----
+ bindingReadScanBlockFor: litVarIndex using: scanner
+ "Answer a block argument for InstructionStream>>scanFor: that answers true
+ for reads of the value of the binding with zero-relative index litVarIndex.
+ N.B. Don't assume the compiler uses the most compact encoding available."
+
+ " 16-31 0001 i i i i Push Literal Variable #iiii
+ * 224 11100000 aaaaaaaa Extend A (Ext A = Ext A prev * 256 + Ext A)
+ * 227 11100011 i i i i i i i i Push Literal Variable #iiiiiiii (+ Extend A * 256)"
+ | extension |
+ extension := 0.
+ ^[:b| | prevext |
+   prevext := extension.
+   extension := b = 224 ifTrue: [scanner followingByte bitShift: 8] ifFalse: [0].
+   (b < 32 and: [b >= 16 and: [b - 16 = litVarIndex]])
+    or: [b = 227
+ and: [scanner followingByte + prevext = litVarIndex]]]!

Item was added:
+ ----- Method: EncoderForSistaV1 class>>bindingWriteScanBlockFor:using: (in category 'compiled method support') -----
+ bindingWriteScanBlockFor: litVarIndex using: scanner
+ "Answer a block argument for InstructionStream>>scanFor: that answers true
+ for writes of the value of the binding with zero-relative index litVarIndex.
+ N.B. Don't assume the compiler uses the most compact encoding available."
+
+ "* 224 11100000 aaaaaaaa Extend A (Ext A = Ext A prev * 256 + Ext A)
+ * 241 11110001 iiiiiiii Pop and Store Literal Variable #iiiiiiii (+ Extend A * 256)
+ * 244 11110100 iiiiiiii Store Literal Variable #iiiiiiii (+ Extend A * 256)"
+ | extension |
+ extension := 0.
+ ^[:b| | prevext |
+   prevext := extension.
+   extension := b = 224 ifTrue: [scanner followingByte bitShift: 8] ifFalse: [0].
+   (b = 241 or: [b = 244])
+   and: [scanner followingByte + prevext = litVarIndex]]!

Item was added:
+ ----- Method: EncoderForSistaV1 class>>bytecodeSize: (in category 'instruction stream support') -----
+ bytecodeSize: bytecode
+ "Answer the number of bytes in the bytecode."
+ bytecode < 224 ifTrue: [^1].
+ bytecode < 248 ifTrue: [^2].
+ ^3!

Item was added:
+ ----- Method: EncoderForSistaV1 class>>callPrimitiveCode (in category 'bytecode decoding') -----
+ callPrimitiveCode
+ "Answer the call primitive bytecode, if it exists in the encoder's bytecode set, or nil if not.
+ 248 11111000 iiiiiiii mjjjjjjj Call Primitive #iiiiiiii + (jjjjjjj * 256) m=1 means inlined primitive, no hard return after execution."
+ ^248!

Item was added:
+ ----- Method: EncoderForSistaV1 class>>createClosureCode (in category 'bytecode decoding') -----
+ createClosureCode
+ "Answer the create closure bytecode, if it exists in the encoder's bytecode set, or nil if not.
+ Actually this code is that for a closure whose bytecodes are nested within its home method's."
+
+ ^250!

Item was added:
+ ----- Method: EncoderForSistaV1 class>>createClosureScanBlock (in category 'compiled method support') -----
+ createClosureScanBlock
+ "Answer a block argument for InstructionStream>>scanFor: that answers true
+ for block closure creation bytecodes.  ote that with this interface we can't answer
+ true for the extension in front of a push closure bytecode and so the interface may
+ have to change at some point."
+
+ "* 224 11100000 aaaaaaaa Extend A (Ext A = Ext A prev * 256 + Ext A)
+ * 225 11100001 bbbbbbbb Extend B (Ext B = Ext B prev * 256 + Ext B)
+ ** 250 11111010 eeiiikkk jjjjjjjj Push Closure Num Copied iii (+ExtA//16*8) Num Args kkk (+ ExtA\\16*8) BlockSize jjjjjjjj (+ExtB*256). ee = num extensions"
+ ^[:b| b = 250]!

Item was added:
+ ----- Method: EncoderForSistaV1 class>>extensionsAt:in:into: (in category 'compiled method support') -----
+ extensionsAt: bcpc in: method into: aTrinaryBlock
+ "If the bytecode at pc is an extension then evaluate aBinaryBlock with the values of extA and extB and number of extension *bytes*.
+ If the bytecode at pc is not extended then evaluate aBinaryBlock with 0 and 0.
+ 224 11100000 aaaaaaaa Extend A (Ext A = Ext A prev * 256 + Ext A)
+ 225 11100001 bbbbbbbb Extend B (Ext B = Ext B prev * 256 + Ext B)"
+  
+ | scanpc byte extByte extA extB |
+ scanpc := bcpc.
+ "There may be an extension (it could be a false positive).  We must scan as fast as possible..."
+ extA := extB := 0.
+ [byte := method at: scanpc.
+ byte >= 224 and: [byte <= 225]] whileTrue:
+ [extByte := method at: scanpc + 1.
+ scanpc := scanpc + 2.
+ byte = 224
+ ifTrue:
+ [extA := (extA bitShift: 8) + extByte]
+ ifFalse:
+ [extB := (extB = 0 and: [extByte > 127])
+ ifTrue: [extByte - 256]
+ ifFalse: [(extB bitShift: 8) + extByte]]].
+ ^aTrinaryBlock value: extA value: extB value: scanpc - bcpc
+
+
+ "Why use
+ byte >= 224 and: [byte <= 225]
+  and not
+ (byte bitAnd: 16rFE) = 16rE0
+  ?
+  | n |
+  n := 100000000.
+  #(0 224) collect:
+ [:byte|
+ { Time millisecondsToRun: [1 to: n do: [:i| (byte >= 224 and: [byte <= 225]) ifTrue: []]].
+   Time millisecondsToRun: [1 to: n do: [:i| (byte bitAnd: 16rFE) = 16rE0 ifTrue: []]] }] #(#(297 599) #(702 671))"!

Item was added:
+ ----- Method: EncoderForSistaV1 class>>instVarReadScanBlockFor:using: (in category 'compiled method support') -----
+ instVarReadScanBlockFor: varIndexCode using: scanner
+ "Answer a block argument for InstructionStream>>scanFor: that answers true
+ for reads of the inst var with zero-relative index varIndexCode.
+ N.B. Don't assume the compiler uses the most compact encoding available."
+
+ " 0-15 0000 i i i i Push Receiver Variable #iiii
+ * 224 11100000 aaaaaaaa Extend A (Ext A = Ext A prev * 256 + Ext A)
+ * 226 11100010 i i i i i i i i Push Receiver Variable #iiiiiiii (+ Extend A * 256)"
+ | extension |
+ extension := 0.
+ ^[:b| | prevext |
+   prevext := extension.
+   extension := b = 224 ifTrue: [scanner followingByte bitShift: 8] ifFalse: [0].
+   (b < 16 and: [b = varIndexCode])
+    or: [b = 226
+ and: [scanner followingByte + prevext = varIndexCode]]]!

Item was added:
+ ----- Method: EncoderForSistaV1 class>>instVarWriteScanBlockFor:using: (in category 'compiled method support') -----
+ instVarWriteScanBlockFor: varIndexCode using: scanner
+ "Answer a block argument for InstructionStream>>scanFor: that answers true
+ for writes of the inst var with zero-relative index varIndexCode.
+ N.B. Don't assume the compiler uses the most compact encoding available."
+
+ " 200-207 11001 iii Pop and Store Receiver Variable #iii
+ * 224 11100000 aaaaaaaa Extend A (Ext A = Ext A prev * 256 + Ext A)
+ * 240 11110000 iiiiiiii Pop and Store Receiver Variable #iiiiiii (+ Extend A * 256)
+ * 243 11110011 iiiiiiii Store Receiver Variable #iiiiiii (+ Extend A * 256)"
+ | extension |
+ extension := 0.
+ ^[:b| | prevext |
+   prevext := extension.
+   extension := b = 224 ifTrue: [scanner followingByte bitShift: 8] ifFalse: [0].
+   (b >= 200
+    and: [b < 208
+    and: [b - 200 = varIndexCode]])
+   or: [(b = 240 or: [b = 243])
+  and: [scanner followingByte + prevext = varIndexCode]]]!

Item was added:
+ ----- Method: EncoderForSistaV1 class>>interpretJumpIfCondIn: (in category 'compiled method support') -----
+ interpretJumpIfCondIn: anInstructionStream
+ "Double-dispatch through the encoder to select the correct conditional jump decoder for the instruction set."
+ ^anInstructionStream interpretSistaV1JumpIfCond!

Item was added:
+ ----- Method: EncoderForSistaV1 class>>interpretJumpIn: (in category 'compiled method support') -----
+ interpretJumpIn: anInstructionStream
+ "Double-dispatch through the encoder to select the correct unconditional jump decoder for the instruction set."
+ ^anInstructionStream interpretSistaV1Jump!

Item was added:
+ ----- Method: EncoderForSistaV1 class>>interpretNextInstructionFor:in: (in category 'instruction stream support') -----
+ interpretNextInstructionFor: aClient in: anInstructionStream
+ "Double-dispatch through the encoder to select the correct instruction set decoder."
+ ^anInstructionStream interpretNextSistaV1InstructionFor: aClient!

Item was added:
+ ----- Method: EncoderForSistaV1 class>>isBlockReturnAt:in: (in category 'instruction stream support') -----
+ isBlockReturnAt: pc in: method
+ "Answer whether the bytecode at pc is a return from block."
+ " 93 01011101 BlockReturn nil
+ * 94 01011110 BlockReturn Top [* return from enclosing block N, N = Extend A, then jump by Ext B ]"
+ ^(self nonExtensionBytecodeAt: pc in: method) between: 93 and: 94!

Item was added:
+ ----- Method: EncoderForSistaV1 class>>isBranchIfFalseAt:in: (in category 'instruction stream support') -----
+ isBranchIfFalseAt: pc in: method
+ "Answer whether the bytecode at pc is a conditional branch-if-false."
+
+ " 192-199 11000 iii Pop and Jump 0n False iii +1 (i.e., 1 through 8)
+ * 239 11101111 iiiiiiii Pop and Jump 0n False #iiiiiiii (+ Extend B * 256, where Extend B >= 0)"
+ | byte |
+ byte := self nonExtensionBytecodeAt: pc in: method.
+ ^byte >= 192 and: [byte <= 199 or: [byte = 239]]!

Item was added:
+ ----- Method: EncoderForSistaV1 class>>isBranchIfTrueAt:in: (in category 'instruction stream support') -----
+ isBranchIfTrueAt: pc in: method
+ "Answer whether the bytecode at pc is a conditional branch-if-true."
+
+ " 184-191 10111 iii Pop and Jump 0n True iii +1 (i.e., 1 through 8)
+ * 238 11101110 iiiiiiii Pop and Jump 0n True #iiiiiiii (+ Extend B * 256, where Extend B >= 0))"
+ | byte |
+ byte := self nonExtensionBytecodeAt: pc in: method.
+ ^byte >= 184 and: [byte <= 191 or: [byte = 238]]!

Item was added:
+ ----- Method: EncoderForSistaV1 class>>isExtension: (in category 'instruction stream support') -----
+ isExtension: bytecode
+ "Answer if the bytecode is an extension bytecode, i.e. one that extends
+ the range of the following bytecode."
+ ^bytecode >= 16rE0 and: [bytecode <= 16rE1]!

Item was added:
+ ----- Method: EncoderForSistaV1 class>>isJumpAt:in: (in category 'instruction stream support') -----
+ isJumpAt: pc in: method
+ "Answer whether the bytecode at pc is an (unconditional) jump."
+
+ " 176-183 10110 iii Jump iii + 1 (i.e., 1 through 8)
+ * 225 11100001 bbbbbbbb Extend B (Ext B = Ext B prev * 256 + Ext B)
+ * 237 11101101 iiiiiiii Jump #iiiiiiii (+ Extend B * 256, where bbbbbbbb = sddddddd, e.g. -32768 = i=0, a=0, s=1)"
+ | byte |
+ byte := self nonExtensionBytecodeAt: pc in: method.
+ ^byte >= 176 and: [byte <= 183 or: [byte = 237]]!

Item was added:
+ ----- Method: EncoderForSistaV1 class>>isJustPopAt:in: (in category 'instruction stream support') -----
+ isJustPopAt: pc in: method
+ "Answer whether the bytecode at pc is a pop."
+
+ ^(method at: pc) = 216 "216 11011000 Pop Stack Top"!

Item was added:
+ ----- Method: EncoderForSistaV1 class>>isRealSendAt:in: (in category 'instruction stream support') -----
+ isRealSendAt: pc in: method
+ "Answer whether the bytecode at pc is a real message-send, not blockCopy:."
+
+ ^self isSendAt: pc in: method!

Item was added:
+ ----- Method: EncoderForSistaV1 class>>isReturnAt:in: (in category 'instruction stream support') -----
+ isReturnAt: pc in: method
+ "Answer whether the bytecode at pc is a return from block."
+ " 88-91 010110 ii Return Receiver/true/false/nil
+ 92 01011100 Return top
+ 93 01011101 BlockReturn nil
+ * 94 01011110 BlockReturn Top [* return from enclosing block N, N = Extend A, then jump by Ext B ]"
+ ^(self nonExtensionBytecodeAt: pc in: method) between: 88 and: 94!

Item was added:
+ ----- Method: EncoderForSistaV1 class>>isSendAt:in: (in category 'instruction stream support') -----
+ isSendAt: pc in: method
+ "Answer whether the bytecode at pc is a message-send."
+
+ " 96-111 0110 iiii Send Arithmetic Message #iiii #(#+ #- #< #> #'<=' #'>=' #= #'~=' #* #/ #'\\' #@ #bitShift: #'//' #bitAnd: #bitOr:)
+ 112-119 01110 iii Send Special Message #iii #(#at: #at:put: #size #next #nextPut: #atEnd #'==' class)
+ 120 01111000 UNASSIGNED (was: blockCopy:)
+ 121 01111001 Send Special Message #value
+ 122-123 0111101 i Send Special Message #i #(#value: #do:)
+ 124-127 011111 ii Send Special Message #ii #(#new #new: #x #y))
+ 128-143 1000 iiii Send Literal Selector #iiii With 0 Argument
+ 144-159 1001 iiii Send Literal Selector #iiii With 1 Arguments
+ 160-175 1010 iiii Send Literal Selector #iiii With 2 Arguments
+ ** 234 11101010 iiiiijjj Send Literal Selector #iiiii (+ Extend A * 32) with jjj (+ Extend B * 8) Arguments
+ ** 235 11101011 iiiiijjj Send To Superclass Literal Selector #iiiii (+ Extend A * 32) with jjj (+ Extend B * 8) Arguments"
+
+ | byte |
+ byte := self nonExtensionBytecodeAt: pc in: method.
+ ^byte >= 96
+  and: [byte <= 175
+ or: [byte >= 234 and: [byte <= 235]]]!

Item was added:
+ ----- Method: EncoderForSistaV1 class>>isStoreAt:in: (in category 'instruction stream support') -----
+ isStoreAt: pc in: method
+ "Answer whether the bytecode at pc is a store or store-pop."
+
+ " 200-207 11001 iii Pop and Store Receiver Variable #iii
+ 208-215 11010 iii Pop and Store Temporary Variable #iii
+ * 224 11100000 aaaaaaaa Extend A (Ext A = Ext A prev * 256 + Ext A)
+ * 240 11110000 iiiiiiii Pop and Store Receiver Variable #iiiiiii (+ Extend A * 256)
+ * 241 11110001 iiiiiiii Pop and Store Literal Variable #iiiiiiii (+ Extend A * 256)
+ 242 11110010 iiiiiiii Pop and Store Temporary Variable #iiiiiiii
+ * 243 11110011 iiiiiiii Store Receiver Variable #iiiiiii (+ Extend A * 256)
+ * 244 11110100 iiiiiiii Store Literal Variable #iiiiiiii (+ Extend A * 256)
+ 245 11110110 iiiiiiii Store Temporary Variable #iiiiiiii
+
+ 252 11111100 kkkkkkkk jjjjjjjj Store Temp At kkkkkkkk In Temp Vector At: jjjjjjjj
+ 253 11111101 kkkkkkkk jjjjjjjj Pop and Store Temp At kkkkkkkk In Temp Vector At: jjjjjjjj"
+
+ | byte |
+ byte := self nonExtensionBytecodeAt: pc in: method.
+ ^byte >= 200
+  and: [byte <= 215
+ or: [(byte between: 240 and: 245)
+ or: [(byte between: 252 and: 253)]]]!

Item was added:
+ ----- Method: EncoderForSistaV1 class>>isStorePopAt:in: (in category 'instruction stream support') -----
+ isStorePopAt: pc in: method
+ "Answer whether the bytecode at pc is a store or store-pop."
+
+ " 200-207 11001 iii Pop and Store Receiver Variable #iii
+ 208-215 11010 iii Pop and Store Temporary Variable #iii
+ * 224 11100000 aaaaaaaa Extend A (Ext A = Ext A prev * 256 + Ext A)
+ * 240 11110000 iiiiiiii Pop and Store Receiver Variable #iiiiiii (+ Extend A * 256)
+ * 241 11110001 iiiiiiii Pop and Store Literal Variable #iiiiiiii (+ Extend A * 256)
+ 242 11110010 iiiiiiii Pop and Store Temporary Variable #iiiiiiii
+
+ 253 11111101 kkkkkkkk jjjjjjjj Pop and Store Temp At kkkkkkkk In Temp Vector At: jjjjjjjj"
+
+ | byte |
+ byte := self nonExtensionBytecodeAt: pc in: method.
+ ^byte >= 200
+  and: [byte <= 215
+ or: [(byte between: 240 and: 242)
+ or: [byte = 253]]]!

Item was added:
+ ----- Method: EncoderForSistaV1 class>>isSyntheticStoreAt:in:for: (in category 'instruction stream support') -----
+ isSyntheticStoreAt: pc in: method for: anInstructionStream
+ "Answer whether the bytecode at pc is a store or store-pop of an indirect temp vector,
+ which implement mutable closed-over variables in the the closure implementation.
+ Stores into temp vectors are not real stores.  N.B. pcPreviousTo:in:for: is slow, so filter
+ out any preceding bytecodes other than what looks like a pushNewArrayCode.  But the
+ pcPreviousTo:in:for: is still necessary, since the presence of a pcPreviousTo:in:for: in the
+ right place is potentially ambiguous, possibly part of a different bytecode sequence."
+
+ ^(self isTempStoreAt: pc in: method)
+  and: [pc - 2 >= method initialPC
+  and: [(method at: pc - 2) = self pushNewArrayCode
+  and: [(method at: pc - 1) <= 127
+  and: [pc - 2 = (self pcPreviousTo: pc in: method for: anInstructionStream)]]]]!

Item was added:
+ ----- Method: EncoderForSistaV1 class>>isTempStoreAt:in: (in category 'instruction stream support') -----
+ isTempStoreAt: pc in: method
+ "Answer if the bytecode at pc is a store or store-pop into a temporary variable.
+ 208-215 11010 iii Pop and Store Temporary Variable #iii
+ 242 11110010 iiiiiiii Pop and Store Temporary Variable #iiiiiiii
+ 245 11110110 iiiiiiii Store Temporary Variable #iiiiiiii"
+
+ | byte |
+ byte := method at: pc.
+ ^byte >= 208
+  and: [byte <= 215
+ or: [byte = 242 and: [byte = 245]]]!

Item was added:
+ ----- Method: EncoderForSistaV1 class>>method:refersInBytecodeToLiteral:specialSelectorIndex: (in category 'scanning') -----
+ method: method refersInBytecodeToLiteral: aLiteral specialSelectorIndex: specialOrNil
+ "Answer if method refers to the literal aLiteral in the bytecode, as opposed to in its literal frame."
+
+ " 77 01001101 Push true
+ 78 01001110 Push false
+ 79 01001111 Push nil
+ 80 01010000 Push 0
+ 81 01010001 Push 1
+ 88-91 010110 ii Return Receiver/true/false/nil
+ 93 01011101 BlockReturn nil
+ 96-111 0110 iiii Send Arithmetic Message #iiii #(#+ #- #< #> #'<=' #'>=' #= #'~=' #* #/ #'\\' #@ #bitShift: #'//' #bitAnd: #bitOr:)
+ 112-119 01110 iii Send Special Message #iii #(#at: #at:put: #size #next #nextPut: #atEnd #'==' class)
+ 120 01111000 UNASSIGNED (was: blockCopy:)
+ 121 01111001 Send Special Message #value
+ 122-123 0111101 i Send Special Message #i #(#value: #do:)
+ 124-127 011111 ii Send Special Message #ii #(#new #new: #x #y))
+ * 224 11100000 aaaaaaaa Extend A (Ext A = Ext A prev * 256 + Ext A)
+ * 225 11100001 sbbbbbbb Extend B (Ext B = Ext B prev * 256 + Ext B)
+ * 232 11101000 iiiiiiii Push Integer #iiiiiiii (+ Extend B * 256, where bbbbbbbb = sddddddd, e.g. -32768 = i=0, a=0, s=1)
+ * 233 11101001 iiiiiiii Push Character #iiiiiiii (+ Extend B * 256)
+ 249 11111001 xxxxxxxx syyyyyyy Reserved for Push Float"
+ | byte extended scanner |
+ specialOrNil ifNotNil:
+ [byte := specialOrNil + 95.
+ ^(InstructionStream on: method) scanFor: [:b| b = byte]].
+ extended := false.
+ aLiteral isInteger ifTrue:
+ [(aLiteral >= -32768 and: [aLiteral <= 32767]) ifFalse: [^false].
+ scanner := InstructionStream on: method.
+ (aLiteral >= 0 and: [aLiteral <= 255]) ifTrue:
+ [aLiteral <= 1 ifTrue:
+ [byte := aLiteral + 80.
+ ^scanner scanFor: [:b| b = byte]].
+ ^scanner scanFor:
+ [:b|
+ (b = 232
+ and: [extended not
+ and: [scanner followingByte = aLiteral]])
+ or: [extended := b = 225.
+ false]]].
+ byte := (aLiteral bitShift: -8) bitAnd: 255.
+ ^scanner scanFor:
+ [:b|
+ (b = 232
+ and: [extended
+ and: [scanner followingByte = (aLiteral bitAnd: 255)]])
+ or: [extended := b = 225 and: [scanner followingByte = byte].
+ false]]].
+ aLiteral isCharacter ifTrue:
+ [aLiteral asciiValue <= 65535 ifFalse: [^false].
+ scanner := InstructionStream on: method.
+ aLiteral asciiValue <= 255 ifTrue:
+ [^scanner scanFor:
+ [:b|
+ (b = 233
+ and: [extended not
+ and: [scanner followingByte = aLiteral]])
+ or: [extended := b = 225.
+ false]]].
+ byte := (aLiteral bitShift: -8) bitAnd: 255.
+ ^scanner scanFor:
+ [:b|
+ (b = 233
+ and: [extended
+ and: [scanner followingByte = (aLiteral bitAnd: 255)]])
+ or: [extended := b = 225 and: [scanner followingByte = byte].
+ false]]].
+ aLiteral == nil ifTrue:
+ [^(InstructionStream on: method) scanFor: [:b| b = 79 or: [b = 91 or: b = 93]]].
+ aLiteral == true ifTrue:
+ [^(InstructionStream on: method) scanFor: [:b| b = 77 or: [b = 89]]].
+ aLiteral == false ifTrue:
+ [^(InstructionStream on: method) scanFor: [:b| b = 78 or: [b = 90]]].
+
+ ^false!

Item was added:
+ ----- Method: EncoderForSistaV1 class>>nonExtensionBytecodeAt:in: (in category 'instruction stream support') -----
+ nonExtensionBytecodeAt: pc in: method
+ "Answer the actual bytecode at pc in method, skipping past any preceeding extensions."
+ | thePC bytecode |
+ thePC := pc.
+ [self isExtension: (bytecode := method at: thePC)] whileTrue:
+ [thePC := thePC + (self bytecodeSize: bytecode)].
+ ^bytecode!

Item was added:
+ ----- Method: EncoderForSistaV1 class>>nopCode (in category 'bytecode decoding') -----
+ nopCode
+ "Answer the call primitive bytecode, if it exists in the encoder's bytecode set, or nil if not.
+ 95 01011111 Nop"
+ ^95!

Item was added:
+ ----- Method: EncoderForSistaV1 class>>pcOfBlockCreationBytecodeForBlockStartingAt:in: (in category 'bytecode decoding') -----
+ pcOfBlockCreationBytecodeForBlockStartingAt: startpc in: method
+ "Answer the pc of the push closure bytecode whose block starts at startpc in method.
+ May need to back up to include extension bytecodes."
+
+ "* 224 11100000 aaaaaaaa Extend A (Ext A = Ext A prev * 256 + Ext A)
+ * 225 11100001 bbbbbbbb Extend B (Ext B = Ext B prev * 256 + Ext B)
+ ** 250 11111010 eeiiikkk jjjjjjjj Push Closure Num Copied iii (+ExtA//16*8) Num Args kkk (+ ExtA\\16*8) BlockSize jjjjjjjj (+ExtB*256). ee = num extensions"
+ | numExtensions |
+ self assert: (method at: startpc - 3) = 250.
+ numExtensions := (method at: startpc - 2) >> 6.
+ ^startpc - 3 - (numExtensions * 2)!

Item was added:
+ ----- Method: EncoderForSistaV1 class>>pushClosureBytecodeSize (in category 'bytecode decoding') -----
+ pushClosureBytecodeSize
+ "Answer the size of the push closure bytecode.
+ ** 250 11111010 eeiiikkk jjjjjjjj Push Closure Num Copied iii (+ExtA//16*8) Num Args kkk (+ ExtA\\16*8) BlockSize jjjjjjjj (+ExtB*256). ee = num extensions"
+ ^3!

Item was added:
+ ----- Method: EncoderForSistaV1 class>>pushNewArrayCode (in category 'bytecode decoding') -----
+ pushNewArrayCode
+ "231 11100111 jkkkkkkk Push (Array new: kkkkkkk) (j = 0)
+ & Pop kkkkkkk elements into: (Array new: kkkkkkk) (j = 1)"
+ ^231!

Item was added:
+ ----- Method: EncoderForSistaV1 class>>pushNilCode (in category 'bytecode decoding') -----
+ pushNilCode
+ "Answer the pushNil bytecode.
+ 79 01001111 Push nil"
+ ^79!

Item was added:
+ ----- Method: EncoderForSistaV1 class>>selectorToSendOrItselfFor:in:at: (in category 'instruction stream support') -----
+ selectorToSendOrItselfFor: anInstructionStream in: method at: pc
+ "If anInstructionStream is at a send bytecode then answer the send's selector,
+ otherwise answer anInstructionStream itself.  The rationale for answering
+ anInstructionStream instead of, say, nil, is that potentially any existing object
+ can be used as a selector, but since anInstructionStream postdates the method,
+ it can't be one of them.
+
+ The complication is that for convenience we allow the pc to point to the
+ raw send bytecode after its extension(s), or at the extension(s) preceeding it.
+ 96-111 0110 iiii Send Arithmetic Message #iiii (+ - < > <= >= = ~= * / \\ @ bitShift: // bitAnd: bitOr:)
+ 112-119 01110 iii Send Special Message #iii + 0 (at: at:put: size next nextPut: atEnd == class)
+ 120-127 01111 iii Send Special Message #iii + 8 (~~ value value: do: new new: x y)
+ 128-143 1000 iiii Send Literal Selector #iiii With 0 Argument
+ 144-159 1001 iiii Send Literal Selector #iiii With 1 Arguments
+ 160-175 1010 iiii Send Literal Selector #iiii With 2 Arguments
+ * 224 11100000 aaaaaaaa Extend A (Ext A = Ext A prev * 256 + Ext A)
+ * 225 11100001 bbbbbbbb Extend B (Ext B = Ext B prev * 256 + Ext B)
+ ** 234 11101010 iiiiijjj Send Literal Selector #iiiii (+ Extend A * 32) with jjj (+ Extend B * 8) Arguments
+ ** 235 11101011 iiiiijjj ExtendB < 64
+ ifTrue: [Send To Superclass Literal Selector #iiiii (+ Extend A * 32) with jjj (+ Extend B * 8) Arguments]
+ ifFalse: [Send To Superclass of Stacked Class Literal Selector #iiiii (+ Extend A * 32) with jjj (+ (Extend B "
+
+ | byte |
+ byte := method at: pc.
+ byte < 96 ifTrue:
+ [^anInstructionStream].
+ byte <= 175 ifTrue:
+ ["special byte or short send"
+ ^byte >= 128
+ ifTrue: [method literalAt: (byte bitAnd: 15) + 1]
+ ifFalse: [Smalltalk specialSelectorAt: byte - 95]].
+ byte < 234 ifTrue: "need to check for either extension cuz order of extensions is not restricted. so extB could preceed extA"
+ [(byte >= 224 and: [byte <= 225]) ifTrue:
+ [^self extensionsAt: pc in: method into:
+ [:extA :extB :nExtBytes| | byteAfter index |
+ byteAfter := method at: pc + nExtBytes.
+ (byteAfter >= 234 and: [byteAfter <= 235])
+ ifTrue:
+ [index := ((method at: pc + nExtBytes + 1) bitShift: -3) + (extA bitShift: 5).
+ method literalAt: index + 1]
+ ifFalse: [anInstructionStream]]].
+ ^anInstructionStream].
+ byte > 235 ifTrue:
+ [^anInstructionStream].
+ "they could be extended..."
+ ^self extensionsFor: pc in: method into:
+ [:extA :extB :nExtBytes| | index |
+ index := ((method at: pc + 1) bitShift: -3) + (extA bitShift: 5).
+ method literalAt: index + 1]!

Item was added:
+ ----- Method: EncoderForSistaV1 class>>stackDeltaForPrimitive:in: (in category 'bytecode decoding') -----
+ stackDeltaForPrimitive: primitiveIndex in: method
+ "Answer the stack delta for the callPrimitive: bytecode (see my class comment).
+ There is no delta for non-inlined primitives (its implicitly 0 - method numArgs).
+ Inlined primitives are grouped by the thousand by argument count, 32 args max ;-)."
+ ^primitiveIndex < 32678
+ ifTrue: [0]
+ ifFalse: [primitiveIndex - 32768 // 1000]!

Item was added:
+ ----- Method: EncoderForSistaV1 class>>superSendScanBlockUsing: (in category 'instruction stream support') -----
+ superSendScanBlockUsing: scanner
+ "Answer a block argument for InstructionStream>>scanFor:
+ that answers true for super sends."
+
+ "* 224 11100000 aaaaaaaa Extend A (Ext A = Ext A prev * 256 + Ext A)
+ * 225 11100001 sbbbbbbb Extend B (Ext B = Ext B prev * 256 + Ext B)
+ ** 235 11101011 iiiiijjj Send To Superclass Literal Selector #iiiii (+ Extend A * 32) with jjj (+ Extend B * 8) Arguments"
+
+ ^[:instr | instr = 235]!

Item was added:
+ ----- Method: EncoderForSistaV1 class>>supportsClosures (in category 'compiled method support') -----
+ supportsClosures
+ "Answer if the instruction set supports closures (contains
+ closure creation and indirect temp access bytecodes)."
+
+ ^true!

Item was added:
+ ----- Method: EncoderForSistaV1 class>>unusedBytecode (in category 'bytecode decoding') -----
+ unusedBytecode
+ "Answer the opcode of a single-byte unused bytecode, if it exists in the encoder's bytecode set, or nil if not."
+ ^223!

Item was added:
+ ----- Method: EncoderForSistaV1>>computeMethodHeaderForNumArgs:numTemps:numLits:primitive: (in category 'method encoding') -----
+ computeMethodHeaderForNumArgs: numArgs numTemps: numTemps numLits: numLits primitive: primitiveIndex
+ numTemps > 63 ifTrue:
+ [^self error: 'Cannot compile -- too many temporary variables'].
+ numLits > 65535 ifTrue:
+ [^self error: 'Cannot compile -- too many literals'].
+ ^SmallInteger minVal "sign bit is the flag for the alternative bytecode set"
+ + (numArgs bitShift: 24)
+ + (numTemps bitShift: 18)
+ "+ (largeBit bitShift: 17)" "largeBit gets filled in later"
+ + numLits
+ + (primitiveIndex > 0 ifTrue: [1 bitShift: 16] ifFalse: [0])!

Item was added:
+ ----- Method: EncoderForSistaV1>>genBranchPopFalse: (in category 'bytecode generation') -----
+ genBranchPopFalse: distance
+ (distance > 0 and: [distance < 9]) ifTrue:
+ ["192-199 11000 iii Pop and Jump 0n False iii + 1 (i.e., 1 through 8)"
+ stream nextPut: 191 + distance.
+ ^self].
+ ^self genBranchPopFalseLong: distance!

Item was added:
+ ----- Method: EncoderForSistaV1>>genBranchPopFalseLong: (in category 'bytecode generation') -----
+ genBranchPopFalseLong: distance
+ "239 11101111 iiiiiiii Pop and Jump 0n False #iiiiiiii (+ Extend B * 256, where Extend B >= 0) "
+ | distanceMod256 |
+ (distance < 0 or: [distance > 32767]) ifTrue:
+ [^self outOfRangeError: 'distance' index: distance range: 0 to: 32767].
+ distanceMod256 := (distance < 0 or: [distance > 255])
+ ifTrue:
+ [self genUnsignedSingleExtendB: (distance bitShift: -8).
+ distance bitAnd: 255]
+ ifFalse: [distance].
+ stream
+ nextPut: 239;
+ nextPut: distanceMod256!

Item was added:
+ ----- Method: EncoderForSistaV1>>genBranchPopTrue: (in category 'bytecode generation') -----
+ genBranchPopTrue: distance
+ (distance > 0 and: [distance < 9]) ifTrue:
+ ["184-191 10111 iii Pop and Jump 0n True iii + 1 (i.e., 1 through 8)"
+ stream nextPut: 183 + distance.
+ ^self].
+ ^self genBranchPopTrueLong: distance!

Item was added:
+ ----- Method: EncoderForSistaV1>>genBranchPopTrueLong: (in category 'bytecode generation') -----
+ genBranchPopTrueLong: distance
+ "238 11101110 iiiiiiii Pop and Jump 0n True #iiiiiiii (+ Extend B * 256, where Extend B >= 0)"
+ | distanceMod256 |
+ (distance < 0 or: [distance > 32767]) ifTrue:
+ [^self outOfRangeError: 'distance' index: distance range: 0 to: 32767].
+ (distance > 0 and: [distance < 9]) ifTrue:
+ ["184-191 10111 iii Pop and Jump 0n True iii + 1 (i.e., 1 through 8)"
+ stream nextPut: 183 + distance.
+ ^self].
+ distanceMod256 := (distance < 0 or: [distance > 255])
+ ifTrue:
+ [self genUnsignedSingleExtendB: (distance bitShift: -8).
+ distance bitAnd: 255]
+ ifFalse: [distance].
+ stream
+ nextPut: 238;
+ nextPut: distanceMod256!

Item was added:
+ ----- Method: EncoderForSistaV1>>genCallInlinePrimitive: (in category 'extended bytecode generation') -----
+ genCallInlinePrimitive: primitiveIndex
+ " 248 (2) 11111000 iiiiiiii mssjjjjj Call Primitive #iiiiiiii + (jjjjj * 256)
+ m=1 means inlined primitive, no hard return after execution.
+ ss defines the unsafe operation set used to encode the operations.
+ (ss = 0 means sista unsafe operations, ss = 01 means lowcode operations, other numbers are not used)"
+ "N.B. We could have made CallPrimitive a 2-byte code taking an extension, but that would
+ complicate the VM's determination of the primitive number and the primitive error code
+ store since the extension, being optional, would make the sequence variable length."
+ (primitiveIndex < 1 or: [primitiveIndex > 32767]) ifTrue:
+ [self outOfRangeError: 'primitive index' index: primitiveIndex range: 1 to: 32767].
+ stream
+ nextPut: 248;
+ nextPut: (primitiveIndex bitAnd: 255);
+ nextPut: (primitiveIndex bitShift: -8) + 128!

Item was added:
+ ----- Method: EncoderForSistaV1>>genCallPrimitive: (in category 'bytecode generation') -----
+ genCallPrimitive: primitiveIndex
+ "248 (2) 11111000 iiiiiiii mssjjjjj Call Primitive #iiiiiiii + (jjjjj * 256)
+ m=1 means inlined primitive, no hard return after execution.
+ ss defines the unsafe operation set used to encode the operations.
+ (ss = 0 means sista unsafe operations, ss = 01 means lowcode operations, other numbers are not used)"
+ "N.B. We could have made CallPrimitive a 2-byte code taking an extension, but that would
+ complicate the VM's determination of the primitive number and the primitive error code
+ store since the extension, being optional, would make the sequence variable length."
+ (primitiveIndex < 1 or: [primitiveIndex > 32767]) ifTrue:
+ [self outOfRangeError: 'primitive index' index: primitiveIndex range: 1 to: 32767].
+ stream
+ nextPut: 248;
+ nextPut: (primitiveIndex bitAnd: 255);
+ nextPut: (primitiveIndex bitShift: -8)!

Item was added:
+ ----- Method: EncoderForSistaV1>>genDup (in category 'bytecode generation') -----
+ genDup
+ "83 01010011 Duplicate Stack Top"
+ stream nextPut: 83!

Item was added:
+ ----- Method: EncoderForSistaV1>>genInlineSmallIntegerAdd (in category 'in-line primitive generation') -----
+ genInlineSmallIntegerAdd
+ ^self genCallInlinePrimitive: 0!

Item was added:
+ ----- Method: EncoderForSistaV1>>genJump: (in category 'bytecode generation') -----
+ genJump: distance
+ (distance > 0 and: [distance < 9]) ifTrue:
+ ["176-183 10110 iii Jump iii + 1 (i.e., 1 through 8)"
+ stream nextPut: 175 + distance.
+ ^self].
+ "237 11101101 iiiiiiii Jump #iiiiiiii (+ Extend B * 256, where bbbbbbbb = sddddddd, e.g. -32768 = i=0, a=0, s=1)"
+ ^self genJumpLong: distance!

Item was added:
+ ----- Method: EncoderForSistaV1>>genJumpLong: (in category 'bytecode generation') -----
+ genJumpLong: distance
+ "237 11101101 iiiiiiii Jump #iiiiiiii (+ Extend B * 256, where bbbbbbbb = sddddddd, e.g. -32768 = i=0, a=0, s=1)"
+ (distance between: -32768 and: 32767) ifFalse:
+ [^self outOfRangeError: 'index' index: distance range: -32768 to: 32767].
+ (distance < 0 or: [distance > 255]) ifTrue:
+ [self genSignedSingleExtendB: (distance bitShift: -8)].
+ stream
+ nextPut: 237;
+ nextPut: (distance bitAnd: 255)!

Item was added:
+ ----- Method: EncoderForSistaV1>>genNop (in category 'bytecode generation') -----
+ genNop
+ "95 01011111 Nop"
+ stream nextPut: 95!

Item was added:
+ ----- Method: EncoderForSistaV1>>genPop (in category 'bytecode generation') -----
+ genPop
+ "216 11011000 Pop Stack Top"
+ stream nextPut: 216!

Item was added:
+ ----- Method: EncoderForSistaV1>>genPushCharacter: (in category 'bytecode generation') -----
+ genPushCharacter: aCharacterOrCode
+ "233 11101001 i i i i i i i i Push Character #iiiiiiii (+ Extend B * 256)"
+ "Why restrict the range to 16 bits when we could encode arbitrarily 32-bit Characters?
+ Well, 16 bits requires 4 bytes (extB + byte, 78 + byte) and so beyond this range we
+ lose space verses a single-byte pushLiteral and a 4 byte Character literal on 32-bits.
+ And generating the same bytecode on 64-bit and 32-bit is important if we want to be
+ able to load binary code from one to the other (e.g. via Fuel)."
+ | code |
+ code := aCharacterOrCode isInteger ifTrue: [aCharacterOrCode] ifFalse: [aCharacterOrCode asInteger].
+ (code < 0 or: [code > 65535]) ifTrue:
+ [^self outOfRangeError: 'character' index: code range: 0 to: 65535].
+ (code > 255) ifTrue:
+ [self genUnsignedSingleExtendB: (code bitShift: -8)].
+ stream
+ nextPut: 233;
+ nextPut: (code bitAnd: 255)!

Item was added:
+ ----- Method: EncoderForSistaV1>>genPushClosureCopyNumCopiedValues:numArgs:jumpSize: (in category 'bytecode generation') -----
+ genPushClosureCopyNumCopiedValues: numCopied numArgs: numArgs jumpSize: jumpSize
+ "250 11111010 eeiiikkk jjjjjjjj Push Closure Num Copied iii (+ Ext A // 16 * 8) Num Args kkk (+ Ext A \\ 16 * 8) BlockSize jjjjjjjj (+ Ext B * 256). ee = num extensions"
+ "Including numExtensions makes decoding the bytecode quicker since it obviates having to scan from the beginning of a method."
+ | numExtensions numCopiedMod8 numArgsMod8 extA |
+ (jumpSize < 0 or: [jumpSize > 65535]) ifTrue:
+ [^self outOfRangeError: 'block size' index: jumpSize range: 0 to: 65535].
+ (numCopied < 0 or: [numCopied > 127]) ifTrue:
+ [^self outOfRangeError: 'num copied' index: numCopied range: 0 to: 127].
+ (numArgs < 0 or: [numArgs > 127]) ifTrue:
+ [^self outOfRangeError: 'num args' index: numArgs range: 0 to: 127].
+ extA := numExtensions := 0.
+ (numArgsMod8 := numArgs) > 7 ifTrue:
+ [extA := numArgs // 8.
+ numArgsMod8 := numArgsMod8 \\ 8].
+ (numCopiedMod8 := numCopied) > 7 ifTrue:
+ [extA := extA + (numCopied // 8 * 16).
+ numCopiedMod8 := numCopiedMod8 \\ 8].
+ extA ~= 0 ifTrue:
+ [self genUnsignedSingleExtendA: extA.
+ numExtensions := 1].
+ jumpSize > 255 ifTrue:
+ [numExtensions := numExtensions + 1.
+ self genUnsignedSingleExtendB: jumpSize // 256].
+ stream
+ nextPut: 250;
+ nextPut: (numExtensions bitShift: 6) + (numCopiedMod8 bitShift: 3) + numArgsMod8;
+ nextPut: (jumpSize bitAnd: 16rFF)!

Item was added:
+ ----- Method: EncoderForSistaV1>>genPushConsArray: (in category 'bytecode generation') -----
+ genPushConsArray: size
+ (size < 0 or: [size > 127]) ifTrue:
+ [^self outOfRangeError: 'size' index: size range: 0 to: 127].
+ "231 11100111 jkkkkkkk Push (Array new: kkkkkkk) (j = 0)
+ & Pop kkkkkkk elements into: (Array new: kkkkkkk) (j = 1)"
+ stream
+ nextPut: 231;
+ nextPut: size + 128!

Item was added:
+ ----- Method: EncoderForSistaV1>>genPushFullClosure:numCopied: (in category 'extended bytecode generation') -----
+ genPushFullClosure: compiledBlockLiteralIndex numCopied: numCopied
+ "By default the closure will have an outer context and the receiver will be fetched from the current context"
+ self genPushFullClosure: compiledBlockLiteralIndex numCopied: numCopied receiverOnStack: false ignoreOuterContext: false!

Item was added:
+ ----- Method: EncoderForSistaV1>>genPushFullClosure:numCopied:receiverOnStack:ignoreOuterContext: (in category 'extended bytecode generation') -----
+ genPushFullClosure: compiledBlockLiteralIndex numCopied: numCopied receiverOnStack: receiverOnStack ignoreOuterContext: ignoreOuterContext
+ "* 249 11111001 xxxxxxxx siyyyyyy push Closure Compiled block literal index xxxxxxxx (+ Extend A * 256) numCopied yyyyyy receiverOnStack: s = 1 ignoreOuterContext: i = 1"
+ | extendedIndex |
+ (numCopied < 0 or: [numCopied > 64]) ifTrue:
+ [self outOfRangeError: 'num copied' index: numCopied range: 1 to: 64].
+ (compiledBlockLiteralIndex < 0 or: [compiledBlockLiteralIndex > 32767]) ifTrue:
+ [^self outOfRangeError: 'index' index: compiledBlockLiteralIndex range: 0 to: 32767].
+ (extendedIndex := compiledBlockLiteralIndex) > 255 ifTrue:
+ [self genUnsignedSingleExtendA: extendedIndex // 256.
+ extendedIndex := extendedIndex \\ 256].
+ stream
+ nextPut: 249;
+ nextPut: extendedIndex;
+ nextPut: receiverOnStack asBit << 7 + (ignoreOuterContext asBit << 6) + numCopied!

Item was added:
+ ----- Method: EncoderForSistaV1>>genPushInstVar: (in category 'bytecode generation') -----
+ genPushInstVar: instVarIndex
+ (instVarIndex between: 0 and: 15) ifTrue:
+ ["0-15 0000iiii Push Receiver Variable #iiii"
+ stream nextPut: 0 + instVarIndex.
+ ^self].
+ self genPushInstVarLong: instVarIndex!

Item was added:
+ ----- Method: EncoderForSistaV1>>genPushInstVarLong: (in category 'bytecode generation') -----
+ genPushInstVarLong: instVarIndex
+ "226 11100010 i i i i i i i i Push Receiver Variable #iiiiiiii (+ Extend A * 256)"
+ "See also MaybeContextInstanceVariableNode"
+ (instVarIndex < 0 or: [instVarIndex > 65535]) ifTrue:
+ [^self outOfRangeError: 'index' index: instVarIndex range: 0 to: 65535].
+ instVarIndex > 255 ifTrue:
+ [self genUnsignedSingleExtendA: instVarIndex // 256].
+ stream
+ nextPut: 226;
+ nextPut: instVarIndex \\ 256!

Item was added:
+ ----- Method: EncoderForSistaV1>>genPushInteger: (in category 'bytecode generation') -----
+ genPushInteger: anInteger
+ "80 01010000 Push 0
+ 81 01010001 Push 1
+ 232 11101000 i i i i i i i i Push Integer #iiiiiiii (+ Extend B * 256, where bbbbbbbb = sddddddd, e.g. -32768 = i=0, a=0, s=1)"
+ "Why restrict the range to 16 bits when we could encode arbitrarily large integers?
+ Well, 16 bits requires 4 bytes (extB + byte, 78 + byte) and so beyond this range we lose space
+ verses a single-byte pushLiteral and a 4 byte integer literal on 32-bits.  And generating the same
+ bytecode on 64-bit and 32-bit is important if we want to be able to load binary code from one to
+ the other (e.g. via Fuel)."
+ anInteger = 0 ifTrue:
+ [stream nextPut: 80.
+ ^self].
+ anInteger = 1 ifTrue:
+ [stream nextPut: 81.
+ ^self].
+ (anInteger < -32768 or: [anInteger > 32767]) ifTrue:
+ [^self outOfRangeError: 'integer' index: anInteger range: -32768 to: 32767].
+ (anInteger < 0 or: [anInteger > 255]) ifTrue:
+ [self genSignedSingleExtendB: (anInteger bitShift: -8)].
+ stream
+ nextPut: 232;
+ nextPut: (anInteger bitAnd: 255)!

Item was added:
+ ----- Method: EncoderForSistaV1>>genPushLiteral: (in category 'bytecode generation') -----
+ genPushLiteral: literalIndex
+ | extendedIndex |
+ (literalIndex < 0 or: [literalIndex > 65535]) ifTrue:
+ [^self outOfRangeError: 'index' index: literalIndex range: 0 to: 65535].
+ literalIndex < 32 ifTrue:
+ ["32-63 001iiiii Push Literal #iiiii"
+ stream nextPut: 32 + literalIndex.
+ ^self].
+ "228 11100100 i i i i i i i i Push Literal #iiiiiiii (+ Extend A * 256)"
+ (extendedIndex := literalIndex) > 255 ifTrue:
+ [self genUnsignedSingleExtendA: extendedIndex // 256.
+ extendedIndex := extendedIndex \\ 256].
+ stream
+ nextPut: 228;
+ nextPut: extendedIndex!

Item was added:
+ ----- Method: EncoderForSistaV1>>genPushLiteralVar: (in category 'bytecode generation') -----
+ genPushLiteralVar: literalIndex
+ | extendedIndex |
+ (literalIndex < 0 or: [literalIndex > 65535]) ifTrue:
+ [^self outOfRangeError: 'index' index: literalIndex range: 0 to: 65535].
+ literalIndex < 16 ifTrue:
+ ["16-31 0001 i i i i Push Literal Variable #iiii"
+ stream nextPut: 16 + literalIndex.
+ ^self].
+ "227 11100011 i i i i i i i i Push Literal Variable #iiiiiiii (+ Extend A * 256)"
+ (extendedIndex := literalIndex) > 255 ifTrue:
+ [self genUnsignedSingleExtendA: extendedIndex // 256.
+ extendedIndex := extendedIndex \\ 256].
+ stream
+ nextPut: 227;
+ nextPut: extendedIndex!

Item was added:
+ ----- Method: EncoderForSistaV1>>genPushNewArray: (in category 'bytecode generation') -----
+ genPushNewArray: size
+ (size < 0 or: [size > 127]) ifTrue:
+ [^self outOfRangeError: 'size' index: size range: 0 to: 127].
+ "231 11100111 jkkkkkkk Push (Array new: kkkkkkk) (j = 0)
+ & Pop kkkkkkk elements into: (Array new: kkkkkkk) (j = 1)"
+ stream
+ nextPut: 231;
+ nextPut: size!

Item was added:
+ ----- Method: EncoderForSistaV1>>genPushReceiver (in category 'bytecode generation') -----
+ genPushReceiver
+ "76 01001100 Push Receiver"
+ stream nextPut: 76!

Item was added:
+ ----- Method: EncoderForSistaV1>>genPushRemoteTemp:inVectorAt: (in category 'bytecode generation') -----
+ genPushRemoteTemp: tempIndex inVectorAt: tempVectorIndex
+ "251 11111011 kkkkkkkk sjjjjjjj Push Temp At kkkkkkkk In Temp Vector At: jjjjjjj, s = 1 implies remote inst var access instead of remote temp vector access"
+ (tempIndex < 0 or: [tempIndex >= 256]) ifTrue:
+ [^self outOfRangeError: 'remoteTempIndex' index: tempIndex range: 0 to: 255].
+ (tempVectorIndex < 0 or: [tempVectorIndex >= 128]) ifTrue:
+ [^self outOfRangeError: 'tempVectorIndex' index: tempVectorIndex range: 0 to: 127].
+ stream
+ nextPut: 251;
+ nextPut: tempIndex;
+ nextPut: tempVectorIndex!

Item was added:
+ ----- Method: EncoderForSistaV1>>genPushSpecialLiteral: (in category 'bytecode generation') -----
+ genPushSpecialLiteral: aLiteral
+ "77 01001101 Push true
+ 78 01001110 Push false
+ 79 01001111 Push nil
+ 80 01010000 Push 0
+ 81 01010001 Push 1
+ 232 11101000 iiiiiiii Push Integer #iiiiiiii (+ Extend B * 256, where bbbbbbbb = sddddddd, e.g. -32768 = i=0, a=0, s=1)"
+ | index |
+ aLiteral isInteger ifTrue:
+ [aLiteral == 0 ifTrue:
+ [stream nextPut: 80.
+ ^self].
+ aLiteral == 1 ifTrue:
+ [stream nextPut: 81.
+ ^self].
+ ^self genPushInteger: aLiteral].
+ index := #(true false nil)
+ indexOf: aLiteral
+ ifAbsent: [^self error: 'push special literal: ', aLiteral printString,  ' is not one of true false nil'].
+ stream nextPut: 76 + index!

Item was added:
+ ----- Method: EncoderForSistaV1>>genPushTemp: (in category 'bytecode generation') -----
+ genPushTemp: tempIndex
+ (tempIndex < 0 or: [tempIndex > 63]) ifTrue:
+ [^self outOfRangeError: 'index' index: tempIndex range: 0 to: 63].
+ tempIndex < 12 ifTrue:
+ ["64-71 01000 i i i Push Temporary Variable #iii
+   72-75 010010 i i Push Temporary Variable #ii + 8"
+ stream nextPut: 64 + tempIndex.
+ ^self].
+ "229 11100101 i i i i i i i i Push Temporary Variable #iiiiiiii"
+ stream
+ nextPut: 229;
+ nextPut: tempIndex!

Item was added:
+ ----- Method: EncoderForSistaV1>>genPushThisContext (in category 'bytecode generation') -----
+ genPushThisContext
+ "82 01010010 Push thisContext, (then e.g. Extend B 1 = push thisProcess)"
+ stream nextPut: 82!

Item was added:
+ ----- Method: EncoderForSistaV1>>genReturnReceiver (in category 'bytecode generation') -----
+ genReturnReceiver
+ "88-91 010110 ii Return Receiver/true/false/nil"
+ stream nextPut: 88!

Item was added:
+ ----- Method: EncoderForSistaV1>>genReturnSpecialLiteral: (in category 'bytecode generation') -----
+ genReturnSpecialLiteral: aLiteral
+ "88-91 010110 ii Return Receiver/true/false/nil"
+ | index |
+ index := #(true false nil) indexOf: aLiteral ifAbsent: 0.
+ index = 0 ifTrue:
+ [^self error: 'return special literal: ', aLiteral printString,  ' is not one of true false nil'].
+ stream nextPut: 88 + index!

Item was added:
+ ----- Method: EncoderForSistaV1>>genReturnTop (in category 'bytecode generation') -----
+ genReturnTop
+ "92 1011100 Return Stack Top From Message"
+ stream nextPut: 92!

Item was added:
+ ----- Method: EncoderForSistaV1>>genReturnTopToCaller (in category 'bytecode generation') -----
+ genReturnTopToCaller
+ "94 01011110 Return Stack Top From Block [* return from enclosing block N, ExtA]"
+ "If extended, the least significant bit of the extension determines if we return to the caller or not
+ and the most significant bits determine how many levels of the static chain to return from.
+ ExtA = iiiiiiij
+ iiiiiii=0,j=0 => return to caller
+ iiiiiii=0,j=1 => illegal
+ iiiiiii=1,j=0 => return to outerContext
+ iiiiiii=1,j=1 => return to outerContext sender/return from outerContext
+ iiiiiii=2,j=0 => return to outerContext outerContext
+ iiiiiii=2,j=1 => return to outerContext outerContext sender/return from outerContext outerContext
+ etc"
+
+ stream nextPut: 94!

Item was added:
+ ----- Method: EncoderForSistaV1>>genSend:numArgs: (in category 'bytecode generation') -----
+ genSend: selectorLiteralIndex numArgs: nArgs
+ | extendedIndex extendedNArgs |
+ (selectorLiteralIndex < 0 or: [selectorLiteralIndex > 65535]) ifTrue:
+ [^self outOfRangeError: 'selectorLiteralIndex' index: selectorLiteralIndex range: 0 to: 65535].
+ (nArgs < 0 or: [nArgs > 31]) ifTrue:
+ [^self outOfRangeError: 'numArgs' index: nArgs range: 0 to: 31 "!!!!"].
+ (selectorLiteralIndex < 16 and: [nArgs < 3]) ifTrue:
+ ["128-143 1000 iiii Send Literal Selector #iiii With 0 Argument
+  144-159 1001 iiii Send Literal Selector #iiii With 1 Arguments
+  160-175 1010 iiii Send Literal Selector #iiii With 2 Arguments"
+ stream nextPut: 128 + (nArgs * 16) + selectorLiteralIndex.
+ ^self].
+ (extendedIndex := selectorLiteralIndex) > 31 ifTrue:
+ [self genUnsignedMultipleExtendA: extendedIndex // 32.
+ extendedIndex := extendedIndex \\ 32].
+ (extendedNArgs := nArgs) > 7 ifTrue:
+ [self genUnsignedSingleExtendB: extendedNArgs // 8.
+ extendedNArgs := extendedNArgs \\ 8].
+ "234 11101010 i i i i i j j j Send Literal Selector #iiiii (+ Extend A * 32) with jjj (+ Extend B * 8) Arguments"
+ stream
+ nextPut: 234;
+ nextPut: extendedNArgs + (extendedIndex * 8)!

Item was added:
+ ----- Method: EncoderForSistaV1>>genSendDirectedSuper:numArgs: (in category 'extended bytecode generation') -----
+ genSendDirectedSuper: selectorLiteralIndex numArgs: nArgs
+ | extendedIndex |
+ (selectorLiteralIndex < 0 or: [selectorLiteralIndex > 65535]) ifTrue:
+ [^self outOfRangeError: 'selectorLiteralIndex' index: selectorLiteralIndex range: 0 to: 65535].
+ (nArgs < 0 or: [nArgs > 31]) ifTrue:
+ [^self outOfRangeError: 'numArgs' index: nArgs range: 0 to: 31 "!!!!"].
+ (extendedIndex := selectorLiteralIndex) > 31 ifTrue:
+ [self genUnsignedMultipleExtendA: extendedIndex // 32.
+ extendedIndex := extendedIndex \\ 32].
+ "Bit 6 of the ExtB byte is the directed send flag.  Bit 6 allows for future expansion to up to 255 args."
+ self genUnsignedSingleExtendB: nArgs // 8 + 64.
+ "235 11101011 iiiiijjj Send To Superclass Literal Selector #iiiii (+ Extend A * 32) with jjj (+ Extend B * 8) Arguments"
+ stream
+ nextPut: 235;
+ nextPut: nArgs \\ 8 + (extendedIndex * 8)!

Item was added:
+ ----- Method: EncoderForSistaV1>>genSendSpecial:numArgs: (in category 'bytecode generation') -----
+ genSendSpecial: specialSelectorIndex numArgs: nArgs
+ self assert: (specialSelectorIndex between: 1 and: Smalltalk specialSelectorSize).
+ self assert: nArgs = (Smalltalk specialNargsAt: specialSelectorIndex).
+ "Special selector sends.
+ 96-111 0110 iiii Send Arithmetic Message #iiii #(#+ #- #< #> #'<=' #'>=' #= #'~=' #* #/ #'\\' #@ #bitShift: #'//' #bitAnd: #bitOr:)
+ 112-119 01110 iii Send Special Message #iii #(#at: #at:put: #size ? ? ? #'==' class ? value value: ? ? ? ? ?)"
+
+ stream nextPut: specialSelectorIndex + 95!

Item was added:
+ ----- Method: EncoderForSistaV1>>genSendSuper:numArgs: (in category 'bytecode generation') -----
+ genSendSuper: selectorLiteralIndex numArgs: nArgs
+ | extendedIndex extendedNArgs |
+ (selectorLiteralIndex < 0 or: [selectorLiteralIndex > 65535]) ifTrue:
+ [^self outOfRangeError: 'selectorLiteralIndex' index: selectorLiteralIndex range: 0 to: 65535].
+ (nArgs < 0 or: [nArgs > 31]) ifTrue:
+ [^self outOfRangeError: 'numArgs' index: nArgs range: 0 to: 31 "!!!!"].
+ (extendedIndex := selectorLiteralIndex) > 31 ifTrue:
+ [self genUnsignedMultipleExtendA: extendedIndex // 32.
+ extendedIndex := extendedIndex \\ 32].
+ (extendedNArgs := nArgs) > 7 ifTrue:
+ [self genUnsignedSingleExtendB: extendedNArgs // 8.
+ extendedNArgs := extendedNArgs \\ 8].
+ "235 11101011 iiiiijjj Send To Superclass Literal Selector #iiiii (+ Extend A * 32) with jjj (+ Extend B * 8) Arguments"
+ stream
+ nextPut: 235;
+ nextPut: extendedNArgs + (extendedIndex * 8)!

Item was added:
+ ----- Method: EncoderForSistaV1>>genSignedSingleExtendB: (in category 'bytecode generation') -----
+ genSignedSingleExtendB: extendedIndex
+ (extendedIndex between: -128 and: 127) ifFalse:
+ [^self outOfRangeError: 'index' index: extendedIndex range: -128 to: 127].
+ "225 11100001 sbbbbbbb Extend B (Ext B = Ext B prev * 256 + Ext B)"
+ stream
+ nextPut: 225;
+ nextPut: (extendedIndex >= 0 ifTrue: [extendedIndex] ifFalse: [extendedIndex + 256]) !

Item was added:
+ ----- Method: EncoderForSistaV1>>genStoreInstVar: (in category 'bytecode generation') -----
+ genStoreInstVar: instVarIndex
+ "243 11110011 iiiiiiii Store Receiver Variable #iiiiiii (+ Extend A * 256)"
+ self genStoreInstVarLong: instVarIndex!

Item was added:
+ ----- Method: EncoderForSistaV1>>genStoreInstVarLong: (in category 'bytecode generation') -----
+ genStoreInstVarLong: instVarIndex
+ "243 11110011 iiiiiiii Store Receiver Variable #iiiiiii (+ Extend A * 256)"
+ (instVarIndex < 0 or: [instVarIndex > 65535]) ifTrue:
+ [^self outOfRangeError: 'index' index: instVarIndex range: 0 to: 65535].
+ instVarIndex > 255 ifTrue:
+ [self genUnsignedSingleExtendA: instVarIndex // 256].
+ stream
+ nextPut: 243;
+ nextPut: instVarIndex \\ 256!

Item was added:
+ ----- Method: EncoderForSistaV1>>genStoreLiteralVar: (in category 'bytecode generation') -----
+ genStoreLiteralVar: literalIndex
+ "244 11110100 iiiiiiii Store Literal Variable #iiiiiiii (+ Extend A * 256)"
+ (literalIndex < 0 or: [literalIndex > 65535]) ifTrue:
+ [^self outOfRangeError: 'index' index: literalIndex range: 0 to: 65535].
+ literalIndex > 255 ifTrue:
+ [self genUnsignedSingleExtendA: literalIndex // 256].
+ stream
+ nextPut: 244;
+ nextPut: literalIndex \\ 256!

Item was added:
+ ----- Method: EncoderForSistaV1>>genStorePopInstVar: (in category 'bytecode generation') -----
+ genStorePopInstVar: instVarIndex
+ "200-207 11001 iii Pop and Store Receiver Variable #iii
+ 240 11110000 iiiiiiii Pop and Store Receiver Variable #iiiiiii (+ Extend A * 256)"
+ (instVarIndex < 0 or: [instVarIndex > 7]) ifTrue:
+ [^self genStorePopInstVarLong: instVarIndex].
+ stream nextPut: 200 + instVarIndex!

Item was added:
+ ----- Method: EncoderForSistaV1>>genStorePopInstVarLong: (in category 'bytecode generation') -----
+ genStorePopInstVarLong: instVarIndex
+ "240 11110000 iiiiiiii Pop and Store Receiver Variable #iiiiiii (+ Extend A * 256)"
+ (instVarIndex < 0 or: [instVarIndex > 65535]) ifTrue:
+ [^self outOfRangeError: 'index' index: instVarIndex range: 0 to: 65535].
+ instVarIndex > 255 ifTrue:
+ [self genUnsignedSingleExtendA: instVarIndex // 256].
+ stream
+ nextPut: 240;
+ nextPut: instVarIndex \\ 256!

Item was added:
+ ----- Method: EncoderForSistaV1>>genStorePopLiteralVar: (in category 'bytecode generation') -----
+ genStorePopLiteralVar: literalIndex
+ "241 11110001 iiiiiiii Pop and Store Literal Variable #iiiiiiii (+ Extend A * 256)"
+ (literalIndex < 0 or: [literalIndex > 65535]) ifTrue:
+ [^self outOfRangeError: 'index' index: literalIndex range: 0 to: 65535].
+ literalIndex > 255 ifTrue:
+ [self genUnsignedSingleExtendA: literalIndex // 256].
+ stream
+ nextPut: 241;
+ nextPut: literalIndex \\ 256!

Item was added:
+ ----- Method: EncoderForSistaV1>>genStorePopRemoteTemp:inVectorAt: (in category 'bytecode generation') -----
+ genStorePopRemoteTemp: tempIndex inVectorAt: tempVectorIndex
+ "* 253 (3) 11111101 kkkkkkkk sjjjjjjj Pop and Store Temp At kkkkkkkk In Temp Vector At: jjjjjjj s = 1 implies remote inst var access instead of remote temp vector access"
+ (tempIndex < 0 or: [tempIndex >= 256]) ifTrue:
+ [^self outOfRangeError: 'remoteTempIndex' index: tempIndex range: 0 to: 255].
+ (tempVectorIndex < 0 or: [tempVectorIndex >= 128]) ifTrue:
+ [^self outOfRangeError: 'tempVectorIndex' index: tempVectorIndex range: 0 to: 127].
+ stream
+ nextPut: 253;
+ nextPut: tempIndex;
+ nextPut: tempVectorIndex!

Item was added:
+ ----- Method: EncoderForSistaV1>>genStorePopTemp: (in category 'bytecode generation') -----
+ genStorePopTemp: tempIndex
+ "208-215 11010 iii Pop and Store Temporary Variable #iii
+ 242 11110010 iiiiiiii Pop and Store Temporary Variable #iiiiiiii"
+ (tempIndex < 0 or: [tempIndex > 63]) ifTrue:
+ [^self outOfRangeError: 'index' index: tempIndex range: 0 to: 63].
+ tempIndex < 8 ifTrue:
+ [stream nextPut: 208 + tempIndex.
+ ^self].
+ stream
+ nextPut: 242;
+ nextPut: tempIndex!

Item was added:
+ ----- Method: EncoderForSistaV1>>genStoreRemoteTemp:inVectorAt: (in category 'bytecode generation') -----
+ genStoreRemoteTemp: tempIndex inVectorAt: tempVectorIndex
+ "*252 (3) 11111100 kkkkkkkk sjjjjjjj Store Temp At kkkkkkkk In Temp Vector At: jjjjjjj s = 1 implies remote inst var access instead of remote temp vector access"
+ (tempIndex < 0 or: [tempIndex >= 256]) ifTrue:
+ [^self outOfRangeError: 'remoteTempIndex' index: tempIndex range: 0 to: 255].
+ (tempVectorIndex < 0 or: [tempVectorIndex >= 128]) ifTrue:
+ [^self outOfRangeError: 'tempVectorIndex' index: tempVectorIndex range: 0 to: 127].
+ stream
+ nextPut: 252;
+ nextPut: tempIndex;
+ nextPut: tempVectorIndex!

Item was added:
+ ----- Method: EncoderForSistaV1>>genStoreTemp: (in category 'bytecode generation') -----
+ genStoreTemp: tempIndex
+ "245 11110110 iiiiiiii Store Temporary Variable #iiiiiiii"
+ (tempIndex < 0 or: [tempIndex > 63]) ifTrue:
+ [^self outOfRangeError: 'index' index: tempIndex range: 0 to: 63].
+ stream
+ nextPut: 245;
+ nextPut: tempIndex!

Item was added:
+ ----- Method: EncoderForSistaV1>>genTrapIfNotInstanceOf: (in category 'bytecode generation') -----
+ genTrapIfNotInstanceOf: literalIndex
+ "* 236 11101100 iiiiiiii Trap If Not Instance Of Behavior/Array Of Behavior #iiiiiiii (+ Extend A * 256, where Extend A >= 0)"
+
+ | extendedIndex |
+ (literalIndex < 0 or: [literalIndex > 65535]) ifTrue:
+ [^self outOfRangeError: 'index' index: literalIndex range: 0 to: 65536].
+ (extendedIndex := literalIndex) > 255 ifTrue:
+ [self genUnsignedSingleExtendA: extendedIndex // 256.
+ extendedIndex := extendedIndex \\ 256].
+ stream
+ nextPut: 236;
+ nextPut: extendedIndex!

Item was added:
+ ----- Method: EncoderForSistaV1>>genUnsignedMultipleExtendA: (in category 'bytecode generation') -----
+ genUnsignedMultipleExtendA: extendedIndex
+ "224 11100000 aaaaaaaa Extend A (Ext A = Ext A prev * 256 + Ext A)"
+ extendedIndex > 255 ifTrue:
+ [self genUnsignedMultipleExtendA: extendedIndex // 256].
+ stream
+ nextPut: 224;
+ nextPut: extendedIndex \\ 256!

Item was added:
+ ----- Method: EncoderForSistaV1>>genUnsignedSingleExtendA: (in category 'bytecode generation') -----
+ genUnsignedSingleExtendA: extendedIndex
+ (extendedIndex between: 0 and: 255) ifFalse:
+ [^self outOfRangeError: 'index' index: extendedIndex range: 0 to: 255].
+ "224 11100000 aaaaaaaa Extend A (Ext A = Ext A prev * 256 + Ext A)
+ ExtA is normally unsigned."
+ stream
+ nextPut: 224;
+ nextPut: extendedIndex!

Item was added:
+ ----- Method: EncoderForSistaV1>>genUnsignedSingleExtendB: (in category 'bytecode generation') -----
+ genUnsignedSingleExtendB: extendedIndex
+ (extendedIndex between: 0 and: 255) ifFalse:
+ [^self outOfRangeError: 'index' index: extendedIndex range: 0 to: 255].
+ "225 11100001 sbbbbbbb Extend B (Ext B = Ext B prev * 256 + Ext B).
+ ExtB is normally signed"
+ stream
+ nextPut: 225;
+ nextPut: extendedIndex!

Item was added:
+ ----- Method: EncoderForSistaV1>>isSpecialLiteralForPush: (in category 'special literal encodings') -----
+ isSpecialLiteralForPush: literal
+ ^literal == false
+  or: [literal == true
+  or: [literal == nil
+  or: [(literal isInteger and: [literal between: -32768 and: 32767])
+  or: [(literal isCharacter and: [literal asInteger between: 0 and: 65535])]]]]!

Item was added:
+ ----- Method: EncoderForSistaV1>>maxIndexableLiterals (in category 'accessing') -----
+ maxIndexableLiterals
+ "Answer the maximum number of literals supported by the receiver's
+ bytecode set."
+ ^65536!

Item was added:
+ ----- Method: EncoderForSistaV1>>supportsFullBlocks (in category 'testing') -----
+ supportsFullBlocks
+ "Answer if the instruction set supports full closures (closure creation from
+ specfic methods instead of bytecodes embedded in an outer home method)."
+
+ ^true!

Item was added:
+ ----- Method: EncoderForV3 class>>pushNilCode (in category 'bytecode decoding') -----
+ pushNilCode
+ "Answer the pushNil bytecode.
+ 112-119 01110iii Push (receiver, true, false, nil, -1, 0, 1, 2) [iii]"
+ ^115!

Item was added:
+ ----- Method: EncoderForV3>>supportsFullBlocks (in category 'testing') -----
+ supportsFullBlocks
+ "Answer if the instruction set supports full closures (closure creation from
+ specfic methods instead of bytecodes embedded in an outer home method)."
+
+ ^false!

Item was changed:
  ----- Method: EncoderForV3PlusClosures class>>createClosureCode (in category 'bytecode decoding') -----
  createClosureCode
+ "Answer the create closure bytecode, if it exists in the encoder's bytecode set, or nil if not.
+ Actually this code is that for a closure whose bytecodes are nested within its home method's."
- "Answer the create closure bytecode, if it exists in the encoder's byetcode set, or nil if not."
  ^143!

Item was removed:
- ----- Method: EncoderForV3PlusClosures>>genPushNClosureTemps: (in category 'bytecode generation') -----
- genPushNClosureTemps: numTemps
- numTemps timesRepeat: [self genPushSpecialLiteral: nil]!

Item was changed:
  ----- Method: FieldNode>>assignmentCheck:at: (in category 'testing') -----
  assignmentCheck: encoder at: location
  (encoder cantStoreInto: name) ifTrue: [^location].
  fieldDef toSet ifNil:[
  encoder interactive ifTrue:[^location].
+ fieldDef := fieldDef shallowCopy assignDefaultSetter.
- fieldDef := fieldDef clone assignDefaultSetter.
  ].
  ^-1!

Item was changed:
+ ----- Method: FutureNode>>analyseTempsWithin:rootNode:assignmentPools: (in category 'closure analysis') -----
- ----- Method: FutureNode>>analyseTempsWithin:rootNode:assignmentPools: (in category 'code generation (closures)') -----
  analyseTempsWithin: scopeBlock "<BlockNode>" rootNode: rootNode "<MethodNode>" assignmentPools: assignmentPools "<Dictionary>"
  { receiver. futureDelta }, (futureArgs ifNil: [#()]) do:
  [:node|
  node == nil ifFalse:
  [node analyseTempsWithin: scopeBlock rootNode: rootNode assignmentPools: assignmentPools]]!

Item was changed:
+ ----- Method: LeafNode>>analyseTempsWithin:rootNode:assignmentPools: (in category 'closure analysis') -----
- ----- Method: LeafNode>>analyseTempsWithin:rootNode:assignmentPools: (in category 'code generation (closures)') -----
  analyseTempsWithin: scopeBlock "<BlockNode>" rootNode: rootNode "<MethodNode>" assignmentPools: assignmentPools "<Dictionary>"
  "This is a no-op except in TempVariableNode"
  ^self!

Item was changed:
+ ----- Method: MessageNode>>analyseTempsWithin:rootNode:assignmentPools: (in category 'closure analysis') -----
- ----- Method: MessageNode>>analyseTempsWithin:rootNode:assignmentPools: (in category 'code generation (closures)') -----
  analyseTempsWithin: scopeBlock "<BlockNode>" rootNode: rootNode "<MethodNode>" assignmentPools: assignmentPools "<Dictionary>"
  "Assignments within optimized loops are tricky.  Because a loop repeats a
  write to a temporary in an optimized loop effectively occurs after the loop.
  To handle this collect the set of temps assigned to in optimized loops and
  add extra writes after traversing the optimized loop constituents."
  | writtenToTemps |
  self isOptimizedLoop ifTrue:
  [{ receiver }, arguments do:
  [:node|
  (node notNil and: [node isBlockNode and: [node optimized]]) ifTrue:
  [assignmentPools at: node put: Set new]]].
  "receiver is nil in cascades"
  receiver == nil ifFalse:
  [receiver analyseTempsWithin: scopeBlock rootNode: rootNode assignmentPools: assignmentPools].
  arguments do:
  [:node|
  node == nil ifFalse: "last argument of optimized to:do: can be nil"
  [node analyseTempsWithin: scopeBlock rootNode: rootNode assignmentPools: assignmentPools]].
  "Add assignments representing subsequent iterations
  and redo the closure analysis for the written-to temps."
  self isOptimizedLoop ifTrue:
  [writtenToTemps := Set new.
  { receiver }, arguments do:
  [:node|
  (node notNil and: [node isBlockNode and: [node optimized]]) ifTrue:
  [(assignmentPools removeKey: node) do:
  [:temp|
  temp isBlockArg ifFalse: "ignore added assignments to to:do: loop args"
  [writtenToTemps add: temp.
  temp addWriteWithin: node at: rootNode locationCounter]]]].
  writtenToTemps isEmpty ifFalse:
  [(writtenToTemps sorted: ParseNode tempSortBlock) do:
  [:each| each analyseClosure: rootNode].
  (writtenToTemps collect: [:each| each definingScope]) do:
  [:blockNode|
  blockNode ifHasRemoteTempNodeEnsureInitializationStatementExists: rootNode]]]!

Item was changed:
  ----- Method: MessageNode>>emitCodeForToDo:encoder:value: (in category 'code generation') -----
  emitCodeForToDo: stack encoder: encoder value: forValue
  " var := rcvr. L1: [var <= arg1] Bfp(L2) [block body. var := var + inc] Jmp(L1) L2: "
  | loopSize initStmt limitInit test block incStmt blockSize |
  initStmt := arguments at: 4.
  limitInit := arguments at: 7.
  test := arguments at: 5.
  block := arguments at: 3.
  incStmt := arguments at: 6.
  blockSize := sizes at: 1.
  loopSize := sizes at: 2.
- limitInit == nil
- ifFalse: [limitInit emitCodeForEffect: stack encoder: encoder].
 
  "This will return the receiver of to:do: which is the initial value of the loop"
  forValue
+ ifTrue: [initStmt emitCodeForValue: stack encoder: encoder]
- ifTrue: [initStmt emitCodeForValue: stack encoder: encoder.]
  ifFalse: [initStmt emitCodeForEffect: stack encoder: encoder].
+ limitInit ifNotNil:
+ [limitInit emitCodeForEffect: stack encoder: encoder].
  test emitCodeForValue: stack encoder: encoder.
  self emitCodeForBranchOn: false dist: blockSize pop: stack encoder: encoder.
  pc := encoder methodStreamPosition.
  block emitCodeForEvaluatedEffect: stack encoder: encoder.
  incStmt emitCodeForEffect: stack encoder: encoder.
+ self emitCodeForJump: 0 - loopSize encoder: encoder!
- self emitCodeForJump: 0 - loopSize encoder: encoder.!

Item was added:
+ ----- Method: MessageNode>>toDoFromWhileWithCounts:init:limit: (in category 'decompiling') -----
+ toDoFromWhileWithCounts: blockBodyTempCounts init: incrInit limit: limitInitOrNil
+ "If the receiver, a whileTrue: loop, represents a to:[by:]do: loop
+ then answer the replacement to:[by:]do:, otherwise answer nil."
+ | variable increment limit toDoBlock body test |
+ self assert: (selector key == #whileTrue:
+ and: [incrInit isAssignmentNode]).
+ (limitInitOrNil notNil "limit should not be referenced within the loop"
+  and: [(blockBodyTempCounts at: limitInitOrNil variable ifAbsent: [0]) ~= 1]) ifTrue:
+ [^nil].
+ body := arguments last statements.
+ (variable := incrInit variable) isTemp ifFalse:
+ [^nil].
+ (increment := body last toDoIncrement: variable) ifNil:
+ [^nil].
+ receiver statements size ~= 1 ifTrue:
+ [^nil].
+ test := receiver statements first.
+ "Note: test should really be checked that <= or >= comparison
+ jibes with the sign of the (constant) increment"
+ (test isMessageNode
+ and: [(limit := test toDoLimit: variable) notNil]) ifFalse:
+ [^nil].
+ "The block must not overwrite the limit"
+ (limit isVariableNode and: [body anySatisfy: [:e | e isAssignmentNode and: [e variable = limit]]]) ifTrue:
+ [^nil].
+ toDoBlock := BlockNode statements: body allButLast returns: false.
+ toDoBlock arguments: {variable}.
+ ^MessageNode new
+ receiver: incrInit value
+ selector: (SelectorNode new key: #to:by:do: code: #macro)
+ arguments: (Array with: limit with: increment with: toDoBlock)
+ precedence: precedence!

Item was removed:
- ----- Method: MessageNode>>toDoFromWhileWithInit: (in category 'macro transformations') -----
- toDoFromWhileWithInit: initStmt
- "Return nil, or a to:do: expression equivalent to this whileTrue:"
- | variable increment limit toDoBlock body test |
- (selector key == #whileTrue:
- and: [initStmt isAssignmentNode
- and: [initStmt variable isTemp]]) ifFalse:
- [^nil].
- body := arguments last statements.
- variable := initStmt variable.
- increment := body last toDoIncrement: variable.
- (increment == nil
- or: [receiver statements size ~= 1]) ifTrue:
- [^nil].
- test := receiver statements first.
- "Note: test chould really be checked that <= or >= comparison
- jibes with the sign of the (constant) increment"
- (test isMessageNode
- and: [(limit := test toDoLimit: variable) notNil]) ifFalse:
- [^nil].
- "The block must not overwrite the limit"
- (limit isVariableNode and: [body anySatisfy: [:e | e isAssignmentNode and: [e variable = limit]]])
- ifTrue: [^nil].
- toDoBlock := BlockNode statements: body allButLast returns: false.
- toDoBlock arguments: (Array with: variable).
- variable scope: -1.
- variable beBlockArg.
- ^MessageNode new
- receiver: initStmt value
- selector: (SelectorNode new key: #to:by:do: code: #macro)
- arguments: (Array with: limit with: increment with: toDoBlock)
- precedence: precedence!

Item was added:
+ ----- Method: MessageNode>>toDoFromWhileWithInit:withLimit: (in category 'decompiling') -----
+ toDoFromWhileWithInit: incrInit withLimit: limitInitOrNil
+ "If the receiver, a whileTrue: loop, represents a to:[by:]do: loop
+ then answer the replacement to:[by:]do:, otherwise answer nil."
+ | variable increment limit toDoBlock body test |
+ self assert: (selector key == #whileTrue:
+ and: [incrInit isAssignmentNode]).
+ body := arguments last statements.
+ (variable := incrInit variable) isTemp ifFalse:
+ [^nil].
+ (increment := body last toDoIncrement: variable) ifNil:
+ [^nil].
+ receiver statements size ~= 1 ifTrue:
+ [^nil].
+ test := receiver statements first.
+ "Note: test should really be checked that <= or >= comparison
+ jibes with the sign of the (constant) increment"
+ (test isMessageNode
+ and: [(limit := test toDoLimit: variable) notNil]) ifFalse:
+ [^nil].
+ "The block must not overwrite the limit"
+ (limit isVariableNode and: [body anySatisfy: [:e | e isAssignmentNode and: [e variable = limit]]]) ifTrue:
+ [^nil].
+ toDoBlock := BlockNode statements: body allButLast returns: false.
+ toDoBlock arguments: {variable}.
+ ^MessageNode new
+ receiver: incrInit value
+ selector: (SelectorNode new key: #to:by:do: code: #macro)
+ arguments: (Array with: limit with: increment with: toDoBlock)
+ precedence: precedence!

Item was changed:
  ----- Method: MessageNode>>toDoIncrement: (in category 'testing') -----
  toDoIncrement: variable
+ ^(receiver = variable
+   and: [selector key = #+
+   and: [arguments first isConstantNumber]]) ifTrue:
+ [arguments first]!
- (receiver = variable and: [selector key = #+])
- ifFalse: [^ nil].
- arguments first isConstantNumber
- ifTrue: [^ arguments first]
- ifFalse: [^ nil]!

Item was changed:
  ----- Method: MessageNode>>toDoLimit: (in category 'testing') -----
  toDoLimit: variable
+ ^(receiver = variable
+   and: [selector key = #<= or: [selector key = #>=]]) ifTrue:
+ [arguments first]!
- (receiver = variable and: [selector key = #<= or: [selector key = #>=]])
- ifTrue: [^ arguments first]
- ifFalse: [^ nil]!

Item was changed:
+ ----- Method: MethodNode>>addLocalsToPool: (in category 'closure analysis') -----
- ----- Method: MethodNode>>addLocalsToPool: (in category 'code generation (closures)') -----
  addLocalsToPool: locals "<Set of: TempVariableNode>"
  localsPool isNil ifTrue:
  [localsPool := IdentitySet new].
  localsPool addAll: locals!

Item was changed:
+ ----- Method: MethodNode>>ensureClosureAnalysisDone (in category 'closure analysis') -----
- ----- Method: MethodNode>>ensureClosureAnalysisDone (in category 'code generation (closures)') -----
  ensureClosureAnalysisDone
  block blockExtent ifNil:
  [temporaries := block analyseArguments: arguments temporaries: temporaries rootNode: self]!

Item was changed:
  ----- Method: MethodNode>>generate:using: (in category 'code generation') -----
  generate: trailer using: aCompiledMethodClass
  "The receiver is the root of a parse tree. Answer an instance of aCompiledMethodClass.
  The argument, trailer, is arbitrary but is typically either the reference to the source code
  that is stored with every CompiledMethod, or an encoding of the method's temporary names."
 
+ | method |
- | primErrNode blkSize nLits locals literals stack header method |
  self generate: trailer
  using: aCompiledMethodClass
  ifQuick:
  [:m |
+  m literalAt: 2 put: encoder associationForClass;
- encoder noteBlockExtent: (0 to: 2) hasLocals: arguments.
- m literalAt: 2 put: encoder associationForClass;
  properties: properties.
+ ^m].
+ method := encoder generateMethodOfClass: aCompiledMethodClass trailer: trailer from: self.
- ^m].
- primErrNode := self primitiveErrorVariableName ifNotNil:
- [encoder fixTemp: self primitiveErrorVariableName].
- self ensureClosureAnalysisDone.
- encoder rootNode: self. "this is for BlockNode>>sizeCodeForClosureValue:"
- blkSize := (block sizeCodeForEvaluatedValue: encoder)
- + (primitive > 0
- ifTrue: [encoder sizeCallPrimitive: primitive]
- ifFalse: [0])
- + (primErrNode
- ifNil: [0]
- ifNotNil:
- [primErrNode
- index: arguments size + temporaries size;
- sizeCodeForStore: encoder "The VM relies on storeIntoTemp: (129)"]).
- locals := arguments, temporaries, (primErrNode ifNil: [#()] ifNotNil: [{primErrNode}]).
- encoder noteBlockExtent: block blockExtent hasLocals: locals.
- header := encoder computeMethodHeaderForNumArgs: arguments size
- numTemps: locals size
- numLits: (nLits := (literals := encoder allLiterals) size)
- primitive: primitive.
- method := trailer
- createMethod: blkSize
- class: aCompiledMethodClass
- header: header.
- 1 to: nLits do: [:lit | method literalAt: lit put: (literals at: lit)].
- encoder streamToMethod: method.
- stack := ParseStack new init.
- primitive > 0 ifTrue:
- [encoder genCallPrimitive: primitive.
- primErrNode ifNotNil:
- [primErrNode emitCodeForStore: stack encoder: encoder]].
- stack position: method numTemps.
- [block emitCodeForEvaluatedValue: stack encoder: encoder]
- on: Error "If an attempt is made to write too much code the method will be asked"
- do: [:ex|  "to grow, and the grow attempt will fail in CompiledMethod class>>#new:"
- ex signalerContext sender method = (CompiledMethod class>>#new:)
- ifTrue: [^self error: 'Compiler code size discrepancy']
- ifFalse: [ex pass]].
- stack position ~= (method numTemps + 1) ifTrue:
- [^self error: 'Compiler stack discrepancy'].
- encoder methodStreamPosition ~= (method size - trailer size) ifTrue:
- [^self error: 'Compiler code size discrepancy'].
- method needsFrameSize: stack size - method numTemps.
  method properties: properties.
  ^method!

Item was changed:
+ ----- Method: MethodNode>>locationCounter (in category 'closure analysis') -----
- ----- Method: MethodNode>>locationCounter (in category 'code generation (closures)') -----
  locationCounter
  ^locationCounter!

Item was changed:
+ ----- Method: MethodNode>>noteBlockEntry: (in category 'closure analysis') -----
- ----- Method: MethodNode>>noteBlockEntry: (in category 'code generation (closures)') -----
  noteBlockEntry: aBlock
  "Evaluate aBlock with the numbering for the block entry."
  locationCounter isNil ifTrue:
  [locationCounter := -1].
  aBlock value: locationCounter + 1.
  locationCounter := locationCounter + 2!

Item was changed:
+ ----- Method: MethodNode>>noteBlockExit: (in category 'closure analysis') -----
- ----- Method: MethodNode>>noteBlockExit: (in category 'code generation (closures)') -----
  noteBlockExit: aBlock
  "Evaluate aBlock with the numbering for the block exit."
  aBlock value: locationCounter + 1.
  locationCounter := locationCounter + 2!

Item was changed:
+ ----- Method: MethodNode>>referencedValuesWithinBlockExtent: (in category 'closure analysis') -----
- ----- Method: MethodNode>>referencedValuesWithinBlockExtent: (in category 'code generation (closures)') -----
  referencedValuesWithinBlockExtent: anInterval
  ^(localsPool select:
  [:temp|
  temp isReferencedWithinBlockExtent: anInterval]) collect:
  [:temp|
  temp isRemote ifTrue: [temp remoteNode] ifFalse: [temp]]!

Item was changed:
  ----- Method: MethodNode>>schematicTempNamesString (in category 'debugger support') -----
  schematicTempNamesString
  "Answer the temp names for the current method node in a form that captures
  temp structure.  The temps at each method and block scope level occur
  space-separated, with any indirect temps enclosed in parentheses.  Each block
  level is enclosed in square brackets.  e.g.
  'method level temps (indirect temp)[block args and temps (indirect)]'
  This representation can be reconstituted into a blockExtentsToTempsMap
  by a CompiledMethod that has been copied with the schematicTempNamesString."
  encoder hasGeneratedMethod ifFalse:
+ ["create the encoder's blockExtentsToLocals map, except if the method is quick
- ["create the encoder's blockExtentsToLoals map, except if the method is quick
   in which case it has no temps."
+ self generate isQuick ifTrue:
- (self generate) isQuick ifTrue:
  [^'']].
  ^encoder schematicTempNamesString!

Item was changed:
+ ----- Method: NewArrayNode>>analyseTempsWithin:rootNode:assignmentPools: (in category 'closure analysis') -----
- ----- Method: NewArrayNode>>analyseTempsWithin:rootNode:assignmentPools: (in category 'code generation (closures)') -----
  analyseTempsWithin: scopeBlock "<BlockNode>" rootNode: rootNode "<MethodNode>" assignmentPools: assignmentPools "<Dictionary>"
  "This is a no-op except in TempVariableNode"
  ^self!

Item was changed:
+ ----- Method: RemoteTempVectorNode>>addRemoteTemp:encoder: (in category 'closure analysis') -----
- ----- Method: RemoteTempVectorNode>>addRemoteTemp:encoder: (in category 'code generation (closures)') -----
  addRemoteTemp: aTempVariableNode encoder: encoder
+ remoteTemps ifNil:
- remoteTemps isNil ifTrue:
  [remoteTemps := OrderedCollection new].
  remoteTemps addLast: aTempVariableNode.
  aTempVariableNode referenceScopesAndIndicesDo:
  [:scopeBlock "<BlockNode>" :location "<Integer>"|
+ self addReadWithin: scopeBlock at: location]!
- self addReadWithin: scopeBlock at: location].
- encoder supportsClosureOpcodes ifFalse:
- [encoder encodeLiteral: remoteTemps size.
- readNode := encoder encodeSelector: #at:.
- writeNode := encoder encodeSelector: #at:put:]!

Item was removed:
- ----- Method: RemoteTempVectorNode>>emitCodeForIndexOf:stack:encoder: (in category 'code generation (closures)') -----
- emitCodeForIndexOf: aTempVariableNode stack: stack encoder: encoder
- self assert: encoder supportsClosureOpcodes not.
- (encoder encodeLiteral: (remoteTemps indexOf: aTempVariableNode))
- emitCodeForValue: stack encoder: encoder!

Item was removed:
- ----- Method: RemoteTempVectorNode>>emitCodeForLoadFor:stack:encoder: (in category 'code generation (closures)') -----
- emitCodeForLoadFor: aTempVariableNode stack: stack encoder: encoder
- encoder supportsClosureOpcodes ifTrue:
- [^self].
- "Need to generate the first half of
- tempVector at: index put: expr
- i.e. the push of tempVector and index."
- super emitCodeForValue: stack encoder: encoder.
- self emitCodeForIndexOf: aTempVariableNode stack: stack encoder: encoder!

Item was changed:
+ ----- Method: RemoteTempVectorNode>>emitCodeForStoreInto:stack:encoder: (in category 'code generation') -----
- ----- Method: RemoteTempVectorNode>>emitCodeForStoreInto:stack:encoder: (in category 'code generation (closures)') -----
  emitCodeForStoreInto: aTempVariableNode stack: stack encoder: encoder
+ encoder
+ genStoreRemoteTemp: (remoteTemps indexOf: aTempVariableNode) - 1
+ inVectorAt: index!
- encoder supportsClosureOpcodes
- ifTrue:
- [encoder
- genStoreRemoteTemp: (remoteTemps indexOf: aTempVariableNode) - 1
- inVectorAt: index]
- ifFalse:
- [writeNode
- emitCode: stack
- args: 2
- encoder: encoder
- super: false]!

Item was changed:
+ ----- Method: RemoteTempVectorNode>>emitCodeForStorePopInto:stack:encoder: (in category 'code generation') -----
- ----- Method: RemoteTempVectorNode>>emitCodeForStorePopInto:stack:encoder: (in category 'code generation (closures)') -----
  emitCodeForStorePopInto: aTempVariableNode stack: stack encoder: encoder
+ encoder
+ genStorePopRemoteTemp: (remoteTemps indexOf: aTempVariableNode) - 1
+ inVectorAt: index.
- encoder supportsClosureOpcodes
- ifTrue:
- [encoder
- genStorePopRemoteTemp: (remoteTemps indexOf: aTempVariableNode) - 1
- inVectorAt: index]
- ifFalse:
- [self emitCodeForStoreInto: aTempVariableNode stack: stack encoder: encoder.
- encoder genPop].
  stack pop: 1!

Item was changed:
+ ----- Method: RemoteTempVectorNode>>emitCodeForValueOf:stack:encoder: (in category 'code generation') -----
- ----- Method: RemoteTempVectorNode>>emitCodeForValueOf:stack:encoder: (in category 'code generation (closures)') -----
  emitCodeForValueOf: aTempVariableNode stack: stack encoder: encoder
+ encoder
+ genPushRemoteTemp: (remoteTemps indexOf: aTempVariableNode) - 1
+ inVectorAt: index.
+ stack push: 1!
- encoder supportsClosureOpcodes
- ifTrue:
- [encoder
- genPushRemoteTemp: (remoteTemps indexOf: aTempVariableNode) - 1
- inVectorAt: index.
- stack push: 1]
- ifFalse:
- [self emitCodeForLoadFor: aTempVariableNode stack: stack encoder: encoder.
- readNode
- emitCode: stack
- args: 1
- encoder: encoder
- super: false]!

Item was changed:
+ ----- Method: RemoteTempVectorNode>>isIndirectTempVector (in category 'closure analysis') -----
- ----- Method: RemoteTempVectorNode>>isIndirectTempVector (in category 'code generation (closures)') -----
  isIndirectTempVector
  ^true!

Item was changed:
+ ----- Method: RemoteTempVectorNode>>nodeToInitialize: (in category 'code generation') -----
- ----- Method: RemoteTempVectorNode>>nodeToInitialize: (in category 'code generation (closures)') -----
  nodeToInitialize: encoder
  ^AssignmentNode new
  variable: self
+ value: (NewArrayNode new numElements: remoteTemps size)!
- value: (encoder supportsClosureOpcodes
- ifTrue: [NewArrayNode new numElements: remoteTemps size]
- ifFalse:
- [MessageNode new
- receiver: (encoder encodeVariable: 'Array')
- selector: #new:
- arguments: (Array with: (encoder encodeLiteral: remoteTemps size))
- precedence: 3
- from: encoder])!

Item was changed:
+ ----- Method: RemoteTempVectorNode>>referenceScopesAndIndicesDo: (in category 'closure analysis') -----
- ----- Method: RemoteTempVectorNode>>referenceScopesAndIndicesDo: (in category 'code generation (closures)') -----
  referenceScopesAndIndicesDo: aBinaryBlock
  self shouldNotImplement!

Item was changed:
+ ----- Method: RemoteTempVectorNode>>scope (in category 'code generation') -----
- ----- Method: RemoteTempVectorNode>>scope (in category 'code generation (closures)') -----
  scope
  "Answer scope of temporary variables.
  Currently only the following distinctions are made:
  0 outer level: args and user-declared temps
  1 block args and doLimiT temps
  -1 a block temp that is no longer active
  -2 a block temp that held limit of to:do:
  -3 an indirect temp vector"
  ^-3!

Item was removed:
- ----- Method: RemoteTempVectorNode>>sizeCodeForIndexOf:encoder: (in category 'code generation (closures)') -----
- sizeCodeForIndexOf: aTempVariableNode encoder: encoder
- self assert: encoder supportsClosureOpcodes not.
- ^(encoder encodeLiteral: (remoteTemps indexOf: aTempVariableNode)) sizeCodeForValue: encoder!

Item was removed:
- ----- Method: RemoteTempVectorNode>>sizeCodeForLoadFor:encoder: (in category 'code generation (closures)') -----
- sizeCodeForLoadFor: aTempVariableNode encoder: encoder
- encoder supportsClosureOpcodes ifTrue:
- [^0].
- "Need to size the first half of
- tempVector at: index put: expr
- i.e. the push of tempVector and index."
- ^(super sizeCodeForValue: encoder)
- + (self sizeCodeForIndexOf: aTempVariableNode encoder: encoder)!

Item was changed:
+ ----- Method: RemoteTempVectorNode>>sizeCodeForStoreInto:encoder: (in category 'code generation') -----
- ----- Method: RemoteTempVectorNode>>sizeCodeForStoreInto:encoder: (in category 'code generation (closures)') -----
  sizeCodeForStoreInto: aTempVariableNode encoder: encoder
+ ^encoder
+ sizeStoreRemoteTemp: (remoteTemps indexOf: aTempVariableNode) - 1
+ inVectorAt: index!
- encoder supportsClosureOpcodes ifTrue:
- [^encoder sizeStoreRemoteTemp: (remoteTemps indexOf: aTempVariableNode) - 1 inVectorAt: index].
- ^writeNode sizeCode: encoder args: 2 super: false!

Item was changed:
+ ----- Method: RemoteTempVectorNode>>sizeCodeForStorePopInto:encoder: (in category 'code generation') -----
- ----- Method: RemoteTempVectorNode>>sizeCodeForStorePopInto:encoder: (in category 'code generation (closures)') -----
  sizeCodeForStorePopInto: aTempVariableNode encoder: encoder
+ ^encoder
+ sizeStorePopRemoteTemp: (remoteTemps indexOf: aTempVariableNode) - 1
+ inVectorAt: index!
- encoder supportsClosureOpcodes ifTrue:
- [^encoder sizeStorePopRemoteTemp: (remoteTemps indexOf: aTempVariableNode) - 1 inVectorAt: index].
- ^(self sizeCodeForStoreInto: aTempVariableNode encoder: encoder)
- + encoder sizePop!

Item was changed:
+ ----- Method: RemoteTempVectorNode>>sizeCodeForValueOf:encoder: (in category 'code generation') -----
- ----- Method: RemoteTempVectorNode>>sizeCodeForValueOf:encoder: (in category 'code generation (closures)') -----
  sizeCodeForValueOf: aTempVariableNode encoder: encoder
+ ^encoder
+ sizePushRemoteTemp: (remoteTemps indexOf: aTempVariableNode) - 1
+ inVectorAt: index!
- encoder supportsClosureOpcodes ifTrue:
- [^encoder sizePushRemoteTemp: (remoteTemps indexOf: aTempVariableNode) - 1 inVectorAt: index].
- ^(self sizeCodeForValue: encoder)
- + (self sizeCodeForIndexOf: aTempVariableNode encoder: encoder)
- + (readNode sizeCode: encoder args: 1 super: false)!

Item was changed:
+ ----- Method: ReturnNode>>analyseTempsWithin:rootNode:assignmentPools: (in category 'closure analysis') -----
- ----- Method: ReturnNode>>analyseTempsWithin:rootNode:assignmentPools: (in category 'code generation (closures)') -----
  analyseTempsWithin: scopeBlock "<BlockNode>" rootNode: rootNode "<MethodNode>" assignmentPools: assignmentPools "<Dictionary>"
  "Note we could do this:
  scopeBlock ~~ rootNode block ifTrue:
  [scopeBlock noteNonLocalReturn].
  and pass up the flag in <BlockNode>>>analyseTempsWithin:rootNode:
  which may be fast but will also give less information the debugger.
  For now we consider clean blocks a premature optimization."
  self flag: 'consider clean blocks'.
  expr analyseTempsWithin: scopeBlock rootNode: rootNode assignmentPools: assignmentPools!

Item was changed:
+ ----- Method: SpecialLiteralNode>>emitCodeForValue:encoder: (in category 'code generation') -----
- ----- Method: SpecialLiteralNode>>emitCodeForValue:encoder: (in category 'code generation (closures)') -----
  emitCodeForValue: stack encoder: encoder
  stack push: 1.
  encoder genPushSpecialLiteral: key!

Item was changed:
+ ----- Method: SpecialLiteralNode>>sizeCodeForValue: (in category 'code generation') -----
- ----- Method: SpecialLiteralNode>>sizeCodeForValue: (in category 'code generation (closures)') -----
  sizeCodeForValue: encoder
  ^encoder sizePushSpecialLiteral: key!

Item was changed:
+ ----- Method: TempVariableNode>>absorbHoistedTemp: (in category 'closure analysis') -----
- ----- Method: TempVariableNode>>absorbHoistedTemp: (in category 'code generation (closures)') -----
  absorbHoistedTemp: aTempVar
  "Collapse aTempVar into the receiver, being sure to update any closure analysis."
  aTempVar copyScopeAccessTo: self.
  aTempVar becomeForward: self!

Item was changed:
+ ----- Method: TempVariableNode>>addReadWithin:at: (in category 'closure analysis') -----
- ----- Method: TempVariableNode>>addReadWithin:at: (in category 'code generation (closures)') -----
  addReadWithin: scopeBlock "<BlockNode>" at: location "<Integer>"
  readingScopes ifNil: [readingScopes := Dictionary new].
  (readingScopes at: scopeBlock ifAbsentPut: [Set new]) add: location.
  remoteNode ifNotNil:
  [remoteNode addReadWithin: scopeBlock at: location]!

Item was changed:
+ ----- Method: TempVariableNode>>addWriteWithin:at: (in category 'closure analysis') -----
- ----- Method: TempVariableNode>>addWriteWithin:at: (in category 'code generation (closures)') -----
  addWriteWithin: scopeBlock "<BlockNode>" at: location "<Integer>"
  writingScopes ifNil: [writingScopes := Dictionary new].
  (writingScopes at: scopeBlock ifAbsentPut: [Set new]) add: location.
  remoteNode ifNotNil:
  [remoteNode addReadWithin: scopeBlock at: location]!

Item was changed:
+ ----- Method: TempVariableNode>>analyseClosure: (in category 'closure analysis') -----
- ----- Method: TempVariableNode>>analyseClosure: (in category 'code generation (closures)') -----
  analyseClosure: rootNode "<MethodNode>"
  "Analyse whether the temporary needs to be made remote
  or not, and answer whether it was made remote.
  A temp cannot be local if it is written to remotely,
  or if it is written to after it is closed-over.  An exception
  is an inlined block argument that appears to be written
  remotely but is actually local to a block."
  | latestWrite |
  self isBlockArg ifTrue: [^false].
  remoteNode ifNotNil: [^false]. "If already remote, don't remote a second time"
  latestWrite := 0.
  ((writingScopes notNil
  and: [writingScopes associations anySatisfy: [:assoc|
  [:blockScope :refs|
  refs do: [:write| latestWrite := write max: latestWrite].
  "A temp cannot be local if it is written to remotely."
  blockScope actualScope ~~ definingScope actualScope]
  value: assoc key value: assoc value]])
  or: [readingScopes notNil
  and: [readingScopes associations anySatisfy: [:assoc|
  [:blockScope :refs|
  "A temp cannot be local if it is written to after it is closed-over."
  blockScope actualScope ~~ definingScope actualScope
  and: [refs anySatisfy: [:read| read < latestWrite]]]
  value: assoc key value: assoc value]]]) ifTrue:
  [remoteNode := definingScope addRemoteTemp: self rootNode: rootNode.
  ^true].
  ^false!

Item was changed:
+ ----- Method: TempVariableNode>>analyseTempsWithin:rootNode:assignmentPools: (in category 'closure analysis') -----
- ----- Method: TempVariableNode>>analyseTempsWithin:rootNode:assignmentPools: (in category 'code generation (closures)') -----
  analyseTempsWithin: scopeBlock "<BlockNode>" rootNode: rootNode "<MethodNode>" assignmentPools: assignmentPools "<Dictionary>"
  self addReadWithin: scopeBlock at: rootNode locationCounter!

Item was changed:
+ ----- Method: TempVariableNode>>beingAssignedToAnalyseTempsWithin:rootNode:assignmentPools: (in category 'closure analysis') -----
- ----- Method: TempVariableNode>>beingAssignedToAnalyseTempsWithin:rootNode:assignmentPools: (in category 'code generation (closures)') -----
  beingAssignedToAnalyseTempsWithin: scopeBlock "<BlockNode>" rootNode: rootNode "<MethodNode>" assignmentPools: assignmentPools "<Dictionary>"
  self addWriteWithin: scopeBlock at: rootNode locationCounter.
  "For analysis of optimized blocks also record the set of temporaries written to
  within optimized blocks so that additional writes can be added at locations that
  represent subsequent iterations of the loop. e.g. testInlineBlockCollectionSD1"
  assignmentPools keysAndValuesDo:
  [:outerScopeBlock :set|
  "definingScope can be nil in expr in expr ifNil: [:arg|...] expressions because
  arg gets its definingScope set when [:arg|...] is analysed."
  outerScopeBlock actualScope
  = (definingScope
  ifNil: [scopeBlock]
  ifNotNil: [definingScope actualScope]) ifTrue:
  [set add: self]]!

Item was changed:
+ ----- Method: TempVariableNode>>copyScopeAccessTo: (in category 'closure analysis') -----
- ----- Method: TempVariableNode>>copyScopeAccessTo: (in category 'code generation (closures)') -----
  copyScopeAccessTo: aTempVar
  "For absorbHoistedTemp:, copy the receiver's reads and writes into the record in aTempVar."
  readingScopes ifNotNil:
  [readingScopes keysAndValuesDo:
  [:scopeBlock :reads|
  reads do:
  [:location|
  aTempVar addReadWithin: scopeBlock "<BlockNode>" at: location]]].
  writingScopes ifNotNil:
  [writingScopes keysAndValuesDo:
  [:scopeBlock :writes|
  writes do:
  [:location|
  aTempVar addWriteWithin: scopeBlock "<BlockNode>" at: location]]]!

Item was changed:
+ ----- Method: TempVariableNode>>definingScope (in category 'closure analysis') -----
- ----- Method: TempVariableNode>>definingScope (in category 'code generation (closures)') -----
  definingScope
  ^definingScope!

Item was changed:
+ ----- Method: TempVariableNode>>definingScope: (in category 'closure analysis') -----
- ----- Method: TempVariableNode>>definingScope: (in category 'code generation (closures)') -----
  definingScope: scopeBlock "<BlockNode>"
  definingScope = scopeBlock ifTrue: [^ self]. "No need to bail"
  definingScope ifNotNil:
  [self error: 'temp has more than one defining scope.  This is probably a parser error'].
  definingScope := scopeBlock!

Item was removed:
- ----- Method: TempVariableNode>>emitCodeForLoad:forValue:encoder: (in category 'code generation') -----
- emitCodeForLoad: stack forValue: forValue encoder: encoder
- remoteNode ~~ nil ifTrue:
- [remoteNode emitCodeForLoadFor: self stack: stack encoder: encoder]!

Item was changed:
+ ----- Method: TempVariableNode>>index: (in category 'closure analysis') -----
- ----- Method: TempVariableNode>>index: (in category 'code generation (closures)') -----
  index: anInteger
  "For renumbering temps in the closure compiler."
  index := anInteger.
  code := self code: index type: LdTempType!

Item was changed:
+ ----- Method: TempVariableNode>>isDefinedWithinBlockExtent: (in category 'closure analysis') -----
- ----- Method: TempVariableNode>>isDefinedWithinBlockExtent: (in category 'code generation (closures)') -----
  isDefinedWithinBlockExtent: anInterval
  ^anInterval rangeIncludes: definingScope actualScope blockExtent first!

Item was changed:
+ ----- Method: TempVariableNode>>isIndirectTempVector (in category 'closure analysis') -----
- ----- Method: TempVariableNode>>isIndirectTempVector (in category 'code generation (closures)') -----
  isIndirectTempVector
  ^false!

Item was changed:
+ ----- Method: TempVariableNode>>isReferencedWithinBlockExtent: (in category 'closure analysis') -----
- ----- Method: TempVariableNode>>isReferencedWithinBlockExtent: (in category 'code generation (closures)') -----
  isReferencedWithinBlockExtent: anInterval
  readingScopes ~~ nil ifTrue:
  [readingScopes do:
  [:set "<Set of <Integer>>"|
  set do:
  [:location|
  (anInterval rangeIncludes: location) ifTrue:
  [^true]]]].
  writingScopes ~~ nil ifTrue:
  [writingScopes do:
  [:set "<Set of <Integer>>"|
  set do:
  [:location|
  (anInterval rangeIncludes: location) ifTrue:
  [^true]]]].
  ^false!

Item was changed:
+ ----- Method: TempVariableNode>>referenceScopesAndIndicesDo: (in category 'closure analysis') -----
- ----- Method: TempVariableNode>>referenceScopesAndIndicesDo: (in category 'code generation (closures)') -----
  referenceScopesAndIndicesDo: aBinaryBlock
  "Evaluate aBinaryBlock with all read or write scopes and locations.
  This is used to copy the reference information into RemoteTempVectorNodes"
  readingScopes ~~ nil ifTrue:
  [readingScopes keysAndValuesDo:
  [:scopeBlock "<BlockNode>" :set "<Set of <Integer>>"|
  set do: [:location| aBinaryBlock value: scopeBlock value: location]]].
  writingScopes ~~ nil ifTrue:
  [writingScopes keysAndValuesDo:
  [:scopeBlock "<BlockNode>" :set "<Set of <Integer>>"|
  set do: [:location| aBinaryBlock value: scopeBlock value: location]]]!

Item was removed:
- ----- Method: TempVariableNode>>sizeCodeForLoad:forValue: (in category 'code generation') -----
- sizeCodeForLoad: encoder forValue: forValue
- ^remoteNode
- ifNil: [0]
- ifNotNil: [remoteNode sizeCodeForLoadFor: self encoder: encoder]!

Item was changed:
+ ----- Method: VariableNode>>beingAssignedToAnalyseTempsWithin:rootNode:assignmentPools: (in category 'closure analysis') -----
- ----- Method: VariableNode>>beingAssignedToAnalyseTempsWithin:rootNode:assignmentPools: (in category 'code generation (closures)') -----
  beingAssignedToAnalyseTempsWithin: scopeBlock "<BlockNode>" rootNode: rootNode "<MethodNode>" assignmentPools: assignmentPools "<Dictionary>"
  "No-op overridden by TempVariableNode"!

Item was removed:
- ----- Method: VariableNode>>emitCodeForLoad:forValue:encoder: (in category 'code generation') -----
- emitCodeForLoad: stack forValue: forValue encoder: encoder
- "Do nothing"!

Item was changed:
+ (PackageInfo named: 'Compiler') postscript: '"below, add code to be run after the loading of this package"
+ "Make sure all methods using to:do: and to:by:do: are recompiled"
- (PackageInfo named: 'Compiler') postscript: '"Make sure all affected methods are recompiled"
  UIManager default
+ informUser: ''Recompiling methods sending to:do: and to:by:do:''
- informUser: ''Recompiling affected methods''
  during:
  [(self systemNavigation allMethodsSelect:
+ [:m|
+ #(to:do: to:by:do:) anySatisfy: [:l| m refersToLiteral: l]]) do:
+ [:mr| mr actualClass recompile: mr selector]]'!
- [:m| | ebc | "All affected methods send one of these optimized selectors..."
- (#(to:do: to:by:do: ifNotNil: ifNil:ifNotNil: ifNotNil:ifNil:) anySatisfy: [:l| m refersToLiteral: l])
- "but the textDomain properties confuse method comparison below..."
- and: [(m propertyValueAt: #textDomain ifAbsent: nil) isNil
- and: [m numTemps > m numArgs "and have non-argument temporaries in them..."
-  or: [(ebc := m embeddedBlockClosures) notEmpty
- and: [ebc anySatisfy: [:bc| bc numTemps > bc numArgs]]]]]]) do:
- [:mr| | old new |
- old := mr compiledMethod.
- "do a test recompile of the method..."
- new := (mr actualClass compile: old getSource asString notifying: nil trailer: old trailer ifFail: nil) method.
- "and if it changed, report it to the transcript and really recompile it..."
- old ~= new ifTrue:
- [Transcript cr. old printReferenceOn: Transcript. Transcript flush.
- mr actualClass recompile: old selector]]]'!