27 Displaying and manipulating graphical objects

So far, we have seen that fudgets can display text, but we have not seen how to create and display other kinds of graphical objects. (You might have wondered how button borders are drawn, for example.) In the first few sections of this chapter we present data types, type classes and fudgets for handling graphics.

Structure editors of various kinds are programs that can make good use of graphics. Examples of such programs are drawing programs, WYSIWYG word processors, file managers, etc. The common characteristic is that they allow you to manipulate a graphical representation of some object on the screen, for example, by selecting a part of the object and performing some editing operation on it (for example, making a word italic in a word processor, or deleting a file in a file manager). The editing operations performed by the user can lead to marginal or radical changes to the structure of the object and its graphical representation. The editor will need to have an efficient mechanism for updating the screen to reflect these changes. The fudget for graphics that we describe in this chapter supports this.

The Fudget library components we have seen so far allow you to build user interfaces that consist of a number of parts that communicate, but we have not seen any mechanisms that allow an arbitrary part to be selected by the user and perhaps replaced by something else, so we have not seen a general mechanism for building structure editors. Some basic fudgets, like toggleButtonF and stringF can be seen as structure editors for particular structures (booleans and strings, respectively). The later sections in this chapter present data types and fudgets that can be used as a starting point when building more general structure editors. In Chapter 28 we go on and describe combinators more directly aimed at building structure editors, or syntax directed editors.

The support for graphics in the Fudget library was prompted by the development of the syntax directed editor Alfa (Chapter 33), and functionality was added to the fudget system as needed for that particular purpose. Some development was also prompted by the work on the web browser described in Chapter 32.

27.1 The class Graphic

We have already encountered the class Graphic many times. Many of the GUI fudgets presented in Chapter 9 display graphics. Recall, for example, buttonF:

buttonF :: (Graphic a) => a -> F Click Click
It has an argument that determines what is displayed inside the button. In early versions of the Fudget library, the type of buttonF was

buttonF :: String -> F Click Click
but later, the class Graphic was introduced and many fudgets were generalised from displaying only strings to displaying arbitrary graphical objects. Since the new types are more general than the old ones, the changes are backwards compatible (old programs continue to work unmodified).(Footnote: This kind of change can actually cause ambiguous overloading.)

The Graphic class serves a purpose similar to that of the Show class: types whose values have graphical representations are made instances of the Graphic class, just like types whose values have textual representations are instances of the Show class. As with the Show class, the methods of Graphic class are not often used directly, except when defining new instances, and we discuss them in a later section. The library provides instances in the Graphic class for many standard types.

27.2 Primitive drawing operations

Before we describe the data types that are instances of the Graphic class, we take a look at the low-level interface that allows a fudget to draw something in its window.

The Fudgets GUI toolkit is built on top of the Xlib [Nye90] library level of the X Windows system [SG86] (as described in Section 22.1). This shines through in the Fudget library support for graphics: the primitive drawing operations available in the fudget library correspond directly to what is provided by Xlib.

An interface to the Xlib library calls for drawing geometrical shapes and strings is provided through the data type DrawCommand shown in Figure 63.

data DrawCommand
    =  DrawLine Line
    |  DrawImageString Point String
    |  DrawString Point String
    |  DrawRectangle Rect
    |  FillRectangle Rect
    |  FillPolygon Shape CoordMode [Point]
    |  DrawArc Rect Int Int
    |  FillArc Rect Int Int
    |  CopyArea Drawable Rect Point
    |  CopyPlane Drawable Rect Point Int
    |  DrawPoint Point
    |  CreatePutImage Rect ImageFormat [Pixel]
    |  DrawLines CoordMode [Point]
    ...

Figure 63. The type DrawCommand provides an interface to the Xlib library calls for drawing geometrical shapes and strings.

Apart from the parameters describing the shape to be drawn, the Xlib calls have some additional parameters that are not present in the constructors of the DrawCommand type. As a typical example of the relationship between the Xlib calls and the constructors, consider XDrawLine:

XDrawLine(display, d, gc, x1, y1, x2, y2)
Display *display;
Drawable d;
GC gc;
int x1, y1, x2, y2;
A drawable d (a window or a pixmap) and a graphics context gc are supplied by the fudget that outputs the drawing command. The type XCommand (see Section 22.1.1) contains the following constructor for outputting drawing commands:

