Previous
Contents
Next

Advanced Programming Techniques for MVC

Multi-Window Applications


This section explains how to program applications that use several cooperating windows to solve a problem.

To explain some techniques of general importance, we use this example:

This is a program that draws Lissajous-figures. This is simple to program and it gives beautiful results. Lissajous-figures have some importance in electronics; an oscilloscope can show these figures, which are useful to measure frequency ratios.

The formula for a Lissajous-figure is:

 { sin(p1*t), cos(p2*t) }

where t is a parameter and p1, p2 are constants. The ratio of these two constants determines the form of the figure.

To change the pen color and the values of the parameters p1, p2, we use two small windows that can be opened and closed with the switches on the top of the diagram window or with the diagram menu. These small windows may partly cover the diagram window, but nevertheless you can select values. The diagram window is immediately refreshed when you make a selection. Programming techniques to refresh partly obscured windows are one main feature of this section.

You should first install this example into an image and play with it. This will help you to understand the explanation of all the details that follow. The change set is MultiWindowDemo.cs.

The model of the main window is implemented by class MultipleWindowApplication:

Model subclass: #MultipleWindowApplication
      instanceVariableNames: 'switch1 switch2
                              p1 p2 lineColor
                              parameterChooser colorChooser'
      classVariableNames: ''
      poolDictionaries: ''
      category: 'MVCTutorial-MultipleWindows'

The instance variables have these meanings:

The view of a MultipleWindowApplication contains two PluggableButtonViews and a DiagramDisplayView. The latter is defined as follows:

View subclass: #DiagramDisplayView
     instanceVariableNames: 'aspect menuAccessor'
     classVariableNames: ''
     poolDictionaries: ''
     category: 'MVCTutorial-MultipleWindows'

The instance variables have these meanings:

The interesting feature of this class is the instance method displayView, which has the responsibility to fill the inset display box of the view.

displayView
  self visibleAreas do:
    [:rect |  
        Display clippingWith: rect
                do: [model perform: aspect with: self]
    ].

The method first computes a decomposition of the visible part of the inset display box into disjunct rectangles. Once this collection is known, the model is asked to draw the entire diagram once for each rectangle. A properly set clipping rectangle ensures that only the part of the drawing that falls within a rectangle of the visible area is displayed.

It is clear that this principle remarkably increases the display time when the visible area is a large collection of small rectangles. Sometimes it might be a better solution to draw the view content once an a Form. Parts of that form are then copied into the rectangles of the visible area. We will discuss this alternative later.

The method clippingWith:do: is added to the instance protocol of DisplayScreen. It computes the intersection of the current clipping rectangle with a second one:

clippingWith: aRect do: aBlock
    "  It is more convenient to check the intersection
       of two clipping rectangles here than each time
       the #clippingTo:do: is sent.  "
     | saveClip |
   (clippingBox intersects: aRect)
      ifFalse: [^self].
    saveClip := clippingBox.
    clippingBox := aRect intersect: saveClip.
    aBlock value.
    clippingBox := saveClip

The really interesting things are done in method visibleAreas:

visibleAreas
    "  return a collection of reactangles that
       cover the entire visible area of the
       insetDisplayBox. "
    | visibleAreas rect remnants myTopController |
   myTopController := self topView controller.
   self topView isCollapsed
     ifTrue: [^#()].
   visibleAreas := Array with: self insetDisplayBox.
   ScheduledControllers restoresFromBack
     ifTrue: [^visibleAreas].
   ScheduledControllers scheduledWindowControllers
    do: [:c |
          c == myTopController ifTrue: [^ visibleAreas].
          c isClosed not & c isInvisible not
            ifTrue:
              [rect := c view windowBox.
               remnants := OrderedCollection new.
               visibleAreas 
                  do: [:a | remnants addAll: (a areasOutside: rect)].
               visibleAreas := remnants.
               visibleAreas isEmpty
                 ifTrue: [^visibleAreas]
              ].
        ].
   ^visibleAreas

Here we process all scheduled controllers until we find the top controller of our window's top view. All controllers that precede that top controller belong to views that a placed before our window's top view; these views can cover parts of our view. Starting with our inset display box, we take the view frames one by one and, for each view frame, compute the collection of all visible rectangles outside the view frame. We end with a - possibly empty - collection of rectangles that describes exactly those parts of the inset display box that are not occluded by other views.

It is helpful to explain the most important statements of method visibleAreas one by: one:

myTopController := self topView controller.

This statement searches the controller of our window's top view. Such a controller always exists and it is always known to the window manager.

self topView isCollapsed
  ifTrue: [^#()].

For a collapsed top window, the collection of visible areas of a subview is empty.

visibleAreas := Array with: self insetDisplayBox.

As long as we did not find a window that covers parts of the display area of our view, we have to assume that the entire inset display box is visible. The inset display box is therefore the correct initial value for the visible area. For generality it is put into an array.

ScheduledControllers restoresFromBack
  ifTrue: [^visibleAreas].

This is something very special: Under some conditions (when Smalltalk is started, when a project is entered, when the user selects the option 'restore display') the control manager redisplays all views from the background to the foreground. Under this display policy, a view is completely visible when it is redrawn. The method restoresFromBack is used to enquire the manager's display policy. The value true indicates recreation of all views from back to front. The computation of visible areas is then not required and would even give wrong results.

ScheduledControllers scheduledWindowControllers
  do: [:c |
        c == myTopController ifTrue: [^visibleAreas].
        c isClosed not & c isInvisible not
          ifTrue:
            [rect := c view windowBox.
             remnants := OrderedCollection new.
             visibleAreas 
               do: [:a | remnants addAll: (a areasOutside: rect)].
             visibleAreas := remnants.
             visibleAreas isEmpty
               ifTrue: [^visibleAreas]
            ].
       ].
^visibleAreas

This loop iterates over all scheduled window controllers that are placed in front of our window. It computes the collection of visible areas. Four details are worth being commented:

The method visibleAreas is very general, it could be moved to the instance protocol of View.

A peculiarity in the update: method of DiagramDisplayView is also worth being explained: We will sometimes refresh the view content when the top view is not active. A deactivated top view can have a bitmap cache and we have to drop this cache before we repaint the view content. This is done in the update: method:

update: aSymbol
 aSymbol = aspect
   ifTrue:
     [self topView uncacheBits.
      self displayView.]
   ifFalse:
     [super update: aSymbol].

DiagramDisplayView uses MouseMenuController as its default controller class. This controller is needed to bring up a menu. To use this controller, the view has to implement the method getMenu::

getMenu: aBoolean
  ^model perform: menuAccessor with: self.

The menu is requested from the model. The model creates a situation-dependent SelectionMenu:

diagramMenu: aGraphView
  | labels selectors |
  labels := WriteStream on: (Array new: 2).
  selectors := WriteStream on: (Array new: 2).
  parameterChooser isNil
    ifTrue:
      [labels nextPut: 'open parameter view'.
       selectors nextPut: #openParameterChooser]
    ifFalse:
      [labels nextPut: 'close parameter view'.
       selectors nextPut: #closeParameterChooser].
  colorChooser isNil
    ifTrue:
      [labels nextPut: 'open color view'.
       selectors nextPut: #openColorChooser]
    ifFalse:
      [labels nextPut: 'close color view'.
       selectors nextPut: #closeColorChooser].

  ^SelectionMenu labels: labels contents
                 selections: selectors contents.

This menu contains two options - one for each supportive window. When a supportive window is not present, an option is offered to create it, otherwise, an option is offered to close it.

The methods are very similar for both supportive windows. It is sufficient to look at the methods that open and close the parameter chooser utility:

openParameterChooser
 
  parameterChooser := (DiagramParameterChooser for: self)
                             createWindow.
  switch1 set.
  parameterChooser controller open

When a chooser window is created, it receives the identity of the support requestor which it stores in an instance variable. The instance variable parameterChosser of the support requestor stores the created window. The statement switch1 set is only needed because it is possible to open and to close a supportive window with a switch. When the chooser window is created and the switch updated, we open the new window with the message open, sent to the view controller.

closeParameterChooser
    | window |
  switch1 clear.
  window := parameterChooser.
  parameterChooser := nil.
  window controller closeAndUnscheduleNoTerminate.

First of all, we tell the switch that it should change its state to clear to reflect the fact that the chooser window is not available. Next we have to remove the reference from to the chooser window that is kept in instance variable parameterChooser. Finally we close the chooser window. A temporary variable is used because we need a reference to the window after assignment to the instance variable.

The instance protocol of the chooser window is very simple, but some details are worth being mentioned:

Instance initialization is done with this method, which is called from class method for::

forClient: c
  client := c.
  parameter1 := client parameter1.
  parameter2 := client parameter2.

The instance asks its support receiver for the currently selected parameters.

When the user selects a value, the chooser window informs its support receiver:

selectP1: idx
    " store the seletion and inform the support receiver "
  parameter1 := idx + 1.
  client setParameters: parameter1 andParameter2: parameter2

Here is what the support receiver does:

setParameters: a andParameter2: b
  p1 ~= a | (p2 ~= b)
    ifTrue:
      [p1 := a.
       p2 := b.
       self changed: #drawFor:].

It is possible to close a supportive window. This is an activity that we cannot do without telling the support receiver what happens. The top view of a chooser window uses a specialized controller, SystemViewController that sends the message windowWillClose to its model when the window is closed. (The message windowIsClosing, that is sent anyway, comes to late to be useful.) Upon reception of this method, the chooser window can tell its support receiver what is going to happen:

windowWillClose
  client helperIsAboutToClose: self.

The support receiver does the necessary cleanup:

helperIsAboutToClose: aModel

  (parameterChooser notNil and: [parameterChooser model == aModel])
    ifTrue:
      [parameterChooser := nil. switch1 clearSilent.].
  (colorChooser notNil and: [colorChooser model == aModel])
    ifTrue:
      [colorChooser := nil. switch2 clearSilent.].

The helper is identified and the instance variables are updated.

To complete the picture, we mention that MultipleWindowApplication also has a top view with controller SystemViewController and that it also implements the method windowWillClose:

windowWillClose
  parameterChooser notNil
    ifTrue: [parameterChooser controller closeAndUnscheduleNoTerminate].

  colorChooser notNil
    ifTrue: [colorChooser controller closeAndUnscheduleNoTerminate].

Here all currently open supportive windows are closed. This is necessary because a supportive window is useless once it support receiver was closed.

Additional hints:


Previous
Contents
Next