The Trunk: Compiler-eem.258.mcz

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

The Trunk: Compiler-eem.258.mcz

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

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

Name: Compiler-eem.258
Author: eem
Time: 3 April 2013, 12:59:36.409 pm
UUID: 7721a43f-63e6-4524-bb6d-48eddc955654
Ancestors: Compiler-eem.257

Fix store of special bindings.  Exsting code dropped the
value assigned from the stack, so v := binding := expr would
leave v holding binding, not expr.  New code generates
        push expr
        push binding
        duplicate expr (by pushTemp: of expr's stack index)
        send value:
        pop

=============== Diff against Compiler-eem.257 ===============

Item was changed:
  ----- Method: AssignmentNode>>emitCodeForEffect:encoder: (in category 'code generation') -----
  emitCodeForEffect: stack encoder: encoder
 
+ variable emitCodeForLoad: stack forValue: false encoder: encoder.
- variable emitCodeForLoad: stack encoder: encoder.
  value emitCodeForValue: stack encoder: encoder.
  pc := encoder methodStreamPosition + 1. "debug pc is first byte of the store, i.e. the next byte".
  variable emitCodeForStorePop: stack encoder: encoder!

Item was changed:
  ----- Method: AssignmentNode>>emitCodeForValue:encoder: (in category 'code generation') -----
  emitCodeForValue: stack encoder: encoder
 
+ variable emitCodeForLoad: stack forValue: true encoder: encoder.
- variable emitCodeForLoad: stack encoder: encoder.
  value emitCodeForValue: stack encoder: encoder.
  pc := encoder methodStreamPosition + 1. "debug pc is first byte of the store, i.e. the next byte".
  variable emitCodeForStore: stack encoder: encoder!

Item was changed:
  ----- Method: AssignmentNode>>sizeCodeForEffect: (in category 'code generation') -----
  sizeCodeForEffect: encoder
 
+ ^(variable sizeCodeForLoad: encoder forValue: false)
- ^(variable sizeCodeForLoad: encoder)
  + (value sizeCodeForValue: encoder)
  + (variable sizeCodeForStorePop: encoder)!

Item was changed:
  ----- Method: AssignmentNode>>sizeCodeForValue: (in category 'code generation') -----
  sizeCodeForValue: encoder
 
+ ^(variable sizeCodeForLoad: encoder forValue: true)
- ^(variable sizeCodeForLoad: encoder)
  + (value sizeCodeForValue: encoder)
  + (variable sizeCodeForStore: encoder)!

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

Item was added:
+ ----- Method: EncoderForV3>>genPushTempLong: (in category 'bytecode generation') -----
+ genPushTempLong: tempIndex
+ "See BlueBook page 596"
+ (tempIndex >= 0 and: [tempIndex < 64]) ifTrue:
+ ["128 10000000 jjkkkkkk Push (Receiver Variable, Temporary Location, Literal Constant, Literal Variable) [jj] #kkkkkk"
+ stream
+ nextPut: 128;
+ nextPut: 64 + tempIndex.
+ ^self].
+ ^self outOfRangeError: 'index' index: tempIndex range: 0 to: 63!

Item was removed:
- ----- Method: FieldNode>>emitCodeForLoad:encoder: (in category 'code generation') -----
- emitCodeForLoad: stack encoder: encoder
- rcvrNode emitCodeForValue: stack encoder: encoder.
- fieldDef accessKey ifNotNil:[
- super emitCodeForValue: stack encoder: encoder.
- ].!

Item was added:
+ ----- Method: FieldNode>>emitCodeForLoad:forValue:encoder: (in category 'code generation') -----
+ emitCodeForLoad: stack forValue: forValue encoder: encoder
+ rcvrNode emitCodeForValue: stack encoder: encoder.
+ fieldDef accessKey ifNotNil:
+ [super emitCodeForValue: stack encoder: encoder]!

Item was removed:
- ----- Method: LeafNode>>emitCodeForLoad:encoder: (in category 'code generation') -----
- emitCodeForLoad: stack encoder: encoder
- "Default is to do nothing.
- Subclasses may need to override."!

Item was added:
+ ----- Method: LeafNode>>emitCodeForLoad:forValue:encoder: (in category 'code generation') -----
+ emitCodeForLoad: stack forValue: forValue encoder: encoder
+ "Default is to do nothing.
+ Subclasses may need to override."!

Item was removed:
- ----- Method: LeafNode>>sizeCodeForLoad: (in category 'code generation') -----
- sizeCodeForLoad: encoder
- "Default is to do nothing.
- Subclasses may need to override."
- ^0!

Item was added:
+ ----- Method: LeafNode>>sizeCodeForLoad:forValue: (in category 'code generation') -----
+ sizeCodeForLoad: encoder forValue: forValue
+ "Default is to do nothing.
+ Subclasses may need to override."
+ ^0!

Item was removed:
- ----- Method: LiteralVariableNode>>emitCodeForLoad:encoder: (in category 'code generation') -----
- emitCodeForLoad: stack encoder: encoder
- writeNode ifNotNil:
- [encoder genPushLiteral: index.
- stack push: 1]!

Item was added:
+ ----- Method: LiteralVariableNode>>emitCodeForLoad:forValue:encoder: (in category 'code generation') -----
+ emitCodeForLoad: stack forValue: forValue encoder: encoder
+ "If a normal literal variable (not sending value:), do nothing.
+ If for value (e.g. v := Binding := expr) do nothing; the work will be done in emitCodeForStore:encoder:.
+ If not for value then indeed load.  The rest of the work will be done in  emitCodeForStorePop:encoder:."
+ (writeNode isNil or: [forValue]) ifTrue: [^self].
+ encoder genPushLiteral: index.
+ stack push: 1!

Item was changed:
  ----- Method: LiteralVariableNode>>emitCodeForStore:encoder: (in category 'code generation') -----
  emitCodeForStore: stack encoder: encoder
+ | exprOffset |
  writeNode ifNil: [^encoder genStoreLiteralVar: index].
+ "On entry the stack has only the expression.  Push the binding,
+ duplicate the expression, send #value: and pop."
+ exprOffset := stack position - 1.
+ encoder genPushLiteral: index.
+ stack push: 1.
+ encoder genPushTempLong: exprOffset.
+ stack push: 1.
- "THIS IS WRONG!!!! THE VALUE IS LOST FROM THE STACK!!!!
- The various value: methods on Association ReadOnlyVariableBinding
- etc _do not_ return the value assigned; they return the receiver."
- "Should generate something more like
- push expr
- push lit
- push temp (index of expr)
- send value:
- pop
- or use e.g. valueForStore:"
- self flag: #bogus.
  writeNode
  emitCode: stack
  args: 1
  encoder: encoder
+ super: false.
+ stack pop: 1.
+ encoder genPop!
- super: false!

Item was removed:
- ----- Method: LiteralVariableNode>>sizeCodeForLoad: (in category 'code generation') -----
- sizeCodeForLoad: encoder
- self reserve: encoder.
- ^(key isVariableBinding and: [key isSpecialWriteBinding])
- ifTrue: [encoder sizePushLiteral: index]
- ifFalse: [0]!

Item was added:
+ ----- Method: LiteralVariableNode>>sizeCodeForLoad:forValue: (in category 'code generation') -----
+ sizeCodeForLoad: encoder forValue: forValue
+ self reserve: encoder.
+ ^(key isVariableBinding and: [key isSpecialWriteBinding and: [forValue not]])
+ ifTrue: [encoder sizePushLiteral: index]
+ ifFalse: [0]!

Item was changed:
  ----- Method: LiteralVariableNode>>sizeCodeForStore: (in category 'code generation') -----
  sizeCodeForStore: encoder
  self reserve: encoder.
  (key isVariableBinding and: [key isSpecialWriteBinding]) ifFalse:
  [^encoder sizeStoreLiteralVar: index].
  code < 0 ifTrue:
  [self flag: #dubious.
  self code: (self code: self index type: LdLitType)].
- "THIS IS WRONG!!!! THE VALUE IS LOST FROM THE STACK!!!!
- The various value: methods on Association ReadOnlyVariableBinding
- etc _do not_ return the value assigned; they return the receiver."
- "Should generate something more like
- push expr
- push lit
- push temp (index of expr)
- send value:
- pop"
- self flag: #bogus.
  writeNode := encoder encodeSelector: #value:.
+ "On entry the stack has only the expression.  Push the binding,
+ duplicate the expression, send #value: and pop."
+ ^(encoder sizePushLiteral: index)
+  + (encoder sizePushTempLong: 0) "we don't know yet, hence long, sigh..."
+  + (writeNode sizeCode: encoder args: 1 super: false)
+  + encoder sizePop!
- ^writeNode sizeCode: encoder args: 1 super: false!

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

Item was added:
+ ----- 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 removed:
- ----- Method: TempVariableNode>>sizeCodeForLoad: (in category 'code generation') -----
- sizeCodeForLoad: encoder
- ^remoteNode
- ifNil: [0]
- ifNotNil: [remoteNode sizeCodeForLoadFor: self encoder: encoder]!

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

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

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


Reply | Threaded
Open this post in threaded view
|

Re: The Trunk: Compiler-eem.258.mcz

Nicolas Cellier
Please review Compiler-nice.260 in the inbox because emitying code of a special assigment for effect seems to push twice the binding and pop only once. (If you run Decompiler tests you can see it)


2013/4/3 <[hidden email]>
Eliot Miranda uploaded a new version of Compiler to project The Trunk:
http://source.squeak.org/trunk/Compiler-eem.258.mcz

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

Name: Compiler-eem.258
Author: eem
Time: 3 April 2013, 12:59:36.409 pm
UUID: 7721a43f-63e6-4524-bb6d-48eddc955654
Ancestors: Compiler-eem.257

Fix store of special bindings.  Exsting code dropped the
value assigned from the stack, so v := binding := expr would
leave v holding binding, not expr.  New code generates
        push expr
        push binding
        duplicate expr (by pushTemp: of expr's stack index)
        send value:
        pop

=============== Diff against Compiler-eem.257 ===============

Item was changed:
  ----- Method: AssignmentNode>>emitCodeForEffect:encoder: (in category 'code generation') -----
  emitCodeForEffect: stack encoder: encoder

+       variable emitCodeForLoad: stack forValue: false encoder: encoder.
-       variable emitCodeForLoad: stack encoder: encoder.
        value emitCodeForValue: stack encoder: encoder.
        pc := encoder methodStreamPosition + 1. "debug pc is first byte of the store, i.e. the next byte".
        variable emitCodeForStorePop: stack encoder: encoder!

Item was changed:
  ----- Method: AssignmentNode>>emitCodeForValue:encoder: (in category 'code generation') -----
  emitCodeForValue: stack encoder: encoder

+       variable emitCodeForLoad: stack forValue: true encoder: encoder.
-       variable emitCodeForLoad: stack encoder: encoder.
        value emitCodeForValue: stack encoder: encoder.
        pc := encoder methodStreamPosition + 1. "debug pc is first byte of the store, i.e. the next byte".
        variable emitCodeForStore: stack encoder: encoder!

Item was changed:
  ----- Method: AssignmentNode>>sizeCodeForEffect: (in category 'code generation') -----
  sizeCodeForEffect: encoder

+       ^(variable sizeCodeForLoad: encoder forValue: false)
-       ^(variable sizeCodeForLoad: encoder)
        + (value sizeCodeForValue: encoder)
        + (variable sizeCodeForStorePop: encoder)!

Item was changed:
  ----- Method: AssignmentNode>>sizeCodeForValue: (in category 'code generation') -----
  sizeCodeForValue: encoder

+       ^(variable sizeCodeForLoad: encoder forValue: true)
-       ^(variable sizeCodeForLoad: encoder)
        + (value sizeCodeForValue: encoder)
        + (variable sizeCodeForStore: encoder)!

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

Item was added:
+ ----- Method: EncoderForV3>>genPushTempLong: (in category 'bytecode generation') -----
+ genPushTempLong: tempIndex
+       "See BlueBook page 596"
+       (tempIndex >= 0 and: [tempIndex < 64]) ifTrue:
+               ["128   10000000 jjkkkkkk       Push (Receiver Variable, Temporary Location, Literal Constant, Literal Variable) [jj] #kkkkkk"
+                stream
+                       nextPut: 128;
+                       nextPut: 64 + tempIndex.
+                ^self].
+       ^self outOfRangeError: 'index' index: tempIndex range: 0 to: 63!

Item was removed:
- ----- Method: FieldNode>>emitCodeForLoad:encoder: (in category 'code generation') -----
- emitCodeForLoad: stack encoder: encoder
-       rcvrNode emitCodeForValue: stack encoder: encoder.
-       fieldDef accessKey ifNotNil:[
-               super emitCodeForValue: stack encoder: encoder.
-       ].!

Item was added:
+ ----- Method: FieldNode>>emitCodeForLoad:forValue:encoder: (in category 'code generation') -----
+ emitCodeForLoad: stack forValue: forValue encoder: encoder
+       rcvrNode emitCodeForValue: stack encoder: encoder.
+       fieldDef accessKey ifNotNil:
+               [super emitCodeForValue: stack encoder: encoder]!

Item was removed:
- ----- Method: LeafNode>>emitCodeForLoad:encoder: (in category 'code generation') -----
- emitCodeForLoad: stack encoder: encoder
-       "Default is to do nothing.
-        Subclasses may need to override."!

Item was added:
+ ----- Method: LeafNode>>emitCodeForLoad:forValue:encoder: (in category 'code generation') -----
+ emitCodeForLoad: stack forValue: forValue encoder: encoder
+       "Default is to do nothing.
+        Subclasses may need to override."!

Item was removed:
- ----- Method: LeafNode>>sizeCodeForLoad: (in category 'code generation') -----
- sizeCodeForLoad: encoder
-       "Default is to do nothing.
-        Subclasses may need to override."
-       ^0!

Item was added:
+ ----- Method: LeafNode>>sizeCodeForLoad:forValue: (in category 'code generation') -----
+ sizeCodeForLoad: encoder forValue: forValue
+       "Default is to do nothing.
+        Subclasses may need to override."
+       ^0!

Item was removed:
- ----- Method: LiteralVariableNode>>emitCodeForLoad:encoder: (in category 'code generation') -----
- emitCodeForLoad: stack encoder: encoder
-       writeNode ifNotNil:
-               [encoder genPushLiteral: index.
-                stack push: 1]!

Item was added:
+ ----- Method: LiteralVariableNode>>emitCodeForLoad:forValue:encoder: (in category 'code generation') -----
+ emitCodeForLoad: stack forValue: forValue encoder: encoder
+       "If a normal literal variable (not sending value:), do nothing.
+        If for value (e.g. v := Binding := expr) do nothing; the work will be done in emitCodeForStore:encoder:.
+        If not for value then indeed load.  The rest of the work will be done in  emitCodeForStorePop:encoder:."
+       (writeNode isNil or: [forValue]) ifTrue: [^self].
+       encoder genPushLiteral: index.
+       stack push: 1!

Item was changed:
  ----- Method: LiteralVariableNode>>emitCodeForStore:encoder: (in category 'code generation') -----
  emitCodeForStore: stack encoder: encoder
+       | exprOffset |
        writeNode ifNil: [^encoder genStoreLiteralVar: index].
+       "On entry the stack has only the expression.  Push the binding,
+        duplicate the expression, send #value: and pop."
+       exprOffset := stack position - 1.
+       encoder genPushLiteral: index.
+       stack push: 1.
+       encoder genPushTempLong: exprOffset.
+       stack push: 1.
-       "THIS IS WRONG!!!! THE VALUE IS LOST FROM THE STACK!!!!
-        The various value: methods on Association ReadOnlyVariableBinding
-        etc _do not_ return the value assigned; they return the receiver."
-       "Should generate something more like
-               push expr
-               push lit
-               push temp (index of expr)
-               send value:
-               pop
-       or use e.g. valueForStore:"
-       self flag: #bogus.
        writeNode
                emitCode: stack
                args: 1
                encoder: encoder
+               super: false.
+       stack pop: 1.
+       encoder genPop!
-               super: false!

Item was removed:
- ----- Method: LiteralVariableNode>>sizeCodeForLoad: (in category 'code generation') -----
- sizeCodeForLoad: encoder
-       self reserve: encoder.
-       ^(key isVariableBinding and: [key isSpecialWriteBinding])
-               ifTrue: [encoder sizePushLiteral: index]
-               ifFalse: [0]!

Item was added:
+ ----- Method: LiteralVariableNode>>sizeCodeForLoad:forValue: (in category 'code generation') -----
+ sizeCodeForLoad: encoder forValue: forValue
+       self reserve: encoder.
+       ^(key isVariableBinding and: [key isSpecialWriteBinding and: [forValue not]])
+               ifTrue: [encoder sizePushLiteral: index]
+               ifFalse: [0]!

Item was changed:
  ----- Method: LiteralVariableNode>>sizeCodeForStore: (in category 'code generation') -----
  sizeCodeForStore: encoder
        self reserve: encoder.
        (key isVariableBinding and: [key isSpecialWriteBinding]) ifFalse:
                [^encoder sizeStoreLiteralVar: index].
        code < 0 ifTrue:
                [self flag: #dubious.
                 self code: (self code: self index type: LdLitType)].
-       "THIS IS WRONG!!!! THE VALUE IS LOST FROM THE STACK!!!!
-        The various value: methods on Association ReadOnlyVariableBinding
-        etc _do not_ return the value assigned; they return the receiver."
-       "Should generate something more like
-               push expr
-               push lit
-               push temp (index of expr)
-               send value:
-               pop"
-       self flag: #bogus.
        writeNode := encoder encodeSelector: #value:.
+       "On entry the stack has only the expression.  Push the binding,
+        duplicate the expression, send #value: and pop."
+       ^(encoder sizePushLiteral: index)
+         + (encoder sizePushTempLong: 0) "we don't know yet, hence long, sigh..."
+         + (writeNode sizeCode: encoder args: 1 super: false)
+         + encoder sizePop!
-       ^writeNode sizeCode: encoder args: 1 super: false!

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

Item was added:
+ ----- 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 removed:
- ----- Method: TempVariableNode>>sizeCodeForLoad: (in category 'code generation') -----
- sizeCodeForLoad: encoder
-       ^remoteNode
-               ifNil: [0]
-               ifNotNil: [remoteNode sizeCodeForLoadFor: self encoder: encoder]!

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

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

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





Reply | Threaded
Open this post in threaded view
|

Re: The Trunk: Compiler-eem.258.mcz

Frank Shearar-3
On 5 April 2013 01:37, Nicolas Cellier
<[hidden email]> wrote:
> Please review Compiler-nice.260 in the inbox because emitying code of a
> special assigment for effect seems to push twice the binding and pop only
> once. (If you run Decompiler tests you can see it)

Like this?: http://build.squeak.org/job/SqueakTrunk/256/testReport/junit/Tests.Compiler/DecompilerTests/testDecompilerInClassesDAtoDM/

frank

> 2013/4/3 <[hidden email]>
>
>> Eliot Miranda uploaded a new version of Compiler to project The Trunk:
>> http://source.squeak.org/trunk/Compiler-eem.258.mcz
>>
>> ==================== Summary ====================
>>
>> Name: Compiler-eem.258
>> Author: eem
>> Time: 3 April 2013, 12:59:36.409 pm
>> UUID: 7721a43f-63e6-4524-bb6d-48eddc955654
>> Ancestors: Compiler-eem.257
>>
>> Fix store of special bindings.  Exsting code dropped the
>> value assigned from the stack, so v := binding := expr would
>> leave v holding binding, not expr.  New code generates
>>         push expr
>>         push binding
>>         duplicate expr (by pushTemp: of expr's stack index)
>>         send value:
>>         pop
>>
>> =============== Diff against Compiler-eem.257 ===============
>>
>> Item was changed:
>>   ----- Method: AssignmentNode>>emitCodeForEffect:encoder: (in category
>> 'code generation') -----
>>   emitCodeForEffect: stack encoder: encoder
>>
>> +       variable emitCodeForLoad: stack forValue: false encoder: encoder.
>> -       variable emitCodeForLoad: stack encoder: encoder.
>>         value emitCodeForValue: stack encoder: encoder.
>>         pc := encoder methodStreamPosition + 1. "debug pc is first byte of
>> the store, i.e. the next byte".
>>         variable emitCodeForStorePop: stack encoder: encoder!
>>
>> Item was changed:
>>   ----- Method: AssignmentNode>>emitCodeForValue:encoder: (in category
>> 'code generation') -----
>>   emitCodeForValue: stack encoder: encoder
>>
>> +       variable emitCodeForLoad: stack forValue: true encoder: encoder.
>> -       variable emitCodeForLoad: stack encoder: encoder.
>>         value emitCodeForValue: stack encoder: encoder.
>>         pc := encoder methodStreamPosition + 1. "debug pc is first byte of
>> the store, i.e. the next byte".
>>         variable emitCodeForStore: stack encoder: encoder!
>>
>> Item was changed:
>>   ----- Method: AssignmentNode>>sizeCodeForEffect: (in category 'code
>> generation') -----
>>   sizeCodeForEffect: encoder
>>
>> +       ^(variable sizeCodeForLoad: encoder forValue: false)
>> -       ^(variable sizeCodeForLoad: encoder)
>>         + (value sizeCodeForValue: encoder)
>>         + (variable sizeCodeForStorePop: encoder)!
>>
>> Item was changed:
>>   ----- Method: AssignmentNode>>sizeCodeForValue: (in category 'code
>> generation') -----
>>   sizeCodeForValue: encoder
>>
>> +       ^(variable sizeCodeForLoad: encoder forValue: true)
>> -       ^(variable sizeCodeForLoad: encoder)
>>         + (value sizeCodeForValue: encoder)
>>         + (variable sizeCodeForStore: encoder)!
>>
>> Item was added:
>> + ----- Method: BytecodeEncoder>>sizePushTempLong: (in category 'opcode
>> sizing') -----
>> + sizePushTempLong: tempIndex
>> +       ^self sizeOpcodeSelector: #genPushTempLong: withArguments:
>> {tempIndex}!
>>
>> Item was added:
>> + ----- Method: EncoderForV3>>genPushTempLong: (in category 'bytecode
>> generation') -----
>> + genPushTempLong: tempIndex
>> +       "See BlueBook page 596"
>> +       (tempIndex >= 0 and: [tempIndex < 64]) ifTrue:
>> +               ["128   10000000 jjkkkkkk       Push (Receiver Variable,
>> Temporary Location, Literal Constant, Literal Variable) [jj] #kkkkkk"
>> +                stream
>> +                       nextPut: 128;
>> +                       nextPut: 64 + tempIndex.
>> +                ^self].
>> +       ^self outOfRangeError: 'index' index: tempIndex range: 0 to: 63!
>>
>> Item was removed:
>> - ----- Method: FieldNode>>emitCodeForLoad:encoder: (in category 'code
>> generation') -----
>> - emitCodeForLoad: stack encoder: encoder
>> -       rcvrNode emitCodeForValue: stack encoder: encoder.
>> -       fieldDef accessKey ifNotNil:[
>> -               super emitCodeForValue: stack encoder: encoder.
>> -       ].!
>>
>> Item was added:
>> + ----- Method: FieldNode>>emitCodeForLoad:forValue:encoder: (in category
>> 'code generation') -----
>> + emitCodeForLoad: stack forValue: forValue encoder: encoder
>> +       rcvrNode emitCodeForValue: stack encoder: encoder.
>> +       fieldDef accessKey ifNotNil:
>> +               [super emitCodeForValue: stack encoder: encoder]!
>>
>> Item was removed:
>> - ----- Method: LeafNode>>emitCodeForLoad:encoder: (in category 'code
>> generation') -----
>> - emitCodeForLoad: stack encoder: encoder
>> -       "Default is to do nothing.
>> -        Subclasses may need to override."!
>>
>> Item was added:
>> + ----- Method: LeafNode>>emitCodeForLoad:forValue:encoder: (in category
>> 'code generation') -----
>> + emitCodeForLoad: stack forValue: forValue encoder: encoder
>> +       "Default is to do nothing.
>> +        Subclasses may need to override."!
>>
>> Item was removed:
>> - ----- Method: LeafNode>>sizeCodeForLoad: (in category 'code generation')
>> -----
>> - sizeCodeForLoad: encoder
>> -       "Default is to do nothing.
>> -        Subclasses may need to override."
>> -       ^0!
>>
>> Item was added:
>> + ----- Method: LeafNode>>sizeCodeForLoad:forValue: (in category 'code
>> generation') -----
>> + sizeCodeForLoad: encoder forValue: forValue
>> +       "Default is to do nothing.
>> +        Subclasses may need to override."
>> +       ^0!
>>
>> Item was removed:
>> - ----- Method: LiteralVariableNode>>emitCodeForLoad:encoder: (in category
>> 'code generation') -----
>> - emitCodeForLoad: stack encoder: encoder
>> -       writeNode ifNotNil:
>> -               [encoder genPushLiteral: index.
>> -                stack push: 1]!
>>
>> Item was added:
>> + ----- Method: LiteralVariableNode>>emitCodeForLoad:forValue:encoder: (in
>> category 'code generation') -----
>> + emitCodeForLoad: stack forValue: forValue encoder: encoder
>> +       "If a normal literal variable (not sending value:), do nothing.
>> +        If for value (e.g. v := Binding := expr) do nothing; the work
>> will be done in emitCodeForStore:encoder:.
>> +        If not for value then indeed load.  The rest of the work will be
>> done in  emitCodeForStorePop:encoder:."
>> +       (writeNode isNil or: [forValue]) ifTrue: [^self].
>> +       encoder genPushLiteral: index.
>> +       stack push: 1!
>>
>> Item was changed:
>>   ----- Method: LiteralVariableNode>>emitCodeForStore:encoder: (in
>> category 'code generation') -----
>>   emitCodeForStore: stack encoder: encoder
>> +       | exprOffset |
>>         writeNode ifNil: [^encoder genStoreLiteralVar: index].
>> +       "On entry the stack has only the expression.  Push the binding,
>> +        duplicate the expression, send #value: and pop."
>> +       exprOffset := stack position - 1.
>> +       encoder genPushLiteral: index.
>> +       stack push: 1.
>> +       encoder genPushTempLong: exprOffset.
>> +       stack push: 1.
>> -       "THIS IS WRONG!!!! THE VALUE IS LOST FROM THE STACK!!!!
>> -        The various value: methods on Association ReadOnlyVariableBinding
>> -        etc _do not_ return the value assigned; they return the
>> receiver."
>> -       "Should generate something more like
>> -               push expr
>> -               push lit
>> -               push temp (index of expr)
>> -               send value:
>> -               pop
>> -       or use e.g. valueForStore:"
>> -       self flag: #bogus.
>>         writeNode
>>                 emitCode: stack
>>                 args: 1
>>                 encoder: encoder
>> +               super: false.
>> +       stack pop: 1.
>> +       encoder genPop!
>> -               super: false!
>>
>> Item was removed:
>> - ----- Method: LiteralVariableNode>>sizeCodeForLoad: (in category 'code
>> generation') -----
>> - sizeCodeForLoad: encoder
>> -       self reserve: encoder.
>> -       ^(key isVariableBinding and: [key isSpecialWriteBinding])
>> -               ifTrue: [encoder sizePushLiteral: index]
>> -               ifFalse: [0]!
>>
>> Item was added:
>> + ----- Method: LiteralVariableNode>>sizeCodeForLoad:forValue: (in
>> category 'code generation') -----
>> + sizeCodeForLoad: encoder forValue: forValue
>> +       self reserve: encoder.
>> +       ^(key isVariableBinding and: [key isSpecialWriteBinding and:
>> [forValue not]])
>> +               ifTrue: [encoder sizePushLiteral: index]
>> +               ifFalse: [0]!
>>
>> Item was changed:
>>   ----- Method: LiteralVariableNode>>sizeCodeForStore: (in category 'code
>> generation') -----
>>   sizeCodeForStore: encoder
>>         self reserve: encoder.
>>         (key isVariableBinding and: [key isSpecialWriteBinding]) ifFalse:
>>                 [^encoder sizeStoreLiteralVar: index].
>>         code < 0 ifTrue:
>>                 [self flag: #dubious.
>>                  self code: (self code: self index type: LdLitType)].
>> -       "THIS IS WRONG!!!! THE VALUE IS LOST FROM THE STACK!!!!
>> -        The various value: methods on Association ReadOnlyVariableBinding
>> -        etc _do not_ return the value assigned; they return the
>> receiver."
>> -       "Should generate something more like
>> -               push expr
>> -               push lit
>> -               push temp (index of expr)
>> -               send value:
>> -               pop"
>> -       self flag: #bogus.
>>         writeNode := encoder encodeSelector: #value:.
>> +       "On entry the stack has only the expression.  Push the binding,
>> +        duplicate the expression, send #value: and pop."
>> +       ^(encoder sizePushLiteral: index)
>> +         + (encoder sizePushTempLong: 0) "we don't know yet, hence long,
>> sigh..."
>> +         + (writeNode sizeCode: encoder args: 1 super: false)
>> +         + encoder sizePop!
>> -       ^writeNode sizeCode: encoder args: 1 super: false!
>>
>> Item was removed:
>> - ----- Method: TempVariableNode>>emitCodeForLoad:encoder: (in category
>> 'code generation') -----
>> - emitCodeForLoad: stack encoder: encoder
>> -       remoteNode ~~ nil ifTrue:
>> -               [remoteNode emitCodeForLoadFor: self stack: stack encoder:
>> encoder]!
>>
>> Item was added:
>> + ----- 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 removed:
>> - ----- Method: TempVariableNode>>sizeCodeForLoad: (in category 'code
>> generation') -----
>> - sizeCodeForLoad: encoder
>> -       ^remoteNode
>> -               ifNil: [0]
>> -               ifNotNil: [remoteNode sizeCodeForLoadFor: self encoder:
>> encoder]!
>>
>> Item was added:
>> + ----- Method: TempVariableNode>>sizeCodeForLoad:forValue: (in category
>> 'code generation') -----
>> + sizeCodeForLoad: encoder forValue: forValue
>> +       ^remoteNode
>> +               ifNil: [0]
>> +               ifNotNil: [remoteNode sizeCodeForLoadFor: self encoder:
>> encoder]!
>>
>> Item was removed:
>> - ----- Method: VariableNode>>emitCodeForLoad:encoder: (in category 'code
>> generation') -----
>> - emitCodeForLoad: stack encoder: encoder
>> -       "Do nothing"!
>>
>> Item was added:
>> + ----- Method: VariableNode>>emitCodeForLoad:forValue:encoder: (in
>> category 'code generation') -----
>> + emitCodeForLoad: stack forValue: forValue encoder: encoder
>> +       "Do nothing"!
>>
>>
>
>
>
>

Reply | Threaded
Open this post in threaded view
|

Re: The Trunk: Compiler-eem.258.mcz

Nicolas Cellier
Yes exactly, my version in inbox should correct these new failures


2013/4/5 Frank Shearar <[hidden email]>
On 5 April 2013 01:37, Nicolas Cellier
<[hidden email]> wrote:
> Please review Compiler-nice.260 in the inbox because emitying code of a
> special assigment for effect seems to push twice the binding and pop only
> once. (If you run Decompiler tests you can see it)

Like this?: http://build.squeak.org/job/SqueakTrunk/256/testReport/junit/Tests.Compiler/DecompilerTests/testDecompilerInClassesDAtoDM/

frank

> 2013/4/3 <[hidden email]>
>
>> Eliot Miranda uploaded a new version of Compiler to project The Trunk:
>> http://source.squeak.org/trunk/Compiler-eem.258.mcz
>>
>> ==================== Summary ====================
>>
>> Name: Compiler-eem.258
>> Author: eem
>> Time: 3 April 2013, 12:59:36.409 pm
>> UUID: 7721a43f-63e6-4524-bb6d-48eddc955654
>> Ancestors: Compiler-eem.257
>>
>> Fix store of special bindings.  Exsting code dropped the
>> value assigned from the stack, so v := binding := expr would
>> leave v holding binding, not expr.  New code generates
>>         push expr
>>         push binding
>>         duplicate expr (by pushTemp: of expr's stack index)
>>         send value:
>>         pop
>>
>> =============== Diff against Compiler-eem.257 ===============
>>
>> Item was changed:
>>   ----- Method: AssignmentNode>>emitCodeForEffect:encoder: (in category
>> 'code generation') -----
>>   emitCodeForEffect: stack encoder: encoder
>>
>> +       variable emitCodeForLoad: stack forValue: false encoder: encoder.
>> -       variable emitCodeForLoad: stack encoder: encoder.
>>         value emitCodeForValue: stack encoder: encoder.
>>         pc := encoder methodStreamPosition + 1. "debug pc is first byte of
>> the store, i.e. the next byte".
>>         variable emitCodeForStorePop: stack encoder: encoder!
>>
>> Item was changed:
>>   ----- Method: AssignmentNode>>emitCodeForValue:encoder: (in category
>> 'code generation') -----
>>   emitCodeForValue: stack encoder: encoder
>>
>> +       variable emitCodeForLoad: stack forValue: true encoder: encoder.
>> -       variable emitCodeForLoad: stack encoder: encoder.
>>         value emitCodeForValue: stack encoder: encoder.
>>         pc := encoder methodStreamPosition + 1. "debug pc is first byte of
>> the store, i.e. the next byte".
>>         variable emitCodeForStore: stack encoder: encoder!
>>
>> Item was changed:
>>   ----- Method: AssignmentNode>>sizeCodeForEffect: (in category 'code
>> generation') -----
>>   sizeCodeForEffect: encoder
>>
>> +       ^(variable sizeCodeForLoad: encoder forValue: false)
>> -       ^(variable sizeCodeForLoad: encoder)
>>         + (value sizeCodeForValue: encoder)
>>         + (variable sizeCodeForStorePop: encoder)!
>>
>> Item was changed:
>>   ----- Method: AssignmentNode>>sizeCodeForValue: (in category 'code
>> generation') -----
>>   sizeCodeForValue: encoder
>>
>> +       ^(variable sizeCodeForLoad: encoder forValue: true)
>> -       ^(variable sizeCodeForLoad: encoder)
>>         + (value sizeCodeForValue: encoder)
>>         + (variable sizeCodeForStore: encoder)!
>>
>> Item was added:
>> + ----- Method: BytecodeEncoder>>sizePushTempLong: (in category 'opcode
>> sizing') -----
>> + sizePushTempLong: tempIndex
>> +       ^self sizeOpcodeSelector: #genPushTempLong: withArguments:
>> {tempIndex}!
>>
>> Item was added:
>> + ----- Method: EncoderForV3>>genPushTempLong: (in category 'bytecode
>> generation') -----
>> + genPushTempLong: tempIndex
>> +       "See BlueBook page 596"
>> +       (tempIndex >= 0 and: [tempIndex < 64]) ifTrue:
>> +               ["128   10000000 jjkkkkkk       Push (Receiver Variable,
>> Temporary Location, Literal Constant, Literal Variable) [jj] #kkkkkk"
>> +                stream
>> +                       nextPut: 128;
>> +                       nextPut: 64 + tempIndex.
>> +                ^self].
>> +       ^self outOfRangeError: 'index' index: tempIndex range: 0 to: 63!
>>
>> Item was removed:
>> - ----- Method: FieldNode>>emitCodeForLoad:encoder: (in category 'code
>> generation') -----
>> - emitCodeForLoad: stack encoder: encoder
>> -       rcvrNode emitCodeForValue: stack encoder: encoder.
>> -       fieldDef accessKey ifNotNil:[
>> -               super emitCodeForValue: stack encoder: encoder.
>> -       ].!
>>
>> Item was added:
>> + ----- Method: FieldNode>>emitCodeForLoad:forValue:encoder: (in category
>> 'code generation') -----
>> + emitCodeForLoad: stack forValue: forValue encoder: encoder
>> +       rcvrNode emitCodeForValue: stack encoder: encoder.
>> +       fieldDef accessKey ifNotNil:
>> +               [super emitCodeForValue: stack encoder: encoder]!
>>
>> Item was removed:
>> - ----- Method: LeafNode>>emitCodeForLoad:encoder: (in category 'code
>> generation') -----
>> - emitCodeForLoad: stack encoder: encoder
>> -       "Default is to do nothing.
>> -        Subclasses may need to override."!
>>
>> Item was added:
>> + ----- Method: LeafNode>>emitCodeForLoad:forValue:encoder: (in category
>> 'code generation') -----
>> + emitCodeForLoad: stack forValue: forValue encoder: encoder
>> +       "Default is to do nothing.
>> +        Subclasses may need to override."!
>>
>> Item was removed:
>> - ----- Method: LeafNode>>sizeCodeForLoad: (in category 'code generation')
>> -----
>> - sizeCodeForLoad: encoder
>> -       "Default is to do nothing.
>> -        Subclasses may need to override."
>> -       ^0!
>>
>> Item was added:
>> + ----- Method: LeafNode>>sizeCodeForLoad:forValue: (in category 'code
>> generation') -----
>> + sizeCodeForLoad: encoder forValue: forValue
>> +       "Default is to do nothing.
>> +        Subclasses may need to override."
>> +       ^0!
>>
>> Item was removed:
>> - ----- Method: LiteralVariableNode>>emitCodeForLoad:encoder: (in category
>> 'code generation') -----
>> - emitCodeForLoad: stack encoder: encoder
>> -       writeNode ifNotNil:
>> -               [encoder genPushLiteral: index.
>> -                stack push: 1]!
>>
>> Item was added:
>> + ----- Method: LiteralVariableNode>>emitCodeForLoad:forValue:encoder: (in
>> category 'code generation') -----
>> + emitCodeForLoad: stack forValue: forValue encoder: encoder
>> +       "If a normal literal variable (not sending value:), do nothing.
>> +        If for value (e.g. v := Binding := expr) do nothing; the work
>> will be done in emitCodeForStore:encoder:.
>> +        If not for value then indeed load.  The rest of the work will be
>> done in  emitCodeForStorePop:encoder:."
>> +       (writeNode isNil or: [forValue]) ifTrue: [^self].
>> +       encoder genPushLiteral: index.
>> +       stack push: 1!
>>
>> Item was changed:
>>   ----- Method: LiteralVariableNode>>emitCodeForStore:encoder: (in
>> category 'code generation') -----
>>   emitCodeForStore: stack encoder: encoder
>> +       | exprOffset |
>>         writeNode ifNil: [^encoder genStoreLiteralVar: index].
>> +       "On entry the stack has only the expression.  Push the binding,
>> +        duplicate the expression, send #value: and pop."
>> +       exprOffset := stack position - 1.
>> +       encoder genPushLiteral: index.
>> +       stack push: 1.
>> +       encoder genPushTempLong: exprOffset.
>> +       stack push: 1.
>> -       "THIS IS WRONG!!!! THE VALUE IS LOST FROM THE STACK!!!!
>> -        The various value: methods on Association ReadOnlyVariableBinding
>> -        etc _do not_ return the value assigned; they return the
>> receiver."
>> -       "Should generate something more like
>> -               push expr
>> -               push lit
>> -               push temp (index of expr)
>> -               send value:
>> -               pop
>> -       or use e.g. valueForStore:"
>> -       self flag: #bogus.
>>         writeNode
>>                 emitCode: stack
>>                 args: 1
>>                 encoder: encoder
>> +               super: false.
>> +       stack pop: 1.
>> +       encoder genPop!
>> -               super: false!
>>
>> Item was removed:
>> - ----- Method: LiteralVariableNode>>sizeCodeForLoad: (in category 'code
>> generation') -----
>> - sizeCodeForLoad: encoder
>> -       self reserve: encoder.
>> -       ^(key isVariableBinding and: [key isSpecialWriteBinding])
>> -               ifTrue: [encoder sizePushLiteral: index]
>> -               ifFalse: [0]!
>>
>> Item was added:
>> + ----- Method: LiteralVariableNode>>sizeCodeForLoad:forValue: (in
>> category 'code generation') -----
>> + sizeCodeForLoad: encoder forValue: forValue
>> +       self reserve: encoder.
>> +       ^(key isVariableBinding and: [key isSpecialWriteBinding and:
>> [forValue not]])
>> +               ifTrue: [encoder sizePushLiteral: index]
>> +               ifFalse: [0]!
>>
>> Item was changed:
>>   ----- Method: LiteralVariableNode>>sizeCodeForStore: (in category 'code
>> generation') -----
>>   sizeCodeForStore: encoder
>>         self reserve: encoder.
>>         (key isVariableBinding and: [key isSpecialWriteBinding]) ifFalse:
>>                 [^encoder sizeStoreLiteralVar: index].
>>         code < 0 ifTrue:
>>                 [self flag: #dubious.
>>                  self code: (self code: self index type: LdLitType)].
>> -       "THIS IS WRONG!!!! THE VALUE IS LOST FROM THE STACK!!!!
>> -        The various value: methods on Association ReadOnlyVariableBinding
>> -        etc _do not_ return the value assigned; they return the
>> receiver."
>> -       "Should generate something more like
>> -               push expr
>> -               push lit
>> -               push temp (index of expr)
>> -               send value:
>> -               pop"
>> -       self flag: #bogus.
>>         writeNode := encoder encodeSelector: #value:.
>> +       "On entry the stack has only the expression.  Push the binding,
>> +        duplicate the expression, send #value: and pop."
>> +       ^(encoder sizePushLiteral: index)
>> +         + (encoder sizePushTempLong: 0) "we don't know yet, hence long,
>> sigh..."
>> +         + (writeNode sizeCode: encoder args: 1 super: false)
>> +         + encoder sizePop!
>> -       ^writeNode sizeCode: encoder args: 1 super: false!
>>
>> Item was removed:
>> - ----- Method: TempVariableNode>>emitCodeForLoad:encoder: (in category
>> 'code generation') -----
>> - emitCodeForLoad: stack encoder: encoder
>> -       remoteNode ~~ nil ifTrue:
>> -               [remoteNode emitCodeForLoadFor: self stack: stack encoder:
>> encoder]!
>>
>> Item was added:
>> + ----- 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 removed:
>> - ----- Method: TempVariableNode>>sizeCodeForLoad: (in category 'code
>> generation') -----
>> - sizeCodeForLoad: encoder
>> -       ^remoteNode
>> -               ifNil: [0]
>> -               ifNotNil: [remoteNode sizeCodeForLoadFor: self encoder:
>> encoder]!
>>
>> Item was added:
>> + ----- Method: TempVariableNode>>sizeCodeForLoad:forValue: (in category
>> 'code generation') -----
>> + sizeCodeForLoad: encoder forValue: forValue
>> +       ^remoteNode
>> +               ifNil: [0]
>> +               ifNotNil: [remoteNode sizeCodeForLoadFor: self encoder:
>> encoder]!
>>
>> Item was removed:
>> - ----- Method: VariableNode>>emitCodeForLoad:encoder: (in category 'code
>> generation') -----
>> - emitCodeForLoad: stack encoder: encoder
>> -       "Do nothing"!
>>
>> Item was added:
>> + ----- Method: VariableNode>>emitCodeForLoad:forValue:encoder: (in
>> category 'code generation') -----
>> + emitCodeForLoad: stack forValue: forValue encoder: encoder
>> +       "Do nothing"!
>>
>>
>
>
>
>