data XCommand = ... | Draw Drawable GCId DrawCommand | ...
The display argument can be determined from the drawable. (The current Fudget library supports only one display connection, so nothing extra is needed for this.)

27.3 Types for simple graphical objects

Having seen how a fudget can output drawing commands to draw in its window, we can now take a look at some simple types for graphical objects. These types provide the most low-level interface to the Xlib drawing commands.

27.3.1 BitmapFile

Apart from the drawing commands supported through the type DrawCommand, the Fudget library also supports the Xlib library call XReadBitmapFile for reading images (bitmaps) from files:

data XRequest   = ... | ReadBitmapFile FilePath | ...
data XResponse  = ... | BitmapRead BitmapReturn | ...

data BitmapReturn = BitmapBad | BitmapReturn Size (Maybe Point) PixmapId
This means that we can easily create a data type that allows us to use images stored in files as graphical objects.

data BitmapFile = BitmapFile FilePath

instance Graphic BitmapFile where ...
As you can see in Figure 64, by using the type BitmapFile, a program that loads an image from a file and displays it is as just as simple as the "Hello, world!" program (see Section 9.1):
import Fudgets

main = fudlogue (shellF "Hello" helloF)
helloF = labelF (BitmapFile "hello.xbm")

Figure 64. The graphical version of the "Hello, world" program is just as simple as the textual version in Section 9.1.

27.3.2 FlexibleDrawing

The Fudget library provides the following type to create stretchable graphical objects:

data FlexibleDrawing = FlexD Size Bool Bool (Rect -> [DrawCommand])

instance Graphic FlexibleDrawing where ...
The first argument of the FlexD constructor indicates a nominal size, but the actual size is determined by the fudget layout system and depends on the context. The next two arguments indicate the stretchiness, that is, whether the size should be fixed horizontally and vertically, respectively.

The last argument is a function that should produce drawing commands that draw within the given rectangle. The argument is a rectangle rather than just a size to make flexible drawings more efficient to use as parts of structured graphical objects. Although the drawing function could draw completely different things for different rectangle position and sizes, changing the position is expected to have no other effect than a translation, that is,

f (Rect pos size) = moveDrawCommands (f (Rect origin size)) pos
where moveDrawCommands,

moveDrawCommands :: [DrawCommand] -> Point -> [DrawCommand]
moves (translates) drawing commands. Changing the size is expected make the function adjust the drawing to fill the available space, typically by stretching it.

As an example, here are flexible drawings for filled rectangles, horizontal lines and vertical lines:

filledRect, hFiller, vFiller :: Int -> FlexibleDrawing

filledRect = filler False False
hFiller = filler False True
vFiller = filler True False
filler fh fv d = FlexD (Point d d) fh fv (\r->[FillRectangle r])
A sample usage can be seen in Figure 66.

27.3.3 Fixed size drawings

Having defined the type FlexibleDrawing, we can easily define a function for creating graphical objects of a fixed size:

fixedD :: Size -> [DrawCommand] -> FlexibleDrawing
fixedD size dcmds = FlexD size True True drawit
  where drawit (Rect pos _) = moveDrawCommands dcmds pos
The arguments are a list of drawing commands to draw the desired shape and a size. The commands are expected to draw within a rectangle of the indicated size, with the origin as the upper left corner.(Footnote: Instead of leaving it to the user to indicate the size of the drawing, it would be possible to compute a bounding rectangle by inspecting the drawing commands, but doing it accurately in the general case is rather involved and would be less efficient.)

Notice that depending on how you define your FlexibleDrawing value, you may get very different operational behaviour. Using fixedD, you will get a value containing a reference to a list of drawing commands that will be retained in the heap and translated to the appropriate position (by moveDrawCommands) each time the drawing is used. For FlexibleDrawings created like filler above, the drawing commands may be recomputed and thrown away each time the drawing is used. So, although the result on the screen will be the same, how much recomputation that occurs and how much memory is used depends on details in how the program is written and what kind of lambda lifting the compiler does (whether it supports full laziness [Kar92]).

27.4 Types for structured graphical objects

The types for graphical objects presented above lack two important features:As discussed in the introduction of this chapter, we also need a way to identify parts of a composite graphical object when building structure editors. We introduce the type Drawing to take care of these needs.

