Small Suggestion: Distinguishing Inherited Variables from Class Variables

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

Small Suggestion: Distinguishing Inherited Variables from Class Variables

Eric Taylor
Hello Forum,

In working with the Variables pane in the System Browser, it would be
nice to be able to distinguish inherited variables from those that
belong to the class.  The tooltips are helpful, but one has to go down
the list and hover over each one.

Nothing fancy, but perhaps a two-node tree: "Inherited variables",
"Class variables"; or maybe just a different icon, such as the normal
icon with a superimposed "h" to match the inheritance toggle button that
applies to methods.

Just a thought...

Cheers,

Eric


Reply | Threaded
Open this post in threaded view
|

Re: Small Suggestion: Distinguishing Inherited Variables from Class Variables

Ian Bartholomew-21
Eric,

> In working with the Variables pane in the System Browser, it would be
> nice to be able to distinguish inherited variables from those that
> belong to the class.

I'm not sure how useful it would be (to me anyway) but thanks to the wonder
that is Smalltalk the following _nearly_ does what you want.

Copy the section between the delimiters, save in a file and then "File in"
to your Dolphin image.  When a class is selected the variables defined in
that class are shown in bold, inherited variables in normal text.  The same
goes for class instance variables when the class tab is selected.

I say _nearly_ works because there is a problem with refreshing.  If you
change a class and the contents of the variable list does not change the the
view, and hence the emboldening, is not refreshed - you have to select the
protocols tab (for example) and then go back to the variables tab to refresh
the view.   It might be a bit fiddly to get round so I'll have a look later
(the postman just delivered the new Angie Palmer CD and I want to have a
listen :-) ),

NB. Patch tested for 2 minutes so there could be one or more nasties
lurking - don't save in your bestest image.

=============

!ClassBrowserAbstract methodsFor!

customDrawVariables: aNMLVCUSTOMDRAW
 | variable |
 variable := aNMLVCUSTOMDRAW item.
 variable isNil ifTrue: [^self].
 self
  emphasiseVariableItem: aNMLVCUSTOMDRAW
  isRelevant: (classesPresenter actualClass instVarNames includes: variable
value)! !
!ClassBrowserAbstract categoriesFor: #customDrawVariables:!helpers!private!
!

!ClassBrowserAbstract methodsFor!

emphasiseVariableItem: anNMTVCUSTOMDRAW isRelevant: aBoolean
 anNMTVCUSTOMDRAW font isBold: aBoolean! !
!ClassBrowserAbstract categoriesFor:
#emphasiseVariableItem:isRelevant:!helpers!private! !

| viewComposer subView |
viewComposer := ViewComposer show: 'Vertical view'.
viewComposer openOn: (ResourceIdentifier class: ClassBrowserShell name:
'Default view').
subView:= viewComposer composingView viewNamed: 'variables'.
subView customDrawBlock: [:ctx | ctx view presenter parentPresenter
customDrawVariables: ctx].
viewComposer fileSave.
viewComposer openOn: (ResourceIdentifier class: SystemBrowserShell name:
'Default view').
subView:= viewComposer composingView viewNamed: 'variables'.
subView customDrawBlock: [:ctx | ctx view presenter parentPresenter
customDrawVariables: ctx].
viewComposer fileSave.
viewComposer exit

=============

--
Ian

Use the Reply-To address to contact me (limited validity).
Mail sent to the From address is ignored.


Reply | Threaded
Open this post in threaded view
|

Re: Small Suggestion: Distinguishing Inherited Variables from Class Variables

Ian Bartholomew-21
In reply to this post by Eric Taylor
OK, I've included a revised script below.  This fixes the refresh problem
and also adds the update to the ExecutableBrowser.

When making changes to the image, like this, it is best to do it as
transparently as possible and avoid modifying any existing methods.  This
often results in code that is not as efficient or aesthetically pleasing
(very important!) as it would otherwise be.  The way I've got around the
refresh problem in this script is a good example :-)

==========
!ClassBrowserAbstract methodsFor!
customDrawVariables: aNMLVCUSTOMDRAW
 | variable |
 variable := aNMLVCUSTOMDRAW item.
 variable isNil ifTrue: [^self].
 self
  emphasiseVariableItem: aNMLVCUSTOMDRAW
  isRelevant: (classesPresenter actualClass instVarNames includes: variable
value)! !
!ClassBrowserAbstract categoriesFor: #customDrawVariables:!helpers!private!
!

!ClassBrowserAbstract methodsFor!
emphasiseVariableItem: anNMTVCUSTOMDRAW isRelevant: aBoolean
 anNMTVCUSTOMDRAW font isBold: aBoolean! !
