Improving Variable Shadow model

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

Improving Variable Shadow model

Marcus Denker-4
The issue tracker entry "Rule required for shadowed variables" [#8009](https://github.com/pharo-project/pharo/issues/8009)

It reads:

___


In the CI output log for PRs on Pharo 9 issues I see the following warnings on Roassal classes:

SystemNotification: RSCanvas>>numberOfEdges(edges is shadowed)
SystemNotification: RSCanvas>>numberOfEdges(edges is shadowed)
SystemNotification: RSCanvas>>numberOfNodes(nodes is shadowed)
SystemNotification: RSCanvas>>numberOfNodes(nodes is shadowed)
SystemNotification: RSComposite>>numberOfEdges(edges is shadowed)
SystemNotification: RSComposite>>numberOfEdges(edges is shadowed)
SystemNotification: RSComposite>>numberOfNodes(nodes is shadowed)
SystemNotification: RSComposite>>numberOfNodes(nodes is shadowed)
SystemNotification: RSShape>>printOn:(model is shadowed)
SystemNotification: RSShape>>printOn:(model is shadowed)

which means we have local variables (or block variable) in a method with the same name as an existing ivar in the class.

These cases should be cleaned in Rossal3 for the Pharo 9 image - for that I opened https://github.com/ObjectProfile/Roassal3/issues/321 on Roassal3 issue tracker.

But it would be good if we could have a Lint rule that shows that problem so one can avoid it:

**Side note:** Yes - there already is a rule called ReTempVarOverridesInstVarRuleTest - but this is only for temps
                  and does not cover variables in blocks like in

```Smalltalk
numberOfEdges
        "Return the number of edges contained in the container"
        ^ self privateEdges
                ifNil: [ 0 ]
                ifNotNil: [ :edges | edges size ]
```
when "edges" is already an instance variable

___

So how is ReTempVarOverridesInstVarRuleTest implemented?

```Smalltalk
check: aMethod forCritiquesDo: aCriticBlock
        | ivarNames problemTemps|
        ivarNames := aMethod methodClass instVarNames.
        ivarNames ifEmpty: [ ^ self ].
       
        problemTemps := ((aMethod ast arguments, aMethod ast temporaries)
                select: [ :node |ivarNames includes: node name]).
        problemTemps do: [ :node |
                aCriticBlock cull: (self critiqueFor: aMethod about: node) ]
```

So, this test is done purely on the results of the compilation, it just checks if temps are overriding the instance vars.
It just does not care about blocks, nor class variables or globals.

We could now, for this issue, recurse into the compiled block closures, but that would make the code quite complex.

To see a better solution, let's check who actually prints out the log message in the build. Just searching for a substring will
lead us to OCShadowVariableWarning>>#variable:shadows:

```Smalltalk
variable: varNode shadows: semVar
        compilationContext interactive
                ifTrue: [
                        OCSemanticError new
                                node: node;
                                compilationContext: compilationContext;
                                messageText: self stringMessage;
                                signal ]
                ifFalse: [ self showWarningOnTranscript ].
               
```

This is an exception raised by the AST visitor that does name analysis, OCASTSemanticAnalyzer:

```Smalltalk
variable: variableNode shadows: semVar
        compilationContext optionSkipSemanticWarnings ifTrue: [ ^semVar ].
        ^ OCShadowVariableWarning new
                node: variableNode;
                shadowedVar: semVar;
                compilationContext: compilationContext;
                signal
```

This method is called whever we lookup a Variable name to create a Variable object describing it:

```Smalltalk
declareVariableNode: aVariableNode as: anOCTempVariable
        | name var |
        name := aVariableNode name.
        var := scope lookupVarForDeclaration: name.
        var ifNotNil: [
                "Another variable with same name is visible from current scope.
                Warn about the name clash and if proceed add new temp to shadow existing var"
                self variable: aVariableNode shadows: var ].
        var := scope addTemp: anOCTempVariable.
        aVariableNode binding: var.
        ^ var
```

This means: in non-interactive mode, we just log the error and compile while allowing shadowing. In interactive mode
we forbid it (we raise a OCSemanticError exception that will be displayed in the code editor).

What could we now do to improve the model of shadowing variables? The best thing would be if we could add the fact that
 a variable shadows another to the semantic information. That is, it should be modeled as part of the variable.

We do not need much: just add this information as a property would be perfectly enough. This way we can add a test method
(that check if the property exists). On the level of the Code Critique rule it will be very simple: just get all variables
that are defined (args, temps, args of blocks) and check if they are shadowing. That's easy!

So what is needed to implement it?

We first need to make sure we hand over one more parameter to #variable:shadows: and call it later: right now, in
interactive mode, we never create a Variable at all. There is no problem to delay that and tag the variable correctly:

```Smalltalk
variable: aVariable shadows: shadowedVariable inNode: variableNode
        aVariable shadowing: shadowedVariable.
        compilationContext optionSkipSemanticWarnings ifTrue: [ ^aVariable ].
        ^ OCShadowVariableWarning new
                node: variableNode;
                shadowedVar: aVariable;
                compilationContext: compilationContext;
                signal
```

with:

```Smalltalk
declareVariableNode: aVariableNode as: anOCTempVariable
        | name var shadowed |
        name := aVariableNode name.
        var := scope lookupVarForDeclaration: name.
        var ifNotNil: [
                "Another variable with same name is visible from current scope"
                shadowed := var.
                ].
        var := scope addTemp: anOCTempVariable.
        aVariableNode binding: var.
        shadowed ifNotNil: [self variable: var shadows: shadowed inNode: aVariableNode].
        ^ var
```


To be able to tag Variables, we implement


```Smalltalk
shadowing: anotherVariable
        self propertyAt: #shadows put: anotherVariable
```

and

```Smalltalk
"testing"
isShadowing
        ^self hasProperty: #shadows
```

We do this on Variables, which means that we can later introduce Variable shadow tagging even for instance variables and Class Variables

How do we now test this?

One idea is to rewrite ReTempVarOverridesInstVarRule>>#check:forCritiquesDo: to use #isShadowing. ReTempVarOverridesInstVarRuleTest
is green, we have something that is reado to commit.

Let's try

```Smalltalk
check: aMethod forCritiquesDo: aCriticBlock

        | problemTemps |
        problemTemps := aMethod temporaryVariables select: [ :var |
                                var isShadowing ].
        problemTemps do: [ :var |
                aCriticBlock cull:
                        (self critiqueFor: aMethod about: var definingNode) ]
```

And: Success! This is now a first PR to be done [see here](https://github.com/pharo-project/pharo/pull/8909).

This does not yet provide the Rule and the Release Test for shadowing vars in general, but it is a very nice first step that we can build upon next.
Reply | Threaded
Open this post in threaded view
|

Re: Improving Variable Shadow model

Marcus Denker-4
We merged this and did the next step:

        8009-Rule-required-for-shadowed-variables #8917
                https://github.com/pharo-project/pharo/pull/8917

Thus the Code critique now correctly shows shadowed variables even for the case where the argument of a closure
shadows an other variables.

        • The rule of course can now be further improved to exactly tell the user what is shadowed
        • We should add a rule that checks of instance or class vars shadow globals (which needs further refinement on the shadow model)
        • We should add a release test to make sure we have no shadowed vars in the system
                — both on the level of methods and on the level of Classes

but that is for the future


> On 29 Mar 2021, at 16:26, Marcus Denker <[hidden email]> wrote:
>
> The issue tracker entry "Rule required for shadowed variables" [#8009](https://github.com/pharo-project/pharo/issues/8009)
>
> It reads:
>
> ___
>
>
> In the CI output log for PRs on Pharo 9 issues I see the following warnings on Roassal classes:
>
> SystemNotification: RSCanvas>>numberOfEdges(edges is shadowed)
> SystemNotification: RSCanvas>>numberOfEdges(edges is shadowed)
> SystemNotification: RSCanvas>>numberOfNodes(nodes is shadowed)
> SystemNotification: RSCanvas>>numberOfNodes(nodes is shadowed)
> SystemNotification: RSComposite>>numberOfEdges(edges is shadowed)
> SystemNotification: RSComposite>>numberOfEdges(edges is shadowed)
> SystemNotification: RSComposite>>numberOfNodes(nodes is shadowed)
> SystemNotification: RSComposite>>numberOfNodes(nodes is shadowed)
> SystemNotification: RSShape>>printOn:(model is shadowed)
> SystemNotification: RSShape>>printOn:(model is shadowed)
>
> which means we have local variables (or block variable) in a method with the same name as an existing ivar in the class.
>
> These cases should be cleaned in Rossal3 for the Pharo 9 image - for that I opened https://github.com/ObjectProfile/Roassal3/issues/321 on Roassal3 issue tracker.
>
> But it would be good if we could have a Lint rule that shows that problem so one can avoid it:
>
> **Side note:** Yes - there already is a rule called ReTempVarOverridesInstVarRuleTest - but this is only for temps
>                  and does not cover variables in blocks like in
>
> ```Smalltalk
> numberOfEdges
> "Return the number of edges contained in the container"
> ^ self privateEdges
> ifNil: [ 0 ]
> ifNotNil: [ :edges | edges size ]
> ```
> when "edges" is already an instance variable
>
> ___
>
> So how is ReTempVarOverridesInstVarRuleTest implemented?
>
> ```Smalltalk
> check: aMethod forCritiquesDo: aCriticBlock
> | ivarNames problemTemps|
> ivarNames := aMethod methodClass instVarNames.
> ivarNames ifEmpty: [ ^ self ].
>
> problemTemps := ((aMethod ast arguments, aMethod ast temporaries)
> select: [ :node |ivarNames includes: node name]).
> problemTemps do: [ :node |
> aCriticBlock cull: (self critiqueFor: aMethod about: node) ]
> ```
>
> So, this test is done purely on the results of the compilation, it just checks if temps are overriding the instance vars.
> It just does not care about blocks, nor class variables or globals.
>
> We could now, for this issue, recurse into the compiled block closures, but that would make the code quite complex.
>
> To see a better solution, let's check who actually prints out the log message in the build. Just searching for a substring will
> lead us to OCShadowVariableWarning>>#variable:shadows:
>
> ```Smalltalk
> variable: varNode shadows: semVar
> compilationContext interactive
> ifTrue: [
> OCSemanticError new
> node: node;
> compilationContext: compilationContext;
> messageText: self stringMessage;
> signal ]
> ifFalse: [ self showWarningOnTranscript ].
>
> ```
>
> This is an exception raised by the AST visitor that does name analysis, OCASTSemanticAnalyzer:
>
> ```Smalltalk
> variable: variableNode shadows: semVar
> compilationContext optionSkipSemanticWarnings ifTrue: [ ^semVar ].
> ^ OCShadowVariableWarning new
> node: variableNode;
> shadowedVar: semVar;
> compilationContext: compilationContext;
> signal
> ```
>
> This method is called whever we lookup a Variable name to create a Variable object describing it:
>
> ```Smalltalk
> declareVariableNode: aVariableNode as: anOCTempVariable
> | name var |
> name := aVariableNode name.
> var := scope lookupVarForDeclaration: name.
> var ifNotNil: [
> "Another variable with same name is visible from current scope.
> Warn about the name clash and if proceed add new temp to shadow existing var"
> self variable: aVariableNode shadows: var ].
> var := scope addTemp: anOCTempVariable.
> aVariableNode binding: var.
> ^ var
> ```
>
> This means: in non-interactive mode, we just log the error and compile while allowing shadowing. In interactive mode
> we forbid it (we raise a OCSemanticError exception that will be displayed in the code editor).
>
> What could we now do to improve the model of shadowing variables? The best thing would be if we could add the fact that
> a variable shadows another to the semantic information. That is, it should be modeled as part of the variable.
>
> We do not need much: just add this information as a property would be perfectly enough. This way we can add a test method
> (that check if the property exists). On the level of the Code Critique rule it will be very simple: just get all variables
> that are defined (args, temps, args of blocks) and check if they are shadowing. That's easy!
>
> So what is needed to implement it?
>
> We first need to make sure we hand over one more parameter to #variable:shadows: and call it later: right now, in
> interactive mode, we never create a Variable at all. There is no problem to delay that and tag the variable correctly:
>
> ```Smalltalk
> variable: aVariable shadows: shadowedVariable inNode: variableNode
> aVariable shadowing: shadowedVariable.
> compilationContext optionSkipSemanticWarnings ifTrue: [ ^aVariable ].
> ^ OCShadowVariableWarning new
> node: variableNode;
> shadowedVar: aVariable;
> compilationContext: compilationContext;
> signal
> ```
>
> with:
>
> ```Smalltalk
> declareVariableNode: aVariableNode as: anOCTempVariable
> | name var shadowed |
> name := aVariableNode name.
> var := scope lookupVarForDeclaration: name.
> var ifNotNil: [
> "Another variable with same name is visible from current scope"
> shadowed := var.
> ].
> var := scope addTemp: anOCTempVariable.
> aVariableNode binding: var.
> shadowed ifNotNil: [self variable: var shadows: shadowed inNode: aVariableNode].
> ^ var
> ```
>
>
> To be able to tag Variables, we implement
>
>
> ```Smalltalk
> shadowing: anotherVariable
> self propertyAt: #shadows put: anotherVariable
> ```
>
> and
>
> ```Smalltalk
> "testing"
> isShadowing
> ^self hasProperty: #shadows
> ```
>
> We do this on Variables, which means that we can later introduce Variable shadow tagging even for instance variables and Class Variables
>
> How do we now test this?
>
> One idea is to rewrite ReTempVarOverridesInstVarRule>>#check:forCritiquesDo: to use #isShadowing. ReTempVarOverridesInstVarRuleTest
> is green, we have something that is reado to commit.
>
> Let's try
>
> ```Smalltalk
> check: aMethod forCritiquesDo: aCriticBlock
>
> | problemTemps |
> problemTemps := aMethod temporaryVariables select: [ :var |
>                var isShadowing ].
> problemTemps do: [ :var |
> aCriticBlock cull:
> (self critiqueFor: aMethod about: var definingNode) ]
> ```
>
> And: Success! This is now a first PR to be done [see here](https://github.com/pharo-project/pharo/pull/8909).
>
> This does not yet provide the Rule and the Release Test for shadowing vars in general, but it is a very nice first step that we can build upon next.
>
Reply | Threaded
Open this post in threaded view
|

Re: Improving Variable Shadow model

Marcus Denker-4
# Adding a Release Test

This whole exploration of Variable Shadowing started with a bug report. It would be nice to never have cases
of shadowed variables. To make sure we never introduce them again, we can add a test to the ReleaseTest package.

Just looking a bit at other tests checking something for each method and starting with it as a template,
we can easily now implement #testNoShadowedVariablesInMethods:

```Smalltalk
testNoShadowedVariablesInMethods
        "Fail if there are methods who define shadowed temps or args"
        | found validExceptions remaining |
        found := SystemNavigation default allMethodsSelect: [ :m |
                m ast variableDefinitionNodes anySatisfy: [ :node | node variable isShadowing ] ].
       
        "No other exceptions beside the ones mentioned here should be allowed"
        validExceptions := {
                RBDummyRefactoryTestDataApp>>#tempVarOverridesInstVar.
                RBRefactoryTestDataApp>>#tempVarOverridesInstVar.
                RBSmalllintTestObject>>#tempVarOverridesInstVar.
                ReTempVarOverridesInstVarRuleTest>>#sampleMethod:}.
       
        remaining := found asOrderedCollection
                                                                removeAll: validExceptions;
                                                                yourself.
                                                               
        self
                assert: remaining isEmpty
                description: ('the following methods have shadowing variable definitions and should be cleaned: ', remaining asString)
```

Of course I first ran with empty validExceptions, then I added all as these methods are examples from tests that test handling
of variable shadowing.The test is green! PR: https://github.com/pharo-project/pharo/pull/8927

# Shadowed Variables on the level of the class

We should think about Shadowed Variables on the level of a class

Classes define instance variables (modeled by sub-instances of Slot) and Class Variables (sub-instances of ClassVariable). They can shadow variables from the environment that the class is in (in the usual case this is Smalltalk Globals).

We should extend the concept of Shadowed variables to cover these cases, too.

Imagine we have a class that has a class variable "Person". Then we add a class named "Person": The class variable is now shadowing the class. #isShadowing for now is just checking for the property. But here we run into a problem: who could set the property? The classbuilder could do it. But adding a class would mean that we would need to check all existing classes if the new global is shadowed somewhere.

And we would not just have to check the classes: nothing forbids us to use a block argument "Person"... (even though bad style). Thus we would need to re-analyse all code globally. Not a good idea in a system where a user might have >100K classes...

Thus: we need to rethink our solution. It was not wrong: we were concened with just modeling shadowing for methods, the solution to tag the variables was a good one for that use. But now we need to step back. What is shadowing again? It means that the outer scope of a variable has  already a variable of the same name.

Interestingly, the variable model is already modeling all the needed information. Variables have a scope, the scope has a perent scope.
We can lookup vars by name with #lookupVar. We can just change  #isShadowing to implement exactly "I shadow a variable if looking up my name in my outer scope returns a variable".

```Smalltalk
isShadowing
        "I shadow a variable if looking up my name in the outer scope returns a variable"
        ^(self scope outerScope ifNotNil: [:outer | outer lookupVar: self name]) notNil
```

We just have to add a missing #outerScope method to Behavior (as the outer scope is called the "environment" here), and one to SystemDictonary returning nil.
And it works! The tests we did for shadowing are still green.

Pull request is here: https://github.com/pharo-project/pharo/pull/8931

With this in place, we can add a new Critique Rule. But that is for next time.


# TODO NEXT

        • We should add a rule that checks of instance or class vars shadow globals
        • We should add a release test to make sure we have no shadowed vars on the class level in the system
        • All the rules should be further improved to exactly tell the user what is shadowed where, to make it easy to fix
       



> On 30 Mar 2021, at 18:18, Marcus Denker <[hidden email]> wrote:
>
> We merged this and did the next step:
>
> 8009-Rule-required-for-shadowed-variables #8917
> https://github.com/pharo-project/pharo/pull/8917
>
> Thus the Code critique now correctly shows shadowed variables even for the case where the argument of a closure
> shadows an other variables.
>
> • The rule of course can now be further improved to exactly tell the user what is shadowed
> • We should add a rule that checks of instance or class vars shadow globals (which needs further refinement on the shadow model)
> • We should add a release test to make sure we have no shadowed vars in the system
> — both on the level of methods and on the level of Classes
>
> but that is for the future
>
>
>> On 29 Mar 2021, at 16:26, Marcus Denker <[hidden email]> wrote:
>>
>> The issue tracker entry "Rule required for shadowed variables" [#8009](https://github.com/pharo-project/pharo/issues/8009)
>>
>> It reads:
>>
>> ___
>>
>>
>> In the CI output log for PRs on Pharo 9 issues I see the following warnings on Roassal classes:
>>
>> SystemNotification: RSCanvas>>numberOfEdges(edges is shadowed)
>> SystemNotification: RSCanvas>>numberOfEdges(edges is shadowed)
>> SystemNotification: RSCanvas>>numberOfNodes(nodes is shadowed)
>> SystemNotification: RSCanvas>>numberOfNodes(nodes is shadowed)
>> SystemNotification: RSComposite>>numberOfEdges(edges is shadowed)
>> SystemNotification: RSComposite>>numberOfEdges(edges is shadowed)
>> SystemNotification: RSComposite>>numberOfNodes(nodes is shadowed)
>> SystemNotification: RSComposite>>numberOfNodes(nodes is shadowed)
>> SystemNotification: RSShape>>printOn:(model is shadowed)
>> SystemNotification: RSShape>>printOn:(model is shadowed)
>>
>> which means we have local variables (or block variable) in a method with the same name as an existing ivar in the class.
>>
>> These cases should be cleaned in Rossal3 for the Pharo 9 image - for that I opened https://github.com/ObjectProfile/Roassal3/issues/321 on Roassal3 issue tracker.
>>
>> But it would be good if we could have a Lint rule that shows that problem so one can avoid it:
>>
>> **Side note:** Yes - there already is a rule called ReTempVarOverridesInstVarRuleTest - but this is only for temps
>>                 and does not cover variables in blocks like in
>>
>> ```Smalltalk
>> numberOfEdges
>> "Return the number of edges contained in the container"
>> ^ self privateEdges
>> ifNil: [ 0 ]
>> ifNotNil: [ :edges | edges size ]
>> ```
>> when "edges" is already an instance variable
>>
>> ___
>>
>> So how is ReTempVarOverridesInstVarRuleTest implemented?
>>
>> ```Smalltalk
>> check: aMethod forCritiquesDo: aCriticBlock
>> | ivarNames problemTemps|
>> ivarNames := aMethod methodClass instVarNames.
>> ivarNames ifEmpty: [ ^ self ].
>>
>> problemTemps := ((aMethod ast arguments, aMethod ast temporaries)
>> select: [ :node |ivarNames includes: node name]).
>> problemTemps do: [ :node |
>> aCriticBlock cull: (self critiqueFor: aMethod about: node) ]
>> ```
>>
>> So, this test is done purely on the results of the compilation, it just checks if temps are overriding the instance vars.
>> It just does not care about blocks, nor class variables or globals.
>>
>> We could now, for this issue, recurse into the compiled block closures, but that would make the code quite complex.
>>
>> To see a better solution, let's check who actually prints out the log message in the build. Just searching for a substring will
>> lead us to OCShadowVariableWarning>>#variable:shadows:
>>
>> ```Smalltalk
>> variable: varNode shadows: semVar
>> compilationContext interactive
>> ifTrue: [
>> OCSemanticError new
>> node: node;
>> compilationContext: compilationContext;
>> messageText: self stringMessage;
>> signal ]
>> ifFalse: [ self showWarningOnTranscript ].
>>
>> ```
>>
>> This is an exception raised by the AST visitor that does name analysis, OCASTSemanticAnalyzer:
>>
>> ```Smalltalk
>> variable: variableNode shadows: semVar
>> compilationContext optionSkipSemanticWarnings ifTrue: [ ^semVar ].
>> ^ OCShadowVariableWarning new
>> node: variableNode;
>> shadowedVar: semVar;
>> compilationContext: compilationContext;
>> signal
>> ```
>>
>> This method is called whever we lookup a Variable name to create a Variable object describing it:
>>
>> ```Smalltalk
>> declareVariableNode: aVariableNode as: anOCTempVariable
>> | name var |
>> name := aVariableNode name.
>> var := scope lookupVarForDeclaration: name.
>> var ifNotNil: [
>> "Another variable with same name is visible from current scope.
>> Warn about the name clash and if proceed add new temp to shadow existing var"
>> self variable: aVariableNode shadows: var ].
>> var := scope addTemp: anOCTempVariable.
>> aVariableNode binding: var.
>> ^ var
>> ```
>>
>> This means: in non-interactive mode, we just log the error and compile while allowing shadowing. In interactive mode
>> we forbid it (we raise a OCSemanticError exception that will be displayed in the code editor).
>>
>> What could we now do to improve the model of shadowing variables? The best thing would be if we could add the fact that
>> a variable shadows another to the semantic information. That is, it should be modeled as part of the variable.
>>
>> We do not need much: just add this information as a property would be perfectly enough. This way we can add a test method
>> (that check if the property exists). On the level of the Code Critique rule it will be very simple: just get all variables
>> that are defined (args, temps, args of blocks) and check if they are shadowing. That's easy!
>>
>> So what is needed to implement it?
>>
>> We first need to make sure we hand over one more parameter to #variable:shadows: and call it later: right now, in
>> interactive mode, we never create a Variable at all. There is no problem to delay that and tag the variable correctly:
>>
>> ```Smalltalk
>> variable: aVariable shadows: shadowedVariable inNode: variableNode
>> aVariable shadowing: shadowedVariable.
>> compilationContext optionSkipSemanticWarnings ifTrue: [ ^aVariable ].
>> ^ OCShadowVariableWarning new
>> node: variableNode;
>> shadowedVar: aVariable;
>> compilationContext: compilationContext;
>> signal
>> ```
>>
>> with:
>>
>> ```Smalltalk
>> declareVariableNode: aVariableNode as: anOCTempVariable
>> | name var shadowed |
>> name := aVariableNode name.
>> var := scope lookupVarForDeclaration: name.
>> var ifNotNil: [
>> "Another variable with same name is visible from current scope"
>> shadowed := var.
>> ].
>> var := scope addTemp: anOCTempVariable.
>> aVariableNode binding: var.
>> shadowed ifNotNil: [self variable: var shadows: shadowed inNode: aVariableNode].
>> ^ var
>> ```
>>
>>
>> To be able to tag Variables, we implement
>>
>>
>> ```Smalltalk
>> shadowing: anotherVariable
>> self propertyAt: #shadows put: anotherVariable
>> ```
>>
>> and
>>
>> ```Smalltalk
>> "testing"
>> isShadowing
>> ^self hasProperty: #shadows
>> ```
>>
>> We do this on Variables, which means that we can later introduce Variable shadow tagging even for instance variables and Class Variables
>>
>> How do we now test this?
>>
>> One idea is to rewrite ReTempVarOverridesInstVarRule>>#check:forCritiquesDo: to use #isShadowing. ReTempVarOverridesInstVarRuleTest
>> is green, we have something that is reado to commit.
>>
>> Let's try
>>
>> ```Smalltalk
>> check: aMethod forCritiquesDo: aCriticBlock
>>
>> | problemTemps |
>> problemTemps := aMethod temporaryVariables select: [ :var |
>>                var isShadowing ].
>> problemTemps do: [ :var |
>> aCriticBlock cull:
>> (self critiqueFor: aMethod about: var definingNode) ]
>> ```
>>
>> And: Success! This is now a first PR to be done [see here](https://github.com/pharo-project/pharo/pull/8909).
>>
>> This does not yet provide the Rule and the Release Test for shadowing vars in general, but it is a very nice first step that we can build upon next.
>>
>
Reply | Threaded
Open this post in threaded view
|

Re: Improving Variable Shadow model

Marcus Denker-4

# Adding a Release test to check for shadowed vars defined at the level of a class

Imagine we make a class like this:

Object subclass: #MyClass
        instanceVariableNames: 'Array i'
        classVariableNames: 'Object'
        package: 'MyPackage'
       

We can ask the class for all the variables it defines with #definedVariables. Thus is is easy to filter
for the shadowing variables:

```Smalltalk
MyClass definedVariables select: [ :variable | variable isShadowing  ]

"{#Array => InstanceVariableSlot. #Object->nil}"
```

With this, we now can easily scan the whole system for problematic classes:

```Smalltalk
Smalltalk globals allBehaviors select: [ :class |
                class definedVariables anySatisfy: [:var | var isShadowing]].
```

And interestingly, this returns results! Of course, our class MyClass as defined above, but in addition we do have 6 classes
where class variables shadow globals. We should fix them at some point.

For now, we can add a release test that ensures that we do not add more cases:

```Smalltalk


testClassesShadow
        |  classes validExceptions remaining |

        classes := Smalltalk globals allBehaviors select: [ :class |
                class definedVariables anySatisfy: [:var | var isShadowing]].

        validExceptions := #().
       
        remaining := classes asOrderedCollection reject: [ :each  | validExceptions includes: each name].
        "6 left that we need to fix"
        self assert: remaining size <= 6.
```

What we need next is a Code Critique rule. This for once warns developers early, but in addition it will
make it much easier to fix the 6 problem cases seen above.
Reply | Threaded
Open this post in threaded view
|

Re: Improving Variable Shadow model

Marcus Denker-4


# Code Critique

What we need next is a Code Critique rule. This for once warns developers early, but in addition it will
make it much easier to fix the 6 problem cases that the release test exposed.

Checking for current senders of #definedVariables leads us to ReVariableAssignedLiteralRule, we can use this as a template.
The main method doing the check looks like this:

```Smalltalk
check: aClass forCritiquesDo: aCriticBlock

aClass definedVariables do: [ :variable | 
variable isShadowing  ifTrue: [ 
aCriticBlock cull: (self critiqueFor: aClass about: variable name) ] ]
```



Reply | Threaded
Open this post in threaded view
|

Re: Improving Variable Shadow model

Sean P. DeNigris
Administrator
Thanks for the detailed writeup, Marcus. Very interesting and looks like good
work :)



-----
Cheers,
Sean
--
Sent from: http://forum.world.st/Pharo-Smalltalk-Developers-f1294837.html
Cheers,
Sean
Reply | Threaded
Open this post in threaded view
|

Re: Improving Variable Shadow model

Marcus Denker-4


On 5 Apr 2021, at 17:03, Sean P. DeNigris <[hidden email]> wrote:

Thanks for the detailed writeup, Marcus. Very interesting and looks like good
work :)



I am trying to do that more regularly. We will see when I will run out if steam ;-)



And cross posting from forum.world.st is working! But I guess only for people who are 
subscribed to the list, too? (or at least how “post is ok for his From address” configured in some
way).
Reply | Threaded
Open this post in threaded view
|

Re: Improving Variable Shadow model

Marcus Denker-4
In reply to this post by Marcus Denker-4
Just a status update: we merged all the code.

- we now have for both the class and method view a Critique rule that warns you if you use shadowing vars.

- Pavel fixed all the cases of shadowing class variables. Thanks!

- release tests are active, #testNoShadowedVariablesInMethods fo methods  and at the class level:


testClassesShadow

| classes |
classes := Smalltalk globals allBehaviors select: [ :class | 
          class definedVariables anySatisfy: [ :var | 
          var isShadowing ] ].

self assert: classes isEmpty description: classes asArray asString


status cleanups: 

- DONE: Shadowed vars (as we saw)
=> TODO: combine the snippets of writing into one blog post for the devblog
- DONE: unused Class Variables
- ongoing: unused ivars. Just some left in Spec+Newtools (and one in Kernel tests)
- ongoing: all methods should be categorized. 
- todo: we should have no method that is the same as a method in a superclass


On 2 Apr 2021, at 15:33, Marcus Denker <[hidden email]> wrote:



# Code Critique

What we need next is a Code Critique rule. This for once warns developers early, but in addition it will
make it much easier to fix the 6 problem cases that the release test exposed.

Checking for current senders of #definedVariables leads us to ReVariableAssignedLiteralRule, we can use this as a template.
The main method doing the check looks like this:

```Smalltalk
check: aClass forCritiquesDo: aCriticBlock

aClass definedVariables do: [ :variable | 
variable isShadowing  ifTrue: [ 
aCriticBlock cull: (self critiqueFor: aClass about: variable name) ] ]
```




Reply | Threaded
Open this post in threaded view
|

Re: Improving Variable Shadow model

Noury Bouraqadi-2
Thanks Marcus

On Apr 14 2021, at 10:53 am, Marcus Denker <[hidden email]> wrote:
Just a status update: we merged all the code.

- we now have for both the class and method view a Critique rule that warns you if you use shadowing vars.

- Pavel fixed all the cases of shadowing class variables. Thanks!

- release tests are active, #testNoShadowedVariablesInMethods fo methods  and at the class level:


testClassesShadow

| classes |
classes := Smalltalk globals allBehaviors select: [ :class | 
          class definedVariables anySatisfy: [ :var | 
          var isShadowing ] ].

self assert: classes isEmpty description: classes asArray asString


status cleanups: 

- DONE: Shadowed vars (as we saw)
=> TODO: combine the snippets of writing into one blog post for the devblog
- DONE: unused Class Variables
- ongoing: unused ivars. Just some left in Spec+Newtools (and one in Kernel tests)
- ongoing: all methods should be categorized. 
- todo: we should have no method that is the same as a method in a superclass


On 2 Apr 2021, at 15:33, Marcus Denker <[hidden email]> wrote:



# Code Critique

What we need next is a Code Critique rule. This for once warns developers early, but in addition it will
make it much easier to fix the 6 problem cases that the release test exposed.

Checking for current senders of #definedVariables leads us to ReVariableAssignedLiteralRule, we can use this as a template.
The main method doing the check looks like this:

```Smalltalk
check: aClass forCritiquesDo: aCriticBlock

aClass definedVariables do: [ :variable | 
variable isShadowing  ifTrue: [ 
aCriticBlock cull: (self critiqueFor: aClass about: variable name) ] ]
```