data Drawing label leaf
  =  AtomicD    leaf
  |  LabelD     label   (Drawing label leaf)
  |  AttribD    GCSpec  (Drawing label leaf)
  |  SpacedD    Spacer  (Drawing label leaf)
  |  PlacedD    Placer  (Drawing label leaf)
  |  ComposedD          [Drawing label leaf]

instance Graphic leaf => Graphic (Drawing label leaf) where ...

placedD :: Placer -> [Drawing l a] -> Drawing l a
placedD p ds = PlacedD p (ComposedD ds)
So, composite drawings are trees. The leaves (built with the constructor AtomicD) can contain values of any type, but as seen from the instance declaration above, the drawing can be displayed only if the leaf type is an instance of the Graphic class. The internal nodes can contain:Since the Drawing type is an instance of the Graphic class, drawings can be displayed by GUI fudgets that create labels, buttons, menus, displays and so on. There is also a fudget that makes use of the properties of the Drawing type:

hyperGraphicsF :: (Eq lbl, Graphic gfx) =>
                  Drawing lbl gfx -> F (lbl, Drawing lbl gfx) lbl
It displays a drawing, with labels in it. When you click on a point in a drawing, the fudget outputs the label of the smallest part containing the point where you clicked. You can replace a part by feeding a pair of a label and a new drawing to the fudget. hyperGraphicsF can thus be the starting point for simple graphical browsers and editors.

27.4.1 Manipulating drawings

Some functions to manipulate parts of drawings are shown in Figure 65. These can be used in the implementation of structure editors. Values of type DPath identify parts of drawings.
type DPath = [Int]

up :: DPath -> DPath

drawingPart :: Drawing a b -> DPath -> Drawing a b
maybeDrawingPart :: Drawing a b -> DPath -> Maybe (Drawing a b)
updatePart :: Drawing a b -> DPath -> (Drawing a b -> Drawing a b) -> Drawing a b
mapLabelDrawing :: (a -> b) -> Drawing a c -> Drawing b c
mapLeafDrawing :: (a -> b) -> Drawing c a -> Drawing c b
drawingLabels :: Drawing a b -> [(DPath, a)]
deletePart :: Drawing a b -> DPath -> Drawing a b
...

Figure 65. Some functions for manipulating parts of drawings.

27.4.2 Mixing graphical objects of different types in one drawing

In a Drawing, all the leaves must have the same type. Although you could draw anything using only leaves of type FlexibleDrawing, it would be more convenient to be able to mix different types of leaves. For this purpose, the Fudget library provides the following type that makes use of existentially quantified types [LO92]:

data Gfx = (Graphic ?a) => G ?a

instance Graphic Gfx where ...  -- trivial

g :: Graphic a => Drawing lbl Gfx
g = AtomicD . G
In the definition of Gfx, ?a is an existentially quantified type variable. The context (Graphics ?a) => limits the domain of the variable to the types in the Graphic class. The result is that the constructor G can be applied to a value of any type in the Graphic class, yielding a value of type Gfx. When you later use pattern matching to extract the argument of G, you will not know what type it has, but you will know that the type is in the Graphic class, so you can apply the methods of that class on it. So, making Gfx an instance of the Graphic class becomes trivial. (The instance declaration is shown in Figure 71).

An example where strings and a FlexibleDrawing are mixed in a Drawing is shown in Figure 66.

placedD verticalP [SpacedD centerS (g "1"),
                   g (hFiller 1),
                   g "x+y"]

Figure 66. A sample drawing with leaves of different types.

The use of existential types gives us a way of packaging data with the methods that operate on it and abstract away from the concrete representation of the data. This is reminiscent of how data abstraction is achieved in object-oriented programming. (The reader is referred to [CW85] for a fuller discussion of the relation between existential types, data abstraction and object-oriented programming.)

27.4.3 Drawing attributes

Most of the Xlib drawing commands have an argument of type GC, a graphics context. This is a data structure containing the values of a number of parameters that affect the result of the drawing commands, but which would be tiresome to have to pass explicitly as arguments every time you draw something. Examples of such parameters, or attributes, are:Most of these attributes are specified by numbers or elements of enumeration types, but colors and fonts are more troublesome. Colors can be specified using, e.g., color names or RGB values, but before a color can be used in a GC it must be converted to a pixel value. Depending on the visual type of the display, a pixel value can be, e.g., an 8-bit index into a 256 element colormap (for 8-bit PseudoColor displays) or RGB information packed into 16 or 24 bits (for 16-bit and 24-bit TrueColor displays, respectively).

