Order of evaluation bug with in lined to:do: in both Opal and Squeak compilers.

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

Order of evaluation bug with in lined to:do: in both Opal and Squeak compilers.

Eliot Miranda-2
Hi All,

    just stumbled across a bytecode compiler bug that's in both the Squeak compiler and the Opal compiler.  I'm told by Clément that Opal mimics the bug to avoid crashing legacy code.  So there may be places that depend on this bug.  It would be good to eliminate the dependencies and the bug.

For illustration look at the to:do: loop in the ifNil: arm in Context>>privRefresh:

Context>>privRefresh
"Reinitialize the receiver so that it is in the state it was at its creation."
closureOrNil
ifNotNil:
[pc := closureOrNil startpc.
self stackp: closureOrNil numArgs + closureOrNil numCopiedValues.
1 to: closureOrNil numCopiedValues do:
[:i | self tempAt: closureOrNil numArgs + i put: (closureOrNil at: i)]]
ifNil:
[pc := method initialPC.
self stackp: method numTemps.
method numArgs+1 to: method numTemps do:
[:i | self tempAt: i put: nil]]


This should evaluate method numArgs + 1 then method numTemps.  If it were written as a non-in-lined (method numArgs+1 to: method numTemps) do: [:i| self tempAt: i put: nil] then the [self tempAt: i put: nil] block would be created next.  But the bytecode for the inlined version is

self stackp: method numTemps.
63 <70> self
64 <84 40 03> pushRcvr: 3
67 <D6> send: numTemps
68 <E1> send: stackp:
69 <87> pop

iLimit := method numTemps
70 <84 40 03> pushRcvr: 3
73 <D6> send: numTemps
74 <69> popIntoTemp: 1

i := method numArgs + 1
75 <84 40 03> pushRcvr: 3
78 <D2> send: numArgs
79 <76> pushConstant: 1
80 <B0> send: +
81 <81 40> storeIntoTemp: 0 (squeak) <69> popIntoTemp: 1 (pharo)
83 <10> pushTemp: 0
84 <11> pushTemp: 1
85 <B4> send: <=
86 <AC 0B> jumpFalse: 99

There is a second bug in the Squeak bytecode; storeIntoTemp: is used to load i whereas it should be popIntoTemp:.  It was this second bug that alerted me to the order-of-evaluation bug.

_,,,^..^,,,_
best, Eliot


Reply | Threaded
Open this post in threaded view
|

Re: Order of evaluation bug with in lined to:do: in both Opal and Squeak compilers.

Eliot Miranda-2


On Thu, Apr 20, 2017 at 4:41 PM, Eliot Miranda <[hidden email]> wrote:
Hi All,

    just stumbled across a bytecode compiler bug that's in both the Squeak compiler and the Opal compiler.  I'm told by Clément that Opal mimics the bug to avoid crashing legacy code.  So there may be places that depend on this bug.  It would be good to eliminate the dependencies and the bug.

For illustration look at the to:do: loop in the ifNil: arm in Context>>privRefresh:

Context>>privRefresh
"Reinitialize the receiver so that it is in the state it was at its creation."
closureOrNil
ifNotNil:
[pc := closureOrNil startpc.
self stackp: closureOrNil numArgs + closureOrNil numCopiedValues.
1 to: closureOrNil numCopiedValues do:
[:i | self tempAt: closureOrNil numArgs + i put: (closureOrNil at: i)]]
ifNil:
[pc := method initialPC.
self stackp: method numTemps.
method numArgs+1 to: method numTemps do:
[:i | self tempAt: i put: nil]]


This should evaluate method numArgs + 1 then method numTemps.  If it were written as a non-in-lined (method numArgs+1 to: method numTemps) do: [:i| self tempAt: i put: nil] then the [self tempAt: i put: nil] block would be created next.  But the bytecode for the inlined version is

self stackp: method numTemps.
63 <70> self
64 <84 40 03> pushRcvr: 3
67 <D6> send: numTemps
68 <E1> send: stackp:
69 <87> pop

iLimit := method numTemps
70 <84 40 03> pushRcvr: 3
73 <D6> send: numTemps
74 <69> popIntoTemp: 1

