Blog

Tracking a FastTable bug with GTInspector

In a previous article we looked at how moldable tools can change the development experience when tracking down a bug. The bug in question was a duplicated behaviour in GTDebugger: triggering an action from the context menu of the stack triggered that action twice.

A few weeks after that bug was fixed, another interesting bug was reported for GTInspector, affecting the navigation feature of the inspector: when an object is selected in a view, the pane to the right is created four times, as if the user selected that object four times.

In this article we detail the workflow that we followed to understand and fix this bug. This workflow consists in treating software problems as data problems, and formulating and solving one hypothesis at a time. Hence, we do not try to gain knowledge just by reading code. Instead we use tools to query and visualize our data, the code. When an appropriate tools is not available we build it. We then use the gained insight to formulate the next hypothesis and iterate until we understand the cause of the bug, and are able to fix it. As much as possible, we make all hypotheses explicit.

Reproducing the bug

The bug in question only appers when the user selects an object within certain inspector views. For example, we reproduced the bug by creating and inspecting a SharedQueue object, and selecting any value in the 'Items' view. To get a visual indication of the bug, as the SharedQueue that we created contains integers, we added an #inform: message to the method Integer>>gtInspectorIntegerIn: creating the 'Integer' view. This way we can see that when selecting an object in the 'Items' view, the method is called four times:

Inspector_SharedQueue_WrongBehaviour.png

However, the bug did not appear when selecting an object in the 'Raw' view of a SharedQueue object:

Inspector_SharedQueue_RawPresentation.png

By looking at the code of SharedQueue>>#gtInspectorItemsIn:, we observe that it uses a Fast Table presentation. Given that the bug that we previously investigated was also related to Fast Table, we like to check first whether this bug is also related to Fast Table. One way to verify this hypothesis is to create an identical presentation for SharedQueue objects that does not use Fast Table to display a list, but the previous list renderer based on Pluggable Tree Morph. We can view the code of SharedQueue>>#gtInspectorItemsIn: and create the new view directly in the inspector:

SharedQueue_ListView_Code.png

When redoing the previous scenario using the newly created view, we can indeed confirm that the bug is not present; Integer>>gtInspectorIntegerIn: is called only once. Hence, this bug is again related to Fast Table.

Inspector_SharedQueue_PluggableMorphCorrect.png

Comparing a buggy and a correct scenario

Given that we have a correct and a buggy scenario, before going any further, we would like to quickly check if there are any differences between an execution using Fast Table and an execution using Pluggable Tree Morph. We hypothesis that the problem could be caused by the Glamour renderer for Fast Table not following the same logic as Pluggable Tree Morph. Glamour, is the browsing engine on top of which GTInspector is implemented. Glamour provides two distinct renderers for displaying lists, one for Fast Table and one for Pluggable Tree Morph. If we do not see a divergence in the call stacks of the two renderers, we can focus our investigation on the Fast Table renderer.

We could approach this task by opening two debuggers and then manually scrolling through the stacks to find a difference. However, a less manual and error-prone approach consists in creating a custom view that shows the two call stacks using a tree, highlighting the points where the stacks diverge.

To build this tool we first need to log the two stack traces. For that we can rely on the Beacon logging engine and replace the #inform: call from the method Integer>>gtInspectorIntegerIn: with a logging statement that records the stack of method calls (MethodStackSignal emit).

Integer>>gtInspectorIntegerIn: composite
 <gtInspectorPresentationOrder: 30>
	
 MethodStackSignal emit.
	
  ^ composite table
    title: 'Integer';
    display: [ | associations | "..." ]
    "..."

We then start the recording using MemoryLogger start, and trigger the two scenarios by selecting an item in the views 'Items (simple)' and 'Items'. Next, we stop the recorder and inspect the collected stacks using the GTInspector:

MemoryLogger instance recordings collect: #stack 

We observe that we got five stacks. Four correspond to the buggy scenario, and one to the correct scenario. We also notice that there is a difference in the number of stack frames between the two scenarios.

Beacon_Logging_CorrectWrongStacks.png