Fonts can be specified by font names, but before they can be used, they have to be converted to font identifiers. Also, if you want to know how much space the text you draw will take up, you need obtain a data structure containing metric information on the font.

The data types provided by the Fudget library for specify drawing attributes are shown below. The types ColorSpec and FontSpec are described further in the next section.

data GCSpec
  =  SoftGC [GCAttributes ColorSpec FontSpec]
  |  HardGC GCtx

data ColorSpec -- see below
data FontSpec -- see below

data GCAttributes color font
  =  GCFunction GCFunction
  |  GCForeground color
  |  GCBackground color
  |  GCLineWidth Width
  |  GCLineStyle GCLineStyle
  |  GCFont font
  |  GCCapStyle GCCapStyle
  |  GCFillStyle GCFillStyle
  |  GCTile PixmapId
  |  GCStipple PixmapId
  ...

data GCtx = GC GCId FontStruct

data FontStruct -- abstract type for font metric info
data GCId -- An Xlib GC
type Width = Int

data GCFunction = GXclear | GXand | GXandReverse | GXcopy | ... | GXset 
data GCLineStyle = LineSolid | LineDoubleDash | LineOnOffDash
data GCCapStyle = CapNotLast | CapButt | CapRound | CapProjecting
data GCFillStyle = FillSolid | FillTiled | FillStippled | FillOpaqueStippled
To include drawing attributes in a Drawing (defined above), you use the constructor AttribD applied to a GCSpec, which usually is the constructor SoftGC applied to a list of attributes containing high-level specifications of fonts and colors. However, before the drawing can be displayed, this high-level specification must be converted into a GC. In addition, to be able to automatically determine the size of text, the metric information for the specified font is required. The high-level drawing attributes are therefore converted into a value of type GCtx by fudgets that display drawings. This conversion may require calls to Xlib library functions like XLoadQueryFont, XAllocNamedColor and XCreateGC. For drawings that are to be displayed many times, making these calls every time can cause a noticeable performance degradation, so the library provides a way to create GCtx values in advance. These can then be included in drawings using GCSpecs with the constructor HardGC. The drawing can then be displayed without making any calls except for the necessary drawing commands. The reason for choosing the names SoftGC and HardGC is that the subdrawings of a node setting the drawing attributes using the SoftGC alternative, inherit the attributes not present in the GCAttributes list from the parent drawing, whereas with the HardGC alternative, all attributes are taken from the given GCtx.

27.4.4 Specifying fonts and colors

To allow fonts and colors to be specified conveniently in different ways, we have introduced the following types and classes:

class ColorGen a where ...
data ColorSpec -- an abstract type
colorSpec :: ColorGen a => a -> ColorSpec

class FontGen a where ...
data FontSpec -- an abstract type
fontSpec :: FontGen a => a -> FontSpec
The following types are instances of the ColorGen class and can be used to specify colors:

type ColorName = String -- color names, as used by Xlib

data RGB = RGB Int Int Int -- RGB values, as used by Xlib

data Pixel -- previously obtained pixel values
Values of the RGB type specifies the intensities of the primary colors red, green and blue, using 16-bit integers. RGB 0 0 0 is black, and RGB 65535 65535 65535 is white.

The following types are instances of the FontGen class and can be used to specify fonts:

type FontName = String -- font names as used by Xlib

data FontStruct -- a previously obtained FontStruct
The canonical way of including font and color specifications in a drawing is to do something like this:

blueHelloMsg =
   AttribD (SoftGC [GCForeground (colorSpec "blue"),
                    GCFont (fontSpec "-*-times-*-r-*-18-*")]),
           (g "Hello, world!")
As you can see, this is rather clumsy, so the Fudget library provides the following, more convenient functions:

bgD, fgD ::  ColorGen color =>
             color -> Drawing lbl leaf -> Drawing lbl leaf

fontD ::  FontGen font =>
          font -> Drawing lbl leaf -> Drawing lbl leaf
Using these, you can write the above example like this:

blueHelloMsg = fgD "blue" $ fontD "-*-times-*-r-*-18-*" $
               g "Hello, world!"

27.4.5 Allocating colors and fonts in advance

As mentioned above, you might for efficiency reasons want to allocate colors and fonts in advance, and include the resulting GCtx values in the drawings you construct. For this purpose, the Fudget library provides the following:

wCreateGCtx :: (FontGen b, ColorGen a) =>
               GCtx -> [GCAttributes a b] -> (GCtx -> F c d) -> F c d

rootGCtx :: GCtx
The function wCreateGCtx allows you to create GCtx values, by modifying a template GCtx. You can start from rootGCtx which contains the default settings for all attributes.

27.5 Implementation

How should a fudget that displays Drawings be implemented? Drawings are trees, composed from leaves containing simple graphical objects, using placers and spacers from the ordinary fudget layout system. A natural solution thus seems to be to implement new fudgets for displaying simple graphical objects and then display composed drawings by composing fudgets that display the leaves. While this at first seems like a simple and elegant solution that gives us maximal reuse of existing Fudget library components, remember that we not only want to display drawings: to build structure editors we also need a mechanism that lets the user select and manipulate parts of a structure. We would need to set up a structure where every node in a Drawing is represented by a fudget, and a communication structure which allows us to communicate which each node fudget. Further, in order to be able to replace arbitrary nodes with new drawings, we would have to use the combinator dynF (Section 13.4) at each node.

dynF :: F a b -> F (Either (F a b) a) b
We tried this approach, but when taking all requirements into account, this seemingly natural solution became rather tricky. It also turned out to be rather inefficient and there are several possible reasons for this:As a result, we have developed another solution that is now part of the Fudget library. It uses one fudget, graphicsF, to display complete drawings in one window. This has proved to be reasonably efficient. It has allowed us to implement usable, non-trivial applications, the syntax directed editor Alfa (Chapter 33) and the web browser WWWBrowser (Chapter 32) being the largest. A drawback is that some functionality (most notably hit detection and clipping) that in principle could be handled by the window system (and it was in the ``natural'' solution) had to be duplicated in the implementation of graphicsF. The fudget graphicsF could actually be seen as an implementation of a simple window system!

27.5.1 The capabilities of graphicsF

Since graphicsF is intended to satisfy all the needs for displaying graphics within the Fudget library, and also be the ground on which applications like syntax directed editors and web browsers can be built, it has been made fairly general. In addition to just displaying graphics, graphicsFThe type of graphicsF is:

graphicsF :: (Graphic a) => F (GfxCommand a) GfxEvent
The definitions of the message types GfxCommand and GfxEvent are show in Figure 67. The constructor ChangeGfx creates messages that allow you to replace or modify the graphical object being displayed. The argument is a list of changes. Each change has the form

(path,(hilite,opt_repl))
where path selects which part of the object should be changed, hilite switches on or off highlighting and opt_repl is an optional replacement for the selected part.

graphicsF is actually a simplification of graphicsGroupF,

graphicsGroupF :: (Graphic gfx) => 
                  (F a b) -> F (Either (GfxCommand gfx) a) 
                               (Either GfxEvent b)
which like groupF, discussed in Section 22.1.2, can contain subfudgets. The fudget activeGraphicsF (discussed in Section 32.3) for displaying drawing with active parts (for example forms in a web browser) is built on top of graphicsGroupF.

There are also customisable versions of these fudgets, allowing you to change parameters like the event mask, border width and resizing policy.

data GfxCommand gfx
  =  ChangeGfx [(DPath,(Bool,Maybe gfx))]
  |  ChangeGfxBg ColorSpec
  |  ChangeGfxBgPixmap PixmapId Bool -- True = free pixmap
  |  ShowGfx DPath (Maybe Alignment,Maybe Alignment)
     -- makes the selected part visible
  |  BellGfx Int -- sound the bell
  |  GetGfxPlaces [DPath] -- ask for rectangles of listed paths

data GfxEvent
  =  GfxButtonEvent { gfxState :: ModState,
                      gfxType :: Pressed,
                      gfxButton:: Button,
                      gfxPaths :: [(DPath,(Point,Rect))] }
  |  GfxMotionEvent { gfxState :: ModState,
                      gfxPaths :: [(DPath,(Point,Rect))] }
  |  GfxKeyEvent    { gfxState::ModState,
                      gfxKeySym::KeySym,
                      gfxKeyLookup::KeyLookup }
  |  GfxPlaces [Rect] -- response to GetGfxPlaces
  |  GfxResized Size

Figure 67. The message types used by graphicsF.

27.5.2 Implementation of graphicsF

The fudget graphicsGroupF is implemented using groupF:

graphicsGroupF subfudgets = groupF graphicsK subfudgets