!ClassBrowserAbstract categoriesFor:
#emphasiseVariableItem:isRelevant:!helpers!private! !

!ClassBrowserShell methodsFor!
updateVariables
 variablesPresenter model list: variablesPresenter model list , String new.
 ^super updateVariables! !
!ClassBrowserShell categoriesFor: #updateVariables!public! !

!EnvironmentBrowserShell methodsFor!
updateVariables
 variablesPresenter model list: variablesPresenter model list , String new.
 ^super updateVariables! !
!EnvironmentBrowserShell categoriesFor: #updateVariables!public! !

!SystemBrowserShell methodsFor!
updateVariables
 variablesPresenter model list: variablesPresenter model list , String new.
 ^super updateVariables! !
!SystemBrowserShell categoriesFor: #updateVariables!public! !

| viewComposer subView |
viewComposer := ViewComposer show: 'Vertical view'.
viewComposer openOn: (ResourceIdentifier class: ClassBrowserShell name:
'Default view').
subView:= viewComposer composingView viewNamed: 'variables'.
subView customDrawBlock: [:ctx | ctx view presenter parentPresenter
customDrawVariables: ctx].
viewComposer fileSave.
viewComposer openOn: (ResourceIdentifier class: SystemBrowserShell name:
'Default view').
subView:= viewComposer composingView viewNamed: 'variables'.
subView customDrawBlock: [:ctx | ctx view presenter parentPresenter
customDrawVariables: ctx].
viewComposer fileSave.
viewComposer openOn: (ResourceIdentifier class: EnvironmentBrowserShell
name: 'Default view').
subView:= viewComposer composingView viewNamed: 'variables'.
subView customDrawBlock: [:ctx | ctx view presenter parentPresenter
customDrawVariables: ctx].
viewComposer fileSave.

viewComposer exit
==========

--
Ian

Use the Reply-To address to contact me (limited validity).
Mail sent to the From address is ignored.


Reply | Threaded
Open this post in threaded view
|

Re: Small Suggestion: Distinguishing Inherited Variables from Class Variables

Chris Uppal-3
In reply to this post by Eric Taylor
Ian,

> When making changes to the image, like this, it is best to do it as
> transparently as possible and avoid modifying any existing methods.

I'm sure you know, but it may be worth mentioning for Eric and other readers,
that there's a cleaner and more flexible way to customise the system tools --
albeit slightly more work.  You can create your own (more or less trivial)
subclasses of the existing tools, and then use the options in User
Preferences=>Development System to tell the IDE to use your modified subclass
in preference to the existing one.

Also, somewhat off-topic, but since you've reminded me of it.  For some time I
have had a modified CHB in my image which emboldens the method categories,
protocols, and variable names that "match" the currently selected method.  That
feature has made it into D6 (which is nice) for categories and protocols.  I
just wanted to suggest to OA, or anyone who likes to add their own custom
extensions, that doing it for variable names is helpful too.  For instance,
checking an #initialize method to see which variables I've forgotten to set ;-)

    -- chris


Reply | Threaded
Open this post in threaded view
|

Re: Small Suggestion: Distinguishing Inherited Variables from Class Variables

Ian Bartholomew-21
Chris,

>  You can create your own (more or less trivial)
> subclasses of the existing tools, and then use the options in User
> Preferences=>Development System to tell the IDE to use your modified
> subclass
> in preference to the existing one.

Yes, you're right it would be cleaner to do it that way.  The only problem
in this case is that you would have to add three new classes, one for each
ClassBrowserAbstract subclass, and each subclass would have the same
methods.  Slightly smelly in it's own right :-)

The other problem I worry (not quite the right word but you know what I
mean) about with replacing browsers in this way is what happens if all
browser extensions use the same technique.  You could end up with a sort of
"browser extension wars" with each extension trying to make sure it is the
preferred one :-)

> Also, somewhat off-topic, but since you've reminded me of it.  For some
> time I
> have had a modified CHB in my image which emboldens the method categories,
> protocols, and variable names that "match" the currently selected method.
> That
> feature has made it into D6 (which is nice) for categories and protocols.
> I
> just wanted to suggest to OA, or anyone who likes to add their own custom
> extensions, that doing it for variable names is helpful too.  For
> instance,
> checking an #initialize method to see which variables I've forgotten to
> set ;-)

Yes, that's a good idea.  I've already modified the code I posted earlier to
show inherited variables in a different colour and also done something I've
wanted to do for some time - added ClassVariables to the list.  The next
step will be to do as you suggest, emboldening the variable names that are
referenced in the currently selected method.  A quick play indicates that
might require a bit more work so I may ask to "borrow" your code.