i := method numArgs + 1
75 <84 40 03> pushRcvr: 3
78 <D2> send: numArgs
79 <76> pushConstant: 1
80 <B0> send: +
81 <81 40> storeIntoTemp: 0 (squeak) <69> popIntoTemp: 1 (pharo)
83 <10> pushTemp: 0
84 <11> pushTemp: 1
85 <B4> send: <=
86 <AC 0B> jumpFalse: 99

There is a second bug in the Squeak bytecode; storeIntoTemp: is used to load i whereas it should be popIntoTemp:.  It was this second bug that alerted me to the order-of-evaluation bug.

The second bug (Squeak's use of storeIntoTemp:) is actually only a poor implementation of the value/effect distinction through the inlined ifNil:ifNotNil:.  Because ifNil:ifNotNil: has a value (albeit one that is discarded) the Squeak compiler generates a storeIntoTemp: to p[reserve the value of the to:do: lop, which is the initial index.  So the bug is not within the generation of the to:do: (the only bug there being the order-of-evaluation one).  The bug is actually outside; the loop should be being generated for effect but is being evaluated for value.

On the order of evaluation bug, does anyone have any memory of which methods depended on this bug?

_,,,^..^,,,_
best, Eliot



--
_,,,^..^,,,_
best, Eliot


Reply | Threaded
Open this post in threaded view
|

Re: [Vm-dev] Order of evaluation bug with in lined to:do: in both Opal and Squeak compilers.

Nicolai Hess-3-2


2017-04-21 1:56 GMT+02:00 Eliot Miranda <[hidden email]>:
 


On Thu, Apr 20, 2017 at 4:41 PM, Eliot Miranda <[hidden email]> wrote:
Hi All,

    just stumbled across a bytecode compiler bug that's in both the Squeak compiler and the Opal compiler.  I'm told by Clément that Opal mimics the bug to avoid crashing legacy code.  So there may be places that depend on this bug.  It would be good to eliminate the dependencies and the bug.

For illustration look at the to:do: loop in the ifNil: arm in Context>>privRefresh:

Context>>privRefresh
"Reinitialize the receiver so that it is in the state it was at its creation."
closureOrNil
ifNotNil:
[pc := closureOrNil startpc.
self stackp: closureOrNil numArgs + closureOrNil numCopiedValues.
1 to: closureOrNil numCopiedValues do:
[:i | self tempAt: closureOrNil numArgs + i put: (closureOrNil at: i)]]
ifNil:
[pc := method initialPC.
self stackp: method numTemps.
method numArgs+1 to: method numTemps do:
[:i | self tempAt: i put: nil]]


This should evaluate method numArgs + 1 then method numTemps.  If it were written as a non-in-lined (method numArgs+1 to: method numTemps) do: [:i| self tempAt: i put: nil] then the [self tempAt: i put: nil] block would be created next.  But the bytecode for the inlined version is

self stackp: method numTemps.
63 <70> self
64 <84 40 03> pushRcvr: 3
67 <D6> send: numTemps
68 <E1> send: stackp:
69 <87> pop

iLimit := method numTemps
70 <84 40 03> pushRcvr: 3
73 <D6> send: numTemps
74 <69> popIntoTemp: 1

i := method numArgs + 1
75 <84 40 03> pushRcvr: 3
78 <D2> send: numArgs
79 <76> pushConstant: 1
80 <B0> send: +
81 <81 40> storeIntoTemp: 0 (squeak) <69> popIntoTemp: 1 (pharo)
83 <10> pushTemp: 0
84 <11> pushTemp: 1
85 <B4> send: <=
86 <AC 0B> jumpFalse: 99

There is a second bug in the Squeak bytecode; storeIntoTemp: is used to load i whereas it should be popIntoTemp:.  It was this second bug that alerted me to the order-of-evaluation bug.

The second bug (Squeak's use of storeIntoTemp:) is actually only a poor implementation of the value/effect distinction through the inlined ifNil:ifNotNil:.  Because ifNil:ifNotNil: has a value (albeit one that is discarded) the Squeak compiler generates a storeIntoTemp: to p[reserve the value of the to:do: lop, which is the initial index.  So the bug is not within the generation of the to:do: (the only bug there being the order-of-evaluation one).  The bug is actually outside; the loop should be being generated for effect but is being evaluated for value.

On the order of evaluation bug, does anyone have any memory of which methods depended on this bug?

_,,,^..^,,,_
best, Eliot



--
_,,,^..^,,,_
best, Eliot




Reply | Threaded
Open this post in threaded view
|

Re: Order of evaluation bug with in lined to:do: in both Opal and Squeak compilers.

Bert Freudenberg
In reply to this post by Eliot Miranda-2
On Fri, Apr 21, 2017 at 1:56 AM, Eliot Miranda <[hidden email]> wrote:
On the order of evaluation bug, does anyone have any memory of which methods depended on this bug?

No idea ...

- Bert -


Reply | Threaded
Open this post in threaded view
|

Re: Order of evaluation bug with in lined to:do: in both Opal and Squeak compilers.

Nicolas Cellier
I see more than 1000 senders but most of them are in the style 1 to: ...
If any of receiver or 1st arg is a LiteralNode, no need to analyze, so it should be possible to write a small analyzer to select non trivial cases and review manually. Something like:

SystemNavigation default
    browseMessageList: ((SystemNavigation default allCallsOn: #to:do:) select: [:e |
        | ast found |
        ast := e actualClass newParser parse: e sourceCode class: e actualClass.
        found := nil.
        ast accept: (ParseNodeEnumerator
            ofBlock: [:node | ((node isKindOf: MessageNode)
                    and: [node selector key = #to:do:
                    and: [node receiver isLiteralNode not
                    and: [node arguments first isLiteralNode not]]])
                ifTrue: [found := node]]).
        found notNil])
    name: 'complex senders of to:do:'
    autoSelect: true.

Above script did not find any complex senders though I see some, so I must have screwed something, but you get the idea.

Then there is the case of to:by:do: to analyze too.


2017-04-21 16:08 GMT+02:00 Bert Freudenberg <[hidden email]>:
On Fri, Apr 21, 2017 at 1:56 AM, Eliot Miranda <[hidden email]> wrote:
On the order of evaluation bug, does anyone have any memory of which methods depended on this bug?

No idea ...

- Bert -






Reply | Threaded
Open this post in threaded view
|

Re: Order of evaluation bug with in lined to:do: in both Opal and Squeak compilers.

Nicolas Cellier


2017-04-21 23:05 GMT+02:00 Nicolas Cellier <[hidden email]>:
I see more than 1000 senders but most of them are in the style 1 to: ...
If any of receiver or 1st arg is a LiteralNode, no need to analyze, so it should be possible to write a small analyzer to select non trivial cases and review manually. Something like:

SystemNavigation default
    browseMessageList: ((SystemNavigation default allCallsOn: #to:do:) select: [:e |
        | ast found |
        ast := e actualClass newParser parse: e sourceCode class: e actualClass.
        found := nil.
        ast accept: (ParseNodeEnumerator
            ofBlock: [:node | ((node isKindOf: MessageNode)
                    and: [node selector key = #to:do:
                    and: [node receiver isLiteralNode not
                    and: [node arguments first isLiteralNode not]]])
                ifTrue: [found := node]]).
        found notNil])
    name: 'complex senders of to:do:'
    autoSelect: true.

Above script did not find any complex senders though I see some, so I must have screwed something, but you get the idea.

Then there is the case of to:by:do: to analyze too.


Ah, my script failed because to:do: is transformed at this stage (disguised in #to:by:do:)...

SystemNavigation default
    browseMessageList: ((SystemNavigation default allCallsOn: #to:do:) select: [:e |
        | ast found |
        ast := e actualClass newParser parse: e sourceCode class: e actualClass.
        found := nil.
        ast accept: (ParseNodeEnumerator
            ofBlock: [:node | ((node isKindOf: MessageNode)
                    and: [(node selector key = #to:do: or: [node selector key = #to:by:do: ])
                    and: [node receiver isLiteralNode not
                    and: [node arguments first isLiteralNode not]]])
                ifTrue: [found := node]]).
        found notNil])
    name: 'complex senders of to:do:'
    autoSelect: #to:do:
 
But I can't test other trivial cases when node arguments first isVariableNode, because it allways is after transform.
It would be necessary to disable transform during analysis...


2017-04-21 16:08 GMT+02:00 Bert Freudenberg <[hidden email]>:
On Fri, Apr 21, 2017 at 1:56 AM, Eliot Miranda <[hidden email]> wrote:
On the order of evaluation bug, does anyone have any memory of which methods depended on this bug?

No idea ...

- Bert -







Reply | Threaded
Open this post in threaded view
|

Re: Order of evaluation bug with in lined to:do: in both Opal and Squeak compilers.

Levente Uzonyi
This seems to work:

methods := (SystemNavigation default allCallsOn: #to:do:) asSet.
methods addAll: (SystemNavigation default allCallsOn: #to:by:do:).
methods := CurrentReadOnlySourceFiles cacheDuring: [
  methods select: [ :methodReference |
  | ast found |
  ast := methodReference actualClass newParser parse: methodReference sourceCode class: methodReference actualClass.
  found := nil.
  ast accept: (ParseNodeEnumerator ofBlock: [ :node |
  (node isMessage
  and: [ (#(to:do: to:by:do:) includes: node selector key)
  and: [ node receiver isLiteralNode not
  and: [ node receiver isVariableNode not
  and: [ node arguments first isLiteralNode not
  and: [ node arguments first isVariableNode not ] ] ] ] ])
  ifTrue: [ found := node ] ]).
  found notNil ] ].
SystemNavigation default
  browseMessageList: methods sorted
  name: 'complex senders of to:do:'
  autoSelect: 'to:'.

Levente

On Sat, 22 Apr 2017, Nicolas Cellier wrote:

>
>
> 2017-04-21 23:05 GMT+02:00 Nicolas Cellier <[hidden email]>:
>       I see more than 1000 senders but most of them are in the style 1 to: ...
> If any of receiver or 1st arg is a LiteralNode, no need to analyze, so it should be possible to write a small analyzer to select non trivial cases and review manually. Something like:
>
> SystemNavigation default
>     browseMessageList: ((SystemNavigation default allCallsOn: #to:do:) select: [:e |
>         | ast found |
>         ast := e actualClass newParser parse: e sourceCode class: e actualClass.
>         found := nil.
>         ast accept: (ParseNodeEnumerator
>             ofBlock: [:node | ((node isKindOf: MessageNode)
>                     and: [node selector key = #to:do:
>                     and: [node receiver isLiteralNode not
>                     and: [node arguments first isLiteralNode not]]])
>                 ifTrue: [found := node]]).
>         found notNil])
>     name: 'complex senders of to:do:'
>     autoSelect: true.
>
> Above script did not find any complex senders though I see some, so I must have screwed something, but you get the idea.
>
> Then there is the case of to:by:do: to analyze too.
>
>
> Ah, my script failed because to:do: is transformed at this stage (disguised in #to:by:do:)...
>
> SystemNavigation default
>     browseMessageList: ((SystemNavigation default allCallsOn: #to:do:) select: [:e |
>         | ast found |
>         ast := e actualClass newParser parse: e sourceCode class: e actualClass.
>         found := nil.
>         ast accept: (ParseNodeEnumerator
>             ofBlock: [:node | ((node isKindOf: MessageNode)
>                     and: [(node selector key = #to:do: or: [node selector key = #to:by:do: ])
>                     and: [node receiver isLiteralNode not
>                     and: [node arguments first isLiteralNode not]]])
>                 ifTrue: [found := node]]).
>         found notNil])
>     name: 'complex senders of to:do:'
>     autoSelect: #to:do:
>  
> But I can't test other trivial cases when node arguments first isVariableNode, because it allways is after transform.
> It would be necessary to disable transform during analysis...
>
>
> 2017-04-21 16:08 GMT+02:00 Bert Freudenberg <[hidden email]>:
>       On Fri, Apr 21, 2017 at 1:56 AM, Eliot Miranda <[hidden email]> wrote:
>             On the order of evaluation bug, does anyone have any memory of which methods depended on this bug?
>
>
> No idea ...
>
> - Bert -
>
>
>
>
>
>
>

Reply | Threaded
Open this post in threaded view
|

Re: Order of evaluation bug with in lined to:do: in both Opal and Squeak compilers.

Levente Uzonyi
Actually it's possible to have one variable and one non-literal
non-variable node where the latter changes the value of the former, so
the condition should be:

  (node isMessage
  and: [ (#(to:do: to:by:do:) includes: node selector key)
  and: [ node receiver isLiteralNode not
  and: [ node arguments first isLiteralNode not
  and: [ node receiver isVariableNode not
  or: [ node arguments first isVariableNode not ] ] ] ] ])

Levente

On Sat, 22 Apr 2017, Levente Uzonyi wrote:

> This seems to work:
>
> methods := (SystemNavigation default allCallsOn: #to:do:) asSet.
> methods addAll: (SystemNavigation default allCallsOn: #to:by:do:).
> methods := CurrentReadOnlySourceFiles cacheDuring: [
> methods select: [ :methodReference |
> | ast found |
> ast := methodReference actualClass newParser parse:
> methodReference sourceCode class: methodReference actualClass.
> found := nil.
> ast accept: (ParseNodeEnumerator ofBlock: [ :node |
> (node isMessage
> and: [ (#(to:do: to:by:do:) includes: node
> selector key)
> and: [ node receiver isLiteralNode not
> and: [ node receiver isVariableNode not
> and: [ node arguments first isLiteralNode not
> and: [ node arguments first isVariableNode
> not ] ] ] ] ])
> ifTrue: [ found := node ] ]).
> found notNil ] ].
> SystemNavigation default
> browseMessageList: methods sorted
> name: 'complex senders of to:do:'
> autoSelect: 'to:'.
>
> Levente
>
> On Sat, 22 Apr 2017, Nicolas Cellier wrote:
>
>>
>>
>> 2017-04-21 23:05 GMT+02:00 Nicolas Cellier
>> <[hidden email]>:
>>       I see more than 1000 senders but most of them are in the style 1 to:
>> ...
>> If any of receiver or 1st arg is a LiteralNode, no need to analyze, so it
>> should be possible to write a small analyzer to select non trivial cases
>> and review manually. Something like:
>>
>> SystemNavigation default
>>     browseMessageList: ((SystemNavigation default allCallsOn: #to:do:)
>> select: [:e |
>>         | ast found |
>>         ast := e actualClass newParser parse: e sourceCode class: e
>> actualClass.
>>         found := nil.
>>         ast accept: (ParseNodeEnumerator
>>             ofBlock: [:node | ((node isKindOf: MessageNode)
>>                     and: [node selector key = #to:do:
>>                     and: [node receiver isLiteralNode not
>>                     and: [node arguments first isLiteralNode not]]])
>>                 ifTrue: [found := node]]).
>>         found notNil])
>>     name: 'complex senders of to:do:'
>>     autoSelect: true.
>>
>> Above script did not find any complex senders though I see some, so I must
>> have screwed something, but you get the idea.
>>
>> Then there is the case of to:by:do: to analyze too.
>>
>>
>> Ah, my script failed because to:do: is transformed at this stage (disguised
>> in #to:by:do:)...
>>
>> SystemNavigation default
>>     browseMessageList: ((SystemNavigation default allCallsOn: #to:do:)
>> select: [:e |
>>         | ast found |
>>         ast := e actualClass newParser parse: e sourceCode class: e
>> actualClass.
>>         found := nil.
>>         ast accept: (ParseNodeEnumerator
>>             ofBlock: [:node | ((node isKindOf: MessageNode)
>>                     and: [(node selector key = #to:do: or: [node selector
>> key = #to:by:do: ])
>>                     and: [node receiver isLiteralNode not
>>                     and: [node arguments first isLiteralNode not]]])
>>                 ifTrue: [found := node]]).
>>         found notNil])
>>     name: 'complex senders of to:do:'
>>     autoSelect: #to:do:
>>  
>> But I can't test other trivial cases when node arguments first
>> isVariableNode, because it allways is after transform.
>> It would be necessary to disable transform during analysis...
>>
>>
>> 2017-04-21 16:08 GMT+02:00 Bert Freudenberg <[hidden email]>:
>>       On Fri, Apr 21, 2017 at 1:56 AM, Eliot Miranda
>> <[hidden email]> wrote:
>>             On the order of evaluation bug, does anyone have any memory of
>> which methods depended on this bug?
>>
>>
>> No idea ...
>>
>> - Bert -
>>
>>
>>
>>
>>
>>
>

Reply | Threaded
Open this post in threaded view
|

Re: Order of evaluation bug with in lined to:do: in both Opal and Squeak compilers.

Levente Uzonyi
I went through all those senders in my Trunk image and found that they
won't be affected by the change of evaluation order.

Levente

On Sat, 22 Apr 2017, Levente Uzonyi wrote:

> Actually it's possible to have one variable and one non-literal non-variable
> node where the latter changes the value of the former, so the condition
> should be:
>
> (node isMessage
> and: [ (#(to:do: to:by:do:) includes: node
> selector key)
> and: [ node receiver isLiteralNode not
> and: [ node arguments first isLiteralNode not
> and: [ node receiver isVariableNode not
> or: [ node arguments first
> isVariableNode not ] ] ] ] ])
>
> Levente
>
> On Sat, 22 Apr 2017, Levente Uzonyi wrote:
>
>> This seems to work:
>>
>> methods := (SystemNavigation default allCallsOn: #to:do:) asSet.
>> methods addAll: (SystemNavigation default allCallsOn: #to:by:do:).
>> methods := CurrentReadOnlySourceFiles cacheDuring: [
>> methods select: [ :methodReference |
>> | ast found |
>> ast := methodReference actualClass newParser parse:
>> methodReference sourceCode class: methodReference actualClass.
>> found := nil.
>> ast accept: (ParseNodeEnumerator ofBlock: [ :node |
>> (node isMessage
>> and: [ (#(to:do: to:by:do:) includes: node
>> selector key)
>> and: [ node receiver isLiteralNode not
>> and: [ node receiver isVariableNode not
>> and: [ node arguments first isLiteralNode not
>> and: [ node arguments first isVariableNode
>> not ] ] ] ] ])
>> ifTrue: [ found := node ] ]).
>> found notNil ] ].
>> SystemNavigation default
>> browseMessageList: methods sorted
>> name: 'complex senders of to:do:'
>> autoSelect: 'to:'.
>>
>> Levente
>>
>> On Sat, 22 Apr 2017, Nicolas Cellier wrote:
>>
>>>
>>>
>>> 2017-04-21 23:05 GMT+02:00 Nicolas Cellier
>>> <[hidden email]>:
>>>       I see more than 1000 senders but most of them are in the style 1 to:
>>> ...
>>> If any of receiver or 1st arg is a LiteralNode, no need to analyze, so it
>>> should be possible to write a small analyzer to select non trivial cases
>>> and review manually. Something like:
>>>
>>> SystemNavigation default
>>>     browseMessageList: ((SystemNavigation default allCallsOn: #to:do:)
>>> select: [:e |
>>>         | ast found |
>>>         ast := e actualClass newParser parse: e sourceCode class: e
>>> actualClass.
>>>         found := nil.
>>>         ast accept: (ParseNodeEnumerator
>>>             ofBlock: [:node | ((node isKindOf: MessageNode)
>>>                     and: [node selector key = #to:do:
>>>                     and: [node receiver isLiteralNode not
>>>                     and: [node arguments first isLiteralNode not]]])
>>>                 ifTrue: [found := node]]).
>>>         found notNil])
>>>     name: 'complex senders of to:do:'
>>>     autoSelect: true.
>>>
>>> Above script did not find any complex senders though I see some, so I must
>>> have screwed something, but you get the idea.
>>>
>>> Then there is the case of to:by:do: to analyze too.
>>>
>>>
>>> Ah, my script failed because to:do: is transformed at this stage
>>> (disguised in #to:by:do:)...
>>>
>>> SystemNavigation default
>>>     browseMessageList: ((SystemNavigation default allCallsOn: #to:do:)
>>> select: [:e |
>>>         | ast found |
>>>         ast := e actualClass newParser parse: e sourceCode class: e
>>> actualClass.
>>>         found := nil.
>>>         ast accept: (ParseNodeEnumerator
>>>             ofBlock: [:node | ((node isKindOf: MessageNode)
>>>                     and: [(node selector key = #to:do: or: [node selector
>>> key = #to:by:do: ])
>>>                     and: [node receiver isLiteralNode not
>>>                     and: [node arguments first isLiteralNode not]]])
>>>                 ifTrue: [found := node]]).
>>>         found notNil])
>>>     name: 'complex senders of to:do:'
>>>     autoSelect: #to:do:
>>>  
>>> But I can't test other trivial cases when node arguments first
>>> isVariableNode, because it allways is after transform.
>>> It would be necessary to disable transform during analysis...
>>>
>>>
>>> 2017-04-21 16:08 GMT+02:00 Bert Freudenberg <[hidden email]>:
>>>       On Fri, Apr 21, 2017 at 1:56 AM, Eliot Miranda
>>> <[hidden email]> wrote:
>>>             On the order of evaluation bug, does anyone have any memory of
>>> which methods depended on this bug?
>>>
>>>
>>> No idea ...
>>>
>>> - Bert -
>>>
>>>
>>>
>>>
>>>
>>>
>