The Trunk: Compiler-eem.453.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-eem.453.mcz

commits-2
Eliot Miranda uploaded a new version of Compiler to project The Trunk:
http://source.squeak.org/trunk/Compiler-eem.453.mcz

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

Name: Compiler-eem.453
Author: eem
Time: 26 December 2020, 7:30:51.52735 pm
UUID: 1a90195c-0773-4f16-bc29-08b718ad4d66
Ancestors: Compiler-eem.452

Fix a spelling error, preceed => precede, etc

=============== Diff against Compiler-eem.452 ===============

Item was changed:
  ----- Method: BytecodeEncoder class>>extensionsFor:in:into: (in category 'instruction stream support') -----
  extensionsFor: pc in: aCompiledMethod into: trinaryBlock
+ "If the bytecode at pc is an extension, or if the bytecode at pc is preceded by extensions,
- "If the bytecode at pc is an extension, or if the bytecode at pc is preceeded by extensions,
  then evaluate aTrinaryBlock with the values of extA and extB and number of extension *bytes*.
  If the bytecode at pc is neither an extension or extended then evaluate with 0, 0, 0."
   
  | prevPC |
  "If there is what appears to be an extension bytecode before this bytecode
  then scan for the previous pc to confirm."
  (pc - 2 >= aCompiledMethod initialPC
  and: [self isExtension: (aCompiledMethod at: pc - 2)]) ifTrue:
  [prevPC := aCompiledMethod pcPreviousTo: pc.
  (self nonExtensionPcAt: prevPC in: aCompiledMethod) = pc ifTrue:
  [^self extensionsAt: prevPC in: aCompiledMethod into: trinaryBlock]].
  ^self extensionsAt: pc in: aCompiledMethod into: trinaryBlock!

Item was changed:
  ----- Method: BytecodeEncoder class>>nonExtensionBytecodeAt:in: (in category 'instruction stream support') -----
  nonExtensionBytecodeAt: pc in: method
+ "Answer the actual bytecode at pc in method, skipping past any preceding extensions."
- "Answer the actual bytecode at pc in method, skipping past any preceeding extensions."
 
  self subclassResponsibility!

Item was changed:
  ----- Method: BytecodeEncoder class>>nonExtensionPcAt:in: (in category 'instruction stream support') -----
  nonExtensionPcAt: pc in: method
+ "Answer the pc of the actual bytecode at pc in method, skipping past any preceding extensions."
- "Answer the pc of 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)].
  ^thePC!

Item was changed:
  ----- Method: EncoderForSistaV1 class>>blockMethodOrNilFor:in:at: (in category 'instruction stream support') -----
  blockMethodOrNilFor: anInstructionStream in: method at: pc
  "If anInstructionStream is at a block creation bytecode then answer the block's
  CompiledBlock, otherwise answer nil.
 
  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) preceding it.
- raw send bytecode after its extension(s), or at the extension(s) preceeding it.
  249 11111001 xxxxxxxx siyyyyyy push Closure Compiled block literal index xxxxxxxx (+ Extend A * 256) numCopied yyyyyy receiverOnStack: s = 1 ignoreOuterContext: i = 1"
 
  | byte |
  byte := method at: pc.
  byte = 249 ifTrue:
  ["it could be extended..."
  ^self extensionsFor: pc in: method into:
  [:extA :extB :nExtBytes|
  method literalAt: (method at: pc + nExtBytes + 1) + (extA bitShift: 8) + 1]].
  ^byte = 16rE0 ifTrue:
  [self extensionsAt: pc in: method into:
  [:extA :extB :nExtBytes|
  (method at: pc + nExtBytes) = 249 ifTrue:
  [method literalAt: (method at: pc + nExtBytes + 1) + (extA bitShift: 8) + 1]]]!

Item was changed:
  ----- 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 preceding extensions."
- "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 changed:
  ----- 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) preceding it.
- 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 bitAnd: 63) * 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 precede extA"
- 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 changed:
  ----- Method: EncoderForV3 class>>extensionsFor:in:into: (in category 'instruction stream support') -----
  extensionsFor: pc in: aCompiledMethod into: trinaryBlock
+ "If the bytecode at pc is an extension, or if the bytecode at pc is preceded by extensions,
- "If the bytecode at pc is an extension, or if the bytecode at pc is preceeded by extensions,
  then evaluate aTrinaryBlock with the values of extA and extB and number of extension *bytes*.
  If the bytecode at pc is neither an extension or extended then evaluate with 0, 0, 0.
  There are no extensions in the SqueakV3/Smalltalk-80 bytecode set, so..."
  ^trinaryBlock value: 0 value: 0 value: 0!

Item was changed:
  ----- Method: EncoderForV3 class>>nonExtensionBytecodeAt:in: (in category 'instruction stream support') -----
  nonExtensionBytecodeAt: pc in: method
+ "Answer the actual bytecode at pc in method, skipping past any preceding extensions."
- "Answer the actual bytecode at pc in method, skipping past any preceeding extensions."
  ^method at: pc!

Item was changed:
  ----- Method: MethodNode>>preenableNodes (in category 'converting-private') -----
  preenableNodes
  "Answer a Dictionary from node or sequence of nodes to preen method selector for nodes
  in the tree that require post-processing after either a format or a decompile.  Such issues
  are the variable for an ifNotNil: which is local to the ifNotNil: block but, due to the inlining
  of ifNotNil: appears to be declared at the outer level, and, similarly, a temporary variable
  that conflicts with one of the same name in a block when, were the variable declared
  local to some inlined block it would no longer conflict.  The resulting dictionary is used to
  perform the value with the key (node or array) as argument to preen the tree."
 
  | preenableNodes priorBlocks priorVariables |
  preenableNodes := Dictionary new.
  priorBlocks := OrderedCollection new.
  priorVariables := Set new.
  self nodesWithPrecedingStatementsDo:
+ [:node :precedingStatementOrNil| | variable temps |
- [:node :preceedingStatementOrNil| | variable temps |
  (node isMessageNode
  and: [node macroPrinter == #printIfNilNotNil:indent:
  and: [node receiver isMessageNode
  and: [node receiver selector key == #==
  and: [node receiver receiver isAssignmentNode
  and: [(variable := node receiver receiver variable) isTemp
  and: [variable isRemote not
  and: [variable isOnlySubnodeOf: node in: self]]]]]]]) ifTrue:
  [preenableNodes at: node put: #preenIfNotNilNode:.
  priorVariables add: variable].
  node isBlockNode ifTrue:
  [temps := OrderedCollection new.
  node temporaries do:
  [:temp|
  priorBlocks do:
  [:aBlock|
  aBlock temporaries do:
  [:priorTemp|
  (priorVariables includes: priorTemp) ifFalse:
  [priorTemp key = temp key ifTrue:
  [temps addLast: priorTemp]]]]].
  temps isEmpty ifFalse:
  [preenableNodes at: temps put: #preenTempsConflictingWithBlockNode:].
  priorBlocks addLast: node].
  (node == NodeNil
+ and: [precedingStatementOrNil notNil
+ and: [precedingStatementOrNil isMessageNode
+ and: [precedingStatementOrNil isNilIf]]]) ifTrue:
+ [preenableNodes at: precedingStatementOrNil put: #preenNilNodeFollowingNilIfNode:]].
- and: [preceedingStatementOrNil notNil
- and: [preceedingStatementOrNil isMessageNode
- and: [preceedingStatementOrNil isNilIf]]]) ifTrue:
- [preenableNodes at: preceedingStatementOrNil put: #preenNilNodeFollowingNilIfNode:]].
  ^preenableNodes!