graphicsK = ...
The behaviour of the fudget is thus implemented in the fudget kernel graphicsK. Here is roughly what graphicsK does in the course of displaying a graphical object.A shortcoming of current implementation of graphicsF is that it does not handle overlapping parts properly, not because overlapping parts would be too difficult to handle in the current solution, but simply because it has not been important in the applications where graphicsF has been used so far. This means that a drawing with overlapping parts can look different after part of it has been redrawn in response to an Expose event.

Finally, some sample instance declarations for the Graphic class are shown in Figure 71.

instance Graphic Gfx where
  measureGraphicK (G x) = measureGraphicK x

instance Graphic FlexibleDrawing where
  measureGraphicK (FlexD s fh fv drawf) gctx k =
    k (LeafM (plainLayout s fh fv) gctx drawf)
    -- plainLayout is defined in Section 27.6.2.

instance Graphic Char where
  measureGraphicK c = measureString [c]
  measureGraphicListK = measureString

instance Graphic a => Graphic [a] where
  measureGraphicK = measureGraphicListK

instance Graphic Int where        -- and similarly for other basic types
  measureGraphicK i = measureString (show i)

measureString s gctx@(GC gc fs) k =
  let r@(Rect _ size) = string_rect fs s
      d = font_descent fs
      a = font_ascent fs
      p1 = Point 0 a -- left end of base line reference point
      p2 = Point (xcoord size) a -- right end of base line ref point
      drawit (Rect p (Point _ h)) = [DrawString (p+(Point 0 (h-d))) s]
  in k (LeafM (refpLayout size True True [p1,p2]) gctx drawit)
    -- refpLayout is defined in Section 27.6.2.

Figure 71. Some sample instances for the Graphic class.

27.5.3 Efficiency issues in the implementation of graphicsF

As mentioned above, when part of a drawing is replaced, graphicsF recomputes the layout of the complete drawing. None of the old layout computations are utilised in this step. This may put an upper limit on how big objects can be handled with reasonable response times in a structure editor. A better solution would be to reuse layout information for parts that are not affected by a change. This is done in the ordinary fudget layout system (see Chapter 23).

Large drawings consist of many DrawCommands. Outputting these one at a time in low-level messages turned out to entail a considerable overhead. For example, redrawing the window after a page scroll in the editor Alfa (Chapter 33) in a typical situation could take 1 second. In an attempt to improve this, we added a new constructor to the XCommand type:

data XCommand = ...  | XDoCommands [XCommands] ...
It allows many commands to be passed in one low-level message, thus allowing all the DrawCommands needed to redraw a window to be passed in one message from graphicsF to the top level of the fudget hierarchy. The message passing overhead thus becomes negligible. Also, caches and other filters (see Chapter 24) that previously had to examine every DrawCommand now only examine one XDoCommands message (they do not look inside). This reduced the above mentioned redrawing time from 1 second to about 0.1 second, which makes a big difference from the user's point of view.

27.6 Extended layout mechanisms

In Chapter 11, we saw placers and spacers suitable for specifying the layout of GUI elements. However, to describe the layout of text in structured graphical objects fully and conveniently, two new features are needed:These two new features are provided through two new placers, alignP,

alignP :: Placer
which allows you to compose text with base line alignment, and paragraphP,

paragraphP :: Placer
which does line breaking.

To implement these, two extensions of the layout system were needed. Although they should still be considered to be in an experimental stage, we describe them below.

We also present the idea of conditional placers and spacers, which could be implemented without any extensions. These can be used, for example, to select between different layouts depending on the size of an object.

27.6.1 Reference points

To implement alignP, the layout requests (see Chapter 23) were extended to contain, in addition to the nominal size and the stretchiness, a list of reference points:
data LayoutRequest
  = Layout {  minsize :: Size,
              fixedh, fixedv :: Bool,
              refpoints :: [Point] }
The use of these appear in the Graphic instance for strings (see the function measureString in Figure 71).

alignP places the argument boxes so that the last reference point in one box coincides with the first reference point in the next box. This gives us base line alignment when composing text.

Unlike most other placers, alignP does not stretch the argument boxes. In fact, we have not included a mechanism for specifying how reference points are affected by stretching, so you may get odd layout if a box containing reference points is first stretched by one placer and then aligned with another box containing reference points by alignP.

We have also found use for some spacers that manipulate reference points:

refMiddleS, refEdgesS, noRefsS :: Spacer

moveRefsS :: Point -> Spacer
The spacer refMiddleS replaces the reference points of a box with two reference points placed on the middle of the left and right edges. refEdgesS takes the first and last reference points and moves them horizontally to the left and right edges, respectively. noRefsS removes the reference points from a box. moveRefsS displaces the reference points of a box by a given vector.

The placers and spacers we have presented do not make use of more than two reference points, so it perhaps seems more appropriate to have a pair (instead of a list) of reference points in the layout requests. One can also consider more elaborate use of reference points, for example, different placers might use different sets of reference points. To take a concrete example, when putting equations together horizontally in a comma separated list, you probably want to do base line alignment, but when placing equations in a vertical list, you may want them to appear with the = symbols on the same vertical line. Also, you may want the layout system to choose between horizontal and vertical placement depending on the available space, so the equations must contain reference points for both possibilities, and the placers must be able to choose between them.

27.6.2 Line breaking

The fudget layout system computes the layout in two steps: first a bottom-up pass collects the layout requests from the leaf boxes, giving the required size of the top-level window as a result. Based on this size, the exact placement of each box is computed in a top-down pass. The actual size of each box depends on the requested sizes of all boxes. The actual sizes can also be changed if the user resizes the shell window.

To display text with automatic line breaking, we would like the requested height to depend on the actual width. The line breaking should be redone when the width of the window is changed.

In the original fudget layout system, there was no way for a fudget to ask for a size where the requested height depends on the available width. A fudget could still achieve this behaviour: whenever notified of a size change, it could output a new request with the same width as in the notification but with a new height. Care of course had be taken to avoid generating infinite sequences of notifications and requests and other unpleasant effects. This solution was used in an early version of the web browser described in Chapter 32.

As part of the work on support for structured graphics, we developed a better solution to the line breaking problem. We extended the layout requests with a function that answers the question ``if you can be this wide, how tall do you want to be?''. For symmetry, there is also a function that allows the requested width to depend on the actual height (otherwise flipP would not work). The two functions are called wAdj and hAdj, respectively.

data LayoutRequest
  = Layout {  minsize :: Size,
              fixedh, fixedv :: Bool,
              refpoints :: [Point],
              wAdj, hAdj :: Int -> Size}
The placers now combine such functions in addition to combining nominal sizes and stretchiness. Although the old behaviour can be achieved by using constant wAdj/hAdj functions, the layout requests still contain the usual nominal size. This saves us from having to rewrite all placers and spacers. Also, the usual nominal size is still used rather than the wAdj/ hAdj functions on the top level in normal shell windows, while the wAdj function is used in vScrollF (see Section 10.7) , where the width is constrained but the height can vary freely. (Not surprisingly, hAdj is used in hScrollF.)

Changing the data type LayoutRequest meant that all occurrences of the constructor Layout in the Fudget library had to be adjusted. The functions plainLayout and refpLayout were introduced to simplify these adjustments:

plainLayout s fh fv = refpLayout s fh fv []
refpLayout s fh fv rps = Layout s fh fv (const s) (const s) rps

27.6.3 Conditional spacers and placers

Occasionally, we have found use for combinators that try alternative layouts and pick the best one according to some condition. We have implemented an ad hoc choice of such combinators:

ifSizeP  :: (Size->Size->Bool) -> Placer -> Placer -> Placer
ifSizeS  :: (Size->Size->Bool) -> Spacer -> Spacer -> Spacer

stretchCaseS :: ((Bool,Bool)->Spacer) -> Spacer

alignFixedS :: Alignment -> Alignment -> Spacer
The first two allow you to choose between two placers/spacers depending on the size of the resulting box, i.e., if placer1 and placer2 yield boxes of size1 and size2, respectively, then ifSizeP p placer1 placer2 uses placer1 if p size1 size2 is True, and placer2 otherwise. ifSizeS works analogously for spacers.

stretchCaseS allows you to write spacers that depend on the horizontal and vertical stretchiness of the argument box. alignFixedS is an application of stretchCaseS. It can be used to allow stretchable graphical objects to be stretched while objects of fixed size are aligned. As an example, when buttonF was generalised from displaying strings to arbitrary graphics, we switched from unconditionally centering the label with centerS to conditionally centering it with alignFixedS aCenter aCenter. This means that text labels will be centered as before, while graphical labels may be stretched.