--
Ian

Use the Reply-To address to contact me (limited validity).
Mail sent to the From address is ignored.


Reply | Threaded
Open this post in threaded view
|

Re: Small Suggestion: Distinguishing Inherited Variables from Class Variables

Ian Bartholomew-21
In reply to this post by Eric Taylor
The code (OK, hack) below is the result of my first attempt at rejigging the
variable view.  The changes are -

- When the instance tab is selected the variables list contains Class
Variables sorted by name followed by Instance Variables.

- When the class tab is selected the variables list contains Class Variables
and Class Instance Variables

- All variables defined in the currently selected class are drawn in black,
all others are in that wishy washy mauve

- Selecting one or more variables results in the method list only containing
methods that reference the selected variable(s)

- Selecting a method results in all the variables used by the method being
emboldened.  The intention was that if multiple methods were selected then
the variable list would bolden the variables used in any of the methods but
(a) it was proving a bit difficult to implement and (b) I noticed that OA
didn't bother for the category or protocol lists, so it didn't get done.

I'll run with this for a while and if it proves useful then I'll have a go
at implementing it properly.

Comments welcome

BTW, This is for Dolphin Pro, Dolphin CE users will need to remove the
methods for SystemBrowserShell and EnvironmentBrowserShell (3 of each)
before filing in

==========

!ClassBrowserAbstract methodsFor!

updateVariablesIDB
 "Private - Update the list of instance variables in this class and its
superclasses."

 | class |
 variablesPresenter hasView ifFalse: [^self].
 (class := self actualClass) isNil
  ifTrue: [variablesPresenter clear]
  ifFalse:
   [| vars "Construct a list associating each class with each of its
instance variables" classVars |
   vars := SortedCollection sortBlock: [:a :b | a value <= b value].
   classVars := SortedCollection sortBlock: [:a :b | a value <= b value].
   class withAllSuperclasses
    reverseDo:
     [:eachClass |
     self isInstanceMode  | eachClass isMeta
      ifTrue:
       [eachClass classPool keysDo: [:eachClassVar | classVars add:
eachClass -> eachClassVar]].
     eachClass instVarNames do: [:eachInstVar | vars add: eachClass ->
eachInstVar]].
   vars := classVars asOrderedCollection , vars asOrderedCollection.
   "variablesPresenter model list = vars"
   false
    ifFalse:
     [| selectedVars |
     selectedVars := variablesPresenter selections.
     variablesPresenter model list: vars.
     selectedVars := selectedVars intersection: vars.
     selectedVars notEmpty
      ifTrue:
       [variablesPresenter selections: selectedVars.
       ^self]].
   "If there will be no selection, or the variables list has not changed,
then
   the list view won't issue a selection change event, so we must forcibly
   refresh the methods list"
   self onVariableSelected]! !
!ClassBrowserAbstract categoriesFor: #updateVariablesIDB!private!updating! !

!ClassBrowserAbstract methodsFor!

variablesMethodFilterIDB
 "Private - Answer a <monadicValuable> that, when passed a <CompiledMethod>,
answers true if the
 method should be displayed in the receiver by warrant of the variable that
is selected"

 | indices |
 indices := self variablesIndices.
 ^[:m |
 (self isMethodVisible: m)
  and:
   [(m byteCodeDispatcher accessesInstVarAtAnyOf: indices)
    or:
     [| variablesX literalsX |
     variablesPresenter hasSelection
      ifTrue:
       [variablesX := variablesPresenter selections collect: [:each | each
value].
       literalsX := m allLiterals
        select: [:each | each isKindOf: Association]
        thenCollect: [:each | each key].
       (variablesX intersection: literalsX) notEmpty]]]]! !
!ClassBrowserAbstract categoriesFor:
#variablesMethodFilterIDB!accessing!private! !

!ClassBrowserAbstract methodsFor!

customDrawVariables: aNMLVCUSTOMDRAW
 | variable |
 variable := aNMLVCUSTOMDRAW item.
 variable isNil ifTrue: [^self].
 self emphasiseVariableItem: aNMLVCUSTOMDRAW
  isRelevant: ((classesPresenter actualClass instVarNames includes: variable
value)
    or: [classesPresenter actualClass classPool keys anySatisfy: [:each |
each = variable value]]).
 self hasMethodSelected
  ifTrue:
   [| index |
   index := classesPresenter actualClass indexOfInstVar: variable value
ifAbsent: [nil].
   index
    ifNil:
     [self emboldenVariableItem: aNMLVCUSTOMDRAW
      isRelevant: (self method allLiterals
        anySatisfy: [:each | (each isKindOf: Association) and: [each key =
variable value]])]
    ifNotNil:
     [self emboldenVariableItem: aNMLVCUSTOMDRAW
      isRelevant: (self method byteCodeDispatcher accessesInstVarAt:
index)]]
  ifFalse: [self emboldenVariableItem: aNMLVCUSTOMDRAW isRelevant: false]! !
