Previous
Contents
Next

Advanced Programming Techniques for MVC

Drawing on the Backup Form


Alternative Display Policy

When the visible area of the inset display rectangle is decomposed into many rectangles, the model computes the points of the line to be diagrammed many times. It was already mentioned that, under certain circumstances, it may be better to draw the diagram once into a form. Let us look at this alternative in greater detail:

The change in class DiagramDisplayView is very simple: In method displayView the model is asked to do all the work.

displayView
  model perform: aspect with: self

There are two changes in the model class MultipleWindowApplication. The drawing method of the model asks the view to compute the collection of visible areas. Once this collection is known, the model decides how to proceed: For a small number of visible areas, it draws directly on the screen, for a larger number, in draws into a form and copies parts of that drawing into the rectangles of the visible area.

drawFor: aView
   | va form origin |
 va := aView visibleAreas.
 va size <= 1
   ifTrue:
     [va do:
         [:rect |  
           Display clippingWith: rect
                   do: [self drawOn: Display
                             into: aView insetDisplayBox]
         ].
     ]
   ifFalse:
     [form := Form extent: aView insetDisplayBox extent
                    depth: Display depth.
      self drawOn: form into: form boundingBox.
      origin := aView insetDisplayBox origin negated.
      va do:
         [:rect | Display copy: (rect translateBy: origin)
                          from: form
                          to: rect origin
                          rule: Form over
         ].
     ]

The draw method is renamed and slightly generalized; it can now draw both on the Display and on a form.

drawOn: aForm into: box
  | drawBox pen delta t x y xi yi first nroOfPoints |

aForm fill: box
      fillColor: Color white.
drawBox := box insetBy: 8.
pen := Pen newOnForm: aForm.
pen color: lineColor.
  
nroOfPoints := 600.
delta := Float pi * 2 / nroOfPoints.
t := 0.0.

first := true.

nroOfPoints + 1 timesRepeat:
  [x := (p1*t) sin + 1.
   y := (p2*t) cos + 1.
   xi := (drawBox width - 1*x/2) rounded.
   yi := (drawBox height - 1*y/2) rounded.
   t := t + delta.
   first ifTrue:
     [pen place: xi @ yi + drawBox origin.
      first := false]
   ifFalse: [pen goto: xi @ yi + drawBox origin.]
  ]

This display policy can remarkably reduce the time needed to refresh the view, but it comes at a price: For a large inset display box and high color depth, the use of an auxiliary form requires a lot of additional memory. To save memory, it is an tempting idea to draw not on a new form, but to use the window backup form if there is one. This requires again some changes, but the result is certainly worth the effort.

Changes in DiagramDisplayView:

In update:, we do not drop the display cache, because we will use it.

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

Method displayView has now the responsibility to select the best drawing policy. To make a decision, it checks for the availability of a display cache and for the number of rectangles in the visible area.

displayView

    | va cache form box offset |
va := self visibleAreas.
va isEmpty ifTrue: [^self].
cache := self topView windowBits.

cache isNil
  ifTrue:
    [va size = 1
       ifTrue:
         [Display clippingWith: va first
                  do: [model perform: aspect 
                             with: Display
                             with: self insetDisplayBox.
                      ].
          ^self
         ]
       ifFalse:
         [form := Form extent: self insetDisplayBox extent
                       depth: Display depth.
          box := form boundingBox.
          offset := self insetDisplayBox origin negated.
         ].
    ]
  ifFalse:
    [form := cache.
     box := self insetDisplayBox origin - self topView windowBox origin
               extent: self insetDisplayBox extent.
     offset := self topView windowBox origin negated.
    ].    
model perform: aspect
         with: form
         with: box.

va do:
   [:rect |
     Display copy: (rect translateBy: offset)
             from: form
             to: rect origin
             rule: Form over
   ].

Changes in MultipleWindowApplication:

The model has to provide a drawing method with two parameters. A technical detail is very important: When we draw on the display cache form, we have to ensure that all drawing activities are restricted to the inset display box of the view to be painted. The display cache is a common cache for all views of a window and without a properly set clipping rectangle, we can easily damage the cached images of other views.

drawOn: aForm into: box
  | drawBox pen delta t x y xi yi first nroOfPoints |

  aForm fill: box
        fillColor: Color white.
  drawBox := box insetBy: 8.
  pen := Pen newOnForm: aForm.
  pen color: lineColor.
    " for a form, ensure that the pen can draw
      only within the inset display box of the view: "
  aForm class = DisplayScreen
    ifFalse: [pen clipRect: box].

  nroOfPoints := 600.
  delta := Float pi * 2 / nroOfPoints.
  t := 0.0.
  first := true.

  nroOfPoints + 1 timesRepeat:
   [x := (p1*t) sin + 1.
    y := (p2*t) cos + 1.
    xi := (drawBox width - 1*x/2) rounded.
    yi := (drawBox height - 1*y/2) rounded.
    t := t + delta.
    first
      ifTrue:
        [pen place: xi @ yi + drawBox origin.
         first := false]
      ifFalse: [pen goto: xi @ yi + drawBox origin.]
   ]

The name of this method must be used as aspect of the view:

  drawing :=
      DiagramDisplayView new
           model: model;
           aspect: #drawOn:into:;
           menu: #diagramMenu:;
           borderWidth: 1;
           window: (0 @ 0 extent: 200 @ 300).

The aspect must also be used in all methods that notify a change that requires an action from the side of the DiagramDisplayView:

setParameters: a andParameter2: b
  p1 ~= a | (p2 ~= b)
    ifTrue:
      [p1 := a.
       p2 := b.
       self changed: #drawOn:into:].
setLineColor: aColor
  lineColor ~= aColor
    ifTrue:
      [lineColor := aColor.
       self changed: #drawOn:into:].

The change set MultiWindowDemo2.cs contains the complete example with all modification explained so far.


Previous
Contents
Next