Nevertheless, if we briefly look at one correct and one buggy stack trace, we notice that there are a lot of frames that are not related to Glamour, caused by how the two graphical widgets (FTTableMorph used by the Fast Table renderer and PaginatedMorphTreeMorph used by the Pluggable Tree Morph renderer) handle the selection of an element. To verify our hypothesis, we are only interested in those stack frames related to Glamour.

Stack_Inspector_Comparison_CorrectWrong.png

To build the custom view, we switch to the 'Raw' view of the inspector and use a Roassal script. First, we select a correct and a buggy stack trace and then remove all stack frames that are not related to Glamour. We rely on the fact that all Glamour classes have the prefix 'GLM'. Then, we add the filtered stack frames in one set, draw edges between consecutive entries, and arrange the graph in a tree. We also attach an index to methods for ensuring that multiple occurrences of the same method in the stack will have different entries in our view.

| view stacks |
view := RTMondrian new.
stacks := ({self first. self second}) collect: [ :aStack |
  aStack select: [ :frame | frame methodClass name beginsWith: 'GLM' ] ].

stacks := stacks collect: [ :aStack |
  aStack withIndexCollect: [ :aFrame :index |
    index -> aFrame method ] ].

view shape label text: [:each | each value gtDisplayString truncate: 50 ] .
view nodes: (stacks flatCollectAsSet: #yourself).
stacks do: [ :aStack |
  aStack overlappingPairsDo: [ :a :b |
    view edges
      connectFrom: [:x | b ]
        to: [:x | a ] ] ].
view layout tree.
view.

Executing the script in place shows us the view in a new pane to the right directly in the inspector:

Stack_Roassal_Comparison_CorrectWrong.png

We immediately notice that most of the two stacks are identical, with some small differences at the top. We zoom in and slightly rearrange the top contexts to better understand what causes this difference:

Stack_Roassal_Comparison_CorrectWrong_Zoom.png

In this case, we discover that the difference appears because the Glamour renderer for Fast Table and the Glamour renderer for Pluggable Tree Morph have a different way of propagating the selection. However, in the end, both renderers call the correct method GLMPresentation>>#selection:. Hence, the problem is most likely related to Fast Table. We use this newly gained insight to steer the focus of our investigation.

Comparing the four incorrect stack traces

Our next hypothesis is that in the four buggy stack traces the execution branches in a certain method because of a loop. Verifying this hypothesis requires a tree visualization that shows execution branches caused by the same method being sent to different objects. In the previous view, we only took into account methods. To build this new view, we also need to log the actual objects from the execution stack. We can do this be replacing the MethodStackSignal logger with ContextStackSignal logger in the method Integer>>gtInspectorIntegerIn::

Integer>>gtInspectorIntegerIn: composite
<gtInspectorPresentationOrder: 30>

ContextStackSignal emit.

^ composite table
  title: 'Integer';
  display: [ | associations | "..." ]
  "..."

We then clear and start the MemoryLogger, and select an item in the buggy `Items` view. Inspecting the log shows the four stack traces:

Beacon_Logging_FourWrongStacks.png

We create next the tree vizualization using Roassal and execute it in place. We follow the same steps as for the previous visualization, this time without doing any filtering of the stack frames:

Stack_Roassal_Comparison_FourWrongStacks.png

In the resulting view we can see that we have four stack traces because the execution branches in two places: an initial branch point that occurs only once, and a second one that occurs two times.

Stack_Roassal_Comparison_FourWrongStacks_Full.png

Next, we can zoom in and investigate each stack frame corresponding to a branch point in detail:

StackExploration_BranchPoint_1.png StackExploration_BranchPoint_2.png

In each case we notice that the inspected announcer has some duplicated subscriptions. Having some knowledge of the Glamour renderer, we suspect that this should not be the case; each subscription should be registered only once. We use this insight to continue the investigation.

Reducing the scope

Now that we detected a possible cause for the bug, before going any further, we can devise a simpler example exhibiting the same behaviour:

GLMCompositePresentation new
  with: [ :c |
    c fastList 
      send: [ :anInteger | self inform: '#send:'. anInteger ] ];
   openOn: (1 to: 42)

After executing the code above and selecting an element in the list, we get the same four notifications as before.

Simple_Bug_Example.png

Finding the cause of the duplication

To verify if those announcements need to be registered twice, we need to find the places where the registration happens. Searching for the methods that reference the class FTSelectionChanged (one of the duplicated announcements) we discover that it is called from the method GLMMorphicFTRenderer>>initializeAnnouncementForDataSource. The fact that the subscription is registered twice indicates that the method is called twice. We proceed as before, and instead of putting a breakpoint in the method, we add a Beacon logging statement, and only record events while we open the buggy browser.

GLMMorphicFTRenderer>>initializeAnnouncementForDataSource
  ContextStackSignal emit.
  "..."	

RecordingBeacon new
  runDuring: [
    GLMCompositePresentation new 
      with: [ :c | 
        c fastList 
          send: [ :anInteger | self inform: '#send:'. anInteger ] ];
      openOn: (1 to: 42) ].

We see that indeed there are two calls to #initializeAnnouncementForDataSource. As the log event recorded the entire stack, we can select and explore the two contexts making the call to the method #initializeAnnouncementForDataSource that registers the FTSelectionChanged announcement:

Exploring_ProblematicCall_1.png Exploring_ProblematicCall_2.png

We observe that the first call is made from the method GLMMorphicFastListRenderer>>render:, and the second from the method GLMMorphicFastListRenderer>>dataSourceUpdated:. To understand the relation between these two methods within the execution, we again construct a tree with the two call stacks. We already have a visualization for this task, as we built it in a previous step.

Exploring_Two_Stacks_DataSource.png

We immediately see that the two stacks diverge in the method GLMMorphicFastListRenderer>>render:. This is actually the method that makes the first call to #initializeAnnouncementForDataSource. We can now navigate through the other call stack to understand why it was made. We can basically use the GTInspector as a port-mortem debugger!

Exploring_ProblematicCall_Roassal_1.png Exploring_ProblematicCall_Roassal_2.png

Before moving forward, we need to clarify a relevant aspect regarding the design of the Glamour renderer for Fast Table. GLMMorphicFastListRenderer is the Fast Table renderer. The renderer creates a graphical widget (FTTableMorph), a data source and links them together. The widget displays the elements visually and the data source provides the elements that will be displayed.

We see in the previous view that the second call to #initializeAnnouncementForDataSource happens when the graphical widget FTTableMorph is initialized. The reason is that whenever the data source is changed within a FTTableMorph widget, the method #initializeAnnouncementForDataSource is called to link the graphical widget with the new data source. We can see this in the method GLMMorphicFastListRenderer>>#dataSourceUpdated: that is called whenever the data source is changed in the widget, as a result of the GLMDataSourceUpdated announcement (GLMMorphicFastListRenderer>>readyToBeDisplayed):

dataSourceUpdated: announcement
  tableModel ifNotNil: [ self unsubscribeDataSource: tableModel ].
  tableModel := announcement newDataSource.
  self initializeAnnouncementForDataSource

If we look for methods referencing GLMDataSourceUpdated, we discover that the link between the announcement GLMDataSourceUpdated and the method #dataSourceUpdated: is created when the renderer (GLMMorphicFastListRenderer) is initialized:

initializeAnnoucementForPresentation: aPresentation
  aPresentation when: GLMDataSourceUpdated send: #dataSourceUpdated: to: self.
  aPresentation when: GLMContextChanged send: #actOnContextChanged: to: self.
  aPresentation when: GLMPresentationUpdated send: #actOnUpdatedPresentation: to: self 

At this point we gained a good understanding of the factors causing the bug. To summarize them: when a Fast Table view is created, the method GLMMorphicFastListRenderer>>render: instantiates a new data source and calls #initializeTableMorph. #initializeTableMorph creates a graphical widget and sets its data source. After the graphical widget is initialized GLMMorphicFastListRenderer>>render: calls #initializeAnnouncementForDataSource to properly set the announcements between the graphical widget and the data source. However, this method was already executed when the data source was set in a FTTableMorph widget in #dataSourceUpdated:. Hence, we can fix the bug by removing the explicit call to #initializeAnnouncementForDataSource from GLMMorphicFastListRenderer>>render:.

Documenting our finding

Now that we found and fixed the bug we can document our finding. To ensure that this bug will not happen in the future, the best solution is to rely on a test. We create a test that verifies that there are no duplicated subscriptions in an announcer. We then apply this test on the two announcers from Glamour that have duplicated subscriptions. This way, if at any point in the future a duplicated subscription is introduced, we will be notified and can check if the duplication makes sense or if it is a bug.

testNoDuplicateRegistrationsInFastTableRenderer
  | table |
  window := GLMCompositePresentation new
    with: [ :c |
      c fastList ];
    openOn: (1 to: 42).

  table := self find: FTTableMorph in: window.
  self assertNoDuplicatedAnnoucementsIn: table announcer.
  self assertNoDuplicatedAnnoucementsIn: table dataSource announcer.

Building a toolset

Solving this bug was done through building custom tools. In this particular case, the tool consisted in a view for displaying stack traces using a tree. Initially, when we solved the previous bug related to Fast Table, we also built such a view, but then we did not know if we will even reuse that view (tool) so we threw it away. Now, we had to reuse the view again and make a few adaptations: filter stack frames using a condition and create edges based only on method calls. Hence, we can now spend 15 minutes more and transform this view into a tool that we can then reuse in the future, whenever we need to compare stack traces.

We transform this view into a tool by putting in into a dedicated class and adding an API for configuring it:

BeaconRTStackViews>>#executionTreeForContextSignals: aCollectionOfSignals
  | stacks |
  stacks := ((aCollectionOfSignals 
    select: [ :each | each isKindOf: ContextStackSignal ])
    collect: #stack).
  ^ self executionTreeForContexts: stacks 
      select: [ :each | true ] 
      transform: [ :each | each ]
BeaconRTStackViews>>#executionTreeForContexts: aCollectionOfStacks select: aFilterBlock transform: aTransformBlock
  | view stacks |

  stacks := aCollectionOfStacks collect: [ :aStack | aStack select: aFilterBlock ].
  stacks := stacks collect: [ :aStack |
    aStack withIndexCollect: [ :aFrame :index | aTransformBlock cull: aFrame cull: index ] ].

  view := RTMondrian new.
  view shape label text: [:each | each value gtDisplayString truncate: 50 ] .
  view nodes: (stacks flatCollectAsSet: #yourself).
    stacks do: [ :aStack |
      aStack overlappingPairsDo: [ :a :b |
        view edges
          connectFrom: [:x | b ]
          to: [:x | a ] ] ].
  view layout tree.
  ^ view

We are still not done. We invested effort into building this tool, however, if other developers are not aware that this tool exists they will not use it. Hence, we should invest a few more minutes to address this.

This view is applicable when we inspect a collection of Beacon events of type ContextStackSignal. We extend the GTInspector with a custom action for collections that is only applicable if the collection contains at least one Beacon event of that type. We further implement the action so that the view is opened in a new pane to the right, preserving thus the workflow in the same inspector window.

SequenceableCollection>>#gtInspectorActionExecutionTree
  <gtInspectorAction>
  ^ GLMGenericAction new
    title: 'View contexts execution tree';
    category: 'Beacon';
    action: [ :aPresentation |
      aPresentation selection:
        (BeaconRTStackViews new executionTreeForContextSignals: self) ];
    condition: [ self anySatisfy: [ :each | 
      each isKindOf: ContextStackSignal ] ]

Now, whenever somebody inspects a collection containing stack traces recorded with Beacon, she will be able to discover and open this view directly from the inspector:

Beacon_Custom_Extensions.png

Remarks

We started this session with the goal of understanding the cause of a bug and end it by adding a custom tool to our environment. We achieved this as we were able to rapidly create the necessary tool and easily incorporate it into the IDE. We could do this as Pharo is a moldable IDE where creating a new custom extension is just as easy as creating a test.

Posted by Andrei Chis at 25 April 2017, 7:30 am with tags assessment, tools, gt, pharo, moose, story link
|

Hunting leftover weak announcements with GTInspector

Yesterday, I paired with Andrei and joined the hunt for leftover weak announcements that tend to accumulate in Pharo images since recently. This is a problem because it leads to an overall slowdown of the system. There were already several valuable points made in the long thread and there was even a fix readily available provided by Max Leske.

The main issue seemed to be that the weak announcements were not garbage collected because of a VM problem even if their subscribers were nil. However, there also seemed to be indications that the code related to the Glamorous Toolkit might have been responsible for this problem, so we wanted to understand the issue to see if there was anything we could do to help, especially given that the very problems in the inspector seemed to turn the inspector not so useful for identifying the problem. This turned out to be an exciting 30 minutes assessment session. Let me get you through it.

In a Pharo 50662, we started by inspecting:

SystemAnnouncer uniqueInstance

The inspector readily showed us the 2602 subscriptions. From the start we saw that there were many for which the subscribers are nil, a point also raised by Peter:

Weak-1.png

Another thing we noticed is that there seemed to be a repetition of announcements that appeared with nil subscribers. To check this, we executed:

grouped := (SystemAnnouncer uniqueInstance
    subscriptions glmSubscriptions select: [ :each |
    each subscriber isNil ])
        groupedBy: [:each | each announcementClass name].

Indeed, there were only 4 announcements that were affected by the problem:

Weak-3.png

More interestingly, we noticed that we had an equal amount of subscriptions for each announcement type (i.e, 640). This suggested that these registrations came from the same place. To browse this possibility, we looked for all methods that reference all these classes:

grouped keys allButFirst
    inject: (SystemNavigation new
             allReferencesTo: grouped keys first asClass binding)
    into: [ :result :each |
        result intersection: (SystemNavigation new
                              allReferencesTo: each asClass binding) ].

We got 12 such methods:

Weak-5.png

We browsed a bit, and we saw that some of these methods registered other system announcements as well, such as ClassCommented, but those did not appear in our problem list:

Weak-6.png

Thus, this route did not seem to be the best way to understand the source of the problem. We turned a bit around and took another route. As, each subscription provides us the selector that is to be sent when the announcement gets triggered, we queried the system to give us those selectors:

groupedSelectors := grouped associations collect: [ :assoc |
    assoc value collect: [:each | each action selector ] as: Set].

In this case, too, we got for each distinct announcement exactly one selector.

Weak-7.png

So, we looked at all methods that send all of these selectors:

selectors := groupedSelectors flatCollect: #value.
selectors allButFirst
    inject: (selectors first senders)
    into: [ :result :each |
        result intersection: each senders ].

And we got exactly one method: PragmaCollector>>installSystemNotifications.

Weak-8.png

Essentially, this means that the responsible for creating the global subscriptions that should have been garbage collected was the PragmaCollector. Certainly, the problem was not related to the PragmaCollector, but we now knew that no code in the Glamorous Toolkit prevented these subscriptions to become garbage collected.

We manually applied the patch to finalize and eliminate these subscriptions:

(SystemAnnouncer uniqueInstance subscriptions glmSubscriptions copy select: [ :sub |
    sub class = WeakAnnouncementSubscription and: [
        sub subscriber isNil ]])
            do: #finalize.
Smalltalk garbageCollect.

We were not yet quite done because executing:

WeakAnnouncementSubscription allInstances select: [:sub | sub subscriber isNil]

told us that we have more than 2000 instances left to deal with. The first question we asked was where did all these come from. There needed to be some global variables that were keeping those around but we did not know which one given that SystemAnnouncer uniqueInstance was cleaned up. We applied the same type of analysis.

announcements := (WeakAnnouncementSubscription allInstances select: [ :each |
     each subscriber isNil ])
          asOrderedCollection groupedBy: [:each | each announcementClass ].

Again, we found that all of the announcements are global announcers about the state of the system, and that each of them appeared in equal quantities.

Weak-10.png

Like in the previous case, we again looked at the place where all these announcements are sent from:

announcements keys allButFirst
    inject: (SystemNavigation new
            allReferencesTo: announcements keys first binding)
   into: [ :result :each |
      result intersection: (SystemNavigation new
                            allReferencesTo: each binding) ].

We found 3 cases. The first two were using SystemAnnouncer uniqueInstance weak, so these could have not been the root. In the third one, we discovered a new announcer: SystemAnnouncer uniqueInstance private.

Weak-11.png

In the end, this reported problem was not related to GT. There were other problems related to the management of announcements, but those were other cases.

This session showed again how the quick connection between the runtime and code can dramatically speedup the amount and the depth of the questions we can ask our system. And this is critical for modern software engineering.

Posted by Tudor Girba at 29 March 2016, 7:50 am with tags story, assessment, gt link
|

Debugging a duplicated behavior with GTInspector

I have just spent a beautiful 15 minutes tracking a bug down. It was so exciting that afterwards I decided to spend 2 days documenting the experience because I think it offers an elaborate example of how transformative development workflows can be with moldable tools in a live environment.

The bug in question was reported recently and it is related to the GTDebugger version that we introduced recently in Pharo.

The problem looks as follows. Triggering an action from the context menu of a stack seems to trigger twice the action. This is particularly visible when a window is spawned twice, such as when trying to see the implementors of a method from the stack.

Duplicated.png

This is a tricky problem, and it can come from all sorts of places. What is certain, is that at some point there are two executions of spawning the implementors window. The debugger defines this action in the GTMoldableDebugger>>browseMessages method. We put a breakpoint in the method, and indeed, it is being executed twice. Exploring the stack in both cases does not seem to reveal anything meaningful. The stack looks the same, so likely the problem comes from different objects, not from different messages.

To reason about this, we need a different presentation. Ideally, we would like to see the complete execution and check the points in which the execution branches. This information is not apparent in a classic debugger because it mainly shows only the active stack and we are interested in the tree.

Nevertheless, as the tree is what we care about we should be able to build it. To do this, we utilize the Beacon logging engine, and we replace the breakpoint with a logging statement that records the stack of contexts (ContextStackSignal log).

GTMoldableDebugger>>browseMessages
    "Present a menu of all messages sent by the current message.
    Open a message set browser of all implementors of the message chosen.”

    self currentMessageName ifNotNil: [
        ContextStackSignal log.
        self systemNavigation browseAllImplementorsOf: self currentMessageName ]

We turn on recording with RecordingBeacon start. We trigger the problem again: we inspect 42 answer, and then look for implementors. And we start exploring the recordings with GTInspector.

RecordingBeacon instance recordings collect: #stack

As expected there are two such collection of stacks, where the elements in each stack are context objects.

Playground1.png

We switch to the Raw inspector presentation of the collection object, and we try to visualize the entries in the two stack in one picture. We use the RTMondrian builder of Roassal to script the visualization. We concatenate the stack entries in one set, we draw edges between consecutive entries, and we arrange the graph in a tree. We use a set because some of the entries will be the same:

| view |
view := RTMondrian new.
view shape label text: [:each | each gtDisplayString truncate: 50 ] .
view nodes: (self first, self second) asSet.
self first
    overlappingPairsDo: [ :a :b |
        view edges
            connectFrom: [:x | b ]
            to: [:x | a ] ].
self second
    overlappingPairsDo: [ :a :b |
        view edges
            connectFrom: [:x | b ]
            to: [:x | a ] ].
view layout tree.
view.

Executing in place this script shows us the execution tree.

Playground2.png

There seems to be one place which branches the execution. Let’s zoom in to see the details.

Playground3.png

We see that the stack on both branches looks the same in terms of the executed methods. Let’s see if the difference is in the objects that are executing the two branches. For this, we inspect the context before the branching happens.

Playground4.png

We look at the receiver.

Playground5.png

It’s a SubscriptionRegistry which is used by objects interested in announcements. At a closer look, we notice that all announcement, such as GLMMenuItemSelected, seem to be registered twice. This points us towards the direction of a bug in Glamour, the browsing engine on top of which the GTDebugger is implemented. Glamour uses this type of announcements to bind what happens in the concrete Morphic world, and the logical model of the browser.

Armed with this new hypothesis, we can now create a smaller experiment in which we isolate the creation of a FastTable-based list in Glamour.

GLMCompositePresentation new
    with: [ :c |
        c fastList selectionAct: #inspect entitled: 'Value' ];
    openOn: (1 to: 42)

And indeed, in the resulting browser, executing the action via the contextual menu results in two inspector being opened. This means that the problem is actually not related to the GTDebugger but to Glamour. At the same time, a replacing fastList with list does not exhibit the problem, which means that our bug is located somewhere in the binding between FastTable and Glamour. This hypothesis would make sense given that the FastTable support was only recently introduced in Glamour and thus, it can still have bugs.

To figure it out, we would need to debug this. We could try putting a breakpoint in installActionsOnModel:fromPresentation:, but that would imply that if we would use the GTDebugger, our image would go in a loop with the breakpoint trying to spawn a debugger, and the opening of the debugger hitting a new breakpoint.

So, we take the same route as before, and we insert a logging statement that captures the current stack. This time, we look only at methods because it is probably enough:

installActionsOnModel: aMorphicModel fromPresentation: aPresentation
    MethodStackSignal log.
    aMorphicModel when: GLMMenuItemSelected do: [ :ann | ann action morphicActOn: aPresentation ].
    aMorphicModel when: GLMKeyStroke do: [ :ann | ann action actOn: aPresentation ].

This logging statement is placed deep in Glamour. As the GTInspector is based on Glamour, looking at the global log recorder would reveal many appearances of this log entry that are not related to our problem. So, we scope the recording only to the execution of the creation of our browser:

RecordingBeacon new
    runDuring: [
        GLMCompositePresentation new
            with: [ :c |
                c fastList
                    selectionAct: #inspect
                    entitled: 'Value' ];
            openOn: (1 to: 42) ].

Inspecting the result shows us the recordings.

Stack1.png

There are three such recordings. One is related to the window rendering, and two are related to FastTable. We explore the first one, and it is being called from the render: method. We explore the second one, and it comes from a method called dataSourceUpdated::

Stack2.png

We look at the dataSourceUpdated: method (notice how we essentially have a postmortem debugger in the inspector):

Stack3.png

And indeed, this method erroneously calls installActionsOnModel:fromPresentation::

dataSourceUpdated: announcement
    tableModel ifNotNil: [ self unsubscribeDataSource: tableModel ].
    tableModel := announcement newDataSource.
    self installActionsOnModel: tableModel fromPresentation: tableModel glamourPresentation.
    self initializeAnnouncementForDataSource

Now we know where the problem comes from, but we are not done yet. We still have to document our finding. In this case, the most appropriate way is to write a red functional test to capture the problem of multiple announcements with the same type being registered for a FastTable:

testNoDuplicateRegistrationOfAnnouncementsOnDataSource
    | table amountOfMenuItemSelectedSubscriptions |
    window := GLMCompositePresentation new
            with: [ :c |
                c fastList selectionAct: #inspect entitled: 'Value' ];
            openOn: (1 to: 42).
    table := self find: FTTableMorph in: window.
    amountOfMenuItemSelectedSubscriptions := table dataSource announcer subscriptions glmSubscriptions count: [ :each | each announcementClass = GLMMenuItemSelected ].
    self assert: amountOfMenuItemSelectedSubscriptions equals: 1

Then we remove the troubling line, and check that the test is green.

Now we are done.

Remarks

Let’s take a step back and look at the ingredients of this session. We guided all our steps through hypotheses following the humane assessment philosophy. As a consequence, at every point we knew where we were and why we were there. And we guided our actions by testing these hypotheses through custom made analyses.

To make this practical, we need tools that allow us to go through these scenarios inexpensively and live. With Pharo this is now a reality.

Looking at the details, our analysis involved actions such as:

  • recording the stack through a logger,
  • inspecting the stack postmortem with the inspector,
  • visualizing multiple stacks together, or
  • scoping the recording to a particular part of the execution.

Granted, these are typically perceived as advanced actions, but they really are not that complicated.

One thing that might appear hard is the idea of recording the execution context and then utilizing the inspector to debug. I reported on this technique before. On that occasion, I did it by directly inspecting thisContext. In the current case I used Beacon because (1) it makes it even easier to capture the stack as a log signal and offer it for later inspection (e.g., ContextStackSignal log), and (2) it has a convenient way to scope log capturing.

Another thing is the use of visualization which proved to be essential for solving our problem. It helped us analyze the two initial stacks in one meaningful picture that helped us quickly discover the point to look at (i.e., the branching point). This was possible exactly because we could embed that Roassal visualization right in place with little effort. It does require some learning, but together with the deep integration in the Glamorous Toolkit it brings with it a complete new way of exploring objects.

In my book, this session counts as cool. If you agree, we just labelled a debugging session as cool. And this is not at all an isolated case. It is actually rather common in my world. That is because debugging, and assessment in general, is an exciting activity. Can you say the same? If not, I invite you to start exploring what Pharo has to offer and go beyond the typical routine. You will be surprised.

Posted by Tudor Girba at 2 February 2016, 9:30 am with tags story, gt, spike, pharo, moose link
|

Guiding a rename effort with GTInspector

After a debate on the Pharo mailing list, we ended up choosing to rename all variations of the example* pragmas to gtExample*. Furthermore, as a second step, we also wanted all methods annotated with gtExample* to start with an example prefix because this would not conflict with the behavior from the code browser.

With this occasion, we also decided to go through the list manually to review. This is not a terribly complicated issue except that we are talking about some couple of hundred methods scattered through dozens of classes.

Having to affect multiple pieces of code scattered throughout the system is not an atypical software development problem, and I find it odd at how little support there exists in typical IDEs for something like this. So, how do you keep track of something like this in Pharo?

Here is a variation of a script that we used to keep track of the second step of renaming the method names:

(Object withAllSubclasses flatCollectAsSet: [ :each |
     (Pragma allNamed: #gtExample in: each) ,
     (Pragma allNamed: #gtExample: in: each) ,
     (Pragma allNamed: #gtExampleFrom: in: each) ])
     select: [ :each | each selector beginsWith: 'example' ]

Inspecting the result in the inspector, reveals a small query-scoped browser that allows you to focus only on the task at hand and know precisely when you are finished.

Browsing-methods.png

This solution is terribly inexpensive. Essentially, it is a short query combined with some object inspection. The code involved is minimal, too. This is possible exactly because we turned the concept of an IDE on its head, and as a consequence many use cases that are otherwise seen as the exclusive realm of dedicated tools can be handled with compositions of modular and small ones.

Posted by Tudor Girba at 17 May 2015, 4:09 pm with tags story, gt, spike, pharo, moose link
|

Checking for uniformity in SVN from Pharo

In an effort to ease continuous delivery for a system, we needed to ensure that all installation projects (for various sites and customers) had a uniform structure. Specifically, after refactoring the package assembly part of the continuous delivery pipeline, we wanted to ensure that all installation projects had a configs/srv/deployments/ path in them.

To check this, we created a tiny script. First, we invoked the Windows command line to get the list of all installation names from Subversion and we dumped these in a installations.txt file:

WinProcess createAndWaitForProcess: 'cmd /c "svn list https://svn/svn/delivery/installations > installations.txt"'.

Afterwards, to check that each of these projects we traversed all the corresponding Subversion repositories. The simplest way we could think of was to simply check that the header of the http request is not an error (such as 404):

'installations.txt' asFileReference readStreamDo: [ :s |
     s contents lines select: [ :each |
          (ZnClient new
               url: 'https://svn/svn/delivery/installations/', each, 'trunk/configs/srv/deployments/';
               username: ‘username' password: ‘password';
               head;
               response) isError ] ].

We got some 80 such projects that needed to be redone (out of a couple of hundred). The whole exercise took less than 10 minutes and could be done with a stock Moose (or even Pharo in this case) distribution, but it was a useful test that guided a multi-hour work. At the end, we reran the same script to check that we are truly done. And we were done.

Posted by Tudor Girba at 4 May 2015, 11:36 pm with tags story, spike, moose, assessment link
|
<< 1 2 3 4 5 6 7 8 >>