!ClassBrowserAbstract categoriesFor: #customDrawVariables:!public! !

!ClassBrowserAbstract methodsFor!

emboldenVariableItem: anNMTVCUSTOMDRAW isRelevant: aBoolean
 anNMTVCUSTOMDRAW font isBold: aBoolean! !
!ClassBrowserAbstract categoriesFor:
#emboldenVariableItem:isRelevant:!helpers!private! !

!ClassBrowserAbstract methodsFor!

emphasiseVariableItem: anNMTVCUSTOMDRAW isRelevant: aBoolean
  aBoolean ifFalse: [anNMTVCUSTOMDRAW forecolor: self class
looseMethodColor]! !
!ClassBrowserAbstract categoriesFor:
#emphasiseVariableItem:isRelevant:!helpers!private! !

!ClassBrowserShell methodsFor!

updateVariables
 ^super updateVariablesIDB!

variablesMethodFilter
 ^super variablesMethodFilterIDB! !
!ClassBrowserShell categoriesFor: #updateVariables!private!updating! !
!ClassBrowserShell categoriesFor: #variablesMethodFilter!accessing!private!
!

!EnvironmentBrowserShell methodsFor!

updateVariables
 ^super updateVariablesIDB!

variablesMethodFilter
 ^super variablesMethodFilterIDB! !
!EnvironmentBrowserShell categoriesFor: #updateVariables!private!updating! !
!EnvironmentBrowserShell categoriesFor:
#variablesMethodFilter!accessing!private! !

!SystemBrowserShell methodsFor!

updateVariables
 ^super updateVariablesIDB!

variablesMethodFilter
 ^super variablesMethodFilterIDB! !
!SystemBrowserShell categoriesFor: #updateVariables!private!updating! !
!SystemBrowserShell categoriesFor: #variablesMethodFilter!accessing!private!
!

!ClassBrowserShell methodsFor!

onMethodSelected
 super onMethodSelected.
 variablesPresenter view invalidate! !
!ClassBrowserShell categoriesFor: #onMethodSelected!public! !

!EnvironmentBrowserShell methodsFor!

onMethodSelected
 super onMethodSelected.
 variablesPresenter view invalidate! !
!EnvironmentBrowserShell categoriesFor: #onMethodSelected!public! !

!SystemBrowserShell methodsFor!

onMethodSelected
 super onMethodSelected.
 variablesPresenter view invalidate! !
!SystemBrowserShell categoriesFor: #onMethodSelected!public! !

!ClassBrowserShell methodsFor!

onVariableSelected
 super onVariableSelected.
 variablesPresenter view invalidate! !
!ClassBrowserShell categoriesFor: #onVariableSelected!public! !

!EnvironmentBrowserShell methodsFor!

onVariableSelected
 super onVariableSelected.
 variablesPresenter view invalidate! !
!EnvironmentBrowserShell categoriesFor: #onVariableSelected!public! !

!SystemBrowserShell methodsFor!

onVariableSelected
 super onVariableSelected.
 variablesPresenter view invalidate! !
!SystemBrowserShell categoriesFor: #onVariableSelected!public! !

| viewComposer subView |
viewComposer := ViewComposer show: 'Vertical view'.
viewComposer openOn: (ResourceIdentifier class: ClassBrowserShell name:
'Default view').
subView:= viewComposer composingView viewNamed: 'variables'.
subView customDrawBlock: [:ctx | ctx view presenter parentPresenter
customDrawVariables: ctx].
viewComposer fileSave.
viewComposer openOn: (ResourceIdentifier class: SystemBrowserShell name:
'Default view').
subView:= viewComposer composingView viewNamed: 'variables'.
subView customDrawBlock: [:ctx | ctx view presenter parentPresenter
customDrawVariables: ctx].
viewComposer fileSave.
viewComposer openOn: (ResourceIdentifier class: EnvironmentBrowserShell
name: 'Default view').
subView:= viewComposer composingView viewNamed: 'variables'.
subView customDrawBlock: [:ctx | ctx view presenter parentPresenter
customDrawVariables: ctx].
viewComposer fileSave.
viewComposer exit

==========


--
Ian

Use the Reply-To address to contact me (limited validity).
Mail sent to the From address is ignored.