W$TEXTSIZE
The W$TEXTSIZE library routine measures the height and the width of a text.
Syntax:
 CALL "W$TEXTSIZE" USING textString
                         TEXTSIZE-DATA
Parameters:
textString
PIC X(n)
Specifies the text to be measured.
TEXTSIZE-DATA
group item
This group item, defined in isgui.def, has the following structure:
 
01  textsize-data.
    03 textsize-font             handle of font value null.
    03 textsize-window           handle of window 
                                 value null.
    03 textsize-size-x           pic 9(7)v99 comp-4.
    03 textsize-cells-x          pic 9(7)v99 comp-4.
    03 textsize-base-x           pic 9(9comp-4.
    03 textsize-size-y           pic 99v99 comp-4.
    03 textsize-cells-y          pic 99v99 comp-4.
    03 textsize-base-y           pic 9(4comp-4.
    03 textsize-flags            pic x comp-x value zero.
       88 textsize-strip-spaces  value 1 false zero.
 
textsize-font
Specifies the handle of the font used to measure the text specified in textString.
Note: if the font has been loaded with wfont-angle different than zero, results are unpredictable. Rotated fonts should not be used for cell measurement.
 
textsize-window
Specifies the handle of the window used to measure the text specified in textString. This is necessary to return the size of the text in cells. If this member is zero, the current window is used.
 
textsize-size-x
Receives the width of textString, expressed in columns. A column is the width of the character "0" (zero) when drawn with the font specified in textsize-font.
 
textsize-cells-x
Receives the width of textString, expressed in window's cells. Cells refer to the window pointed by textsize-window.
 
textsize-base-x
Receives the width of textString, expressed in pixels.
 
textsize-size-y
Receives the height of textString, expressed in lines. A line is the height of the character "0" (zero) when drawn with the font specified in textsize-font.
 
textsize-cells-y
Receives the height of textString, expressed in window's cells. Cells refer to the window pointed by textsize-window.
 
textsize-base-y
Receives the height of textString, expressed in pixels.
 
textsize-flags
It specifies if trailing spaces found in textString are relevant to the measurement.
 
When the textsize-strip-spaces condition is set to true, trailing spaces not measured. When it is set to false, trailing spaces are measured.
Examples:
Example - retrieve cell dimensions on the current window with default font
working-storage section.
77  hWin          handle of window.
77  text-string   pic x(20).
77  h-font        handle of font.  
 
procedure division.
main.
   display independent graphical window                   
           color  65793
           with   system menu
           title  "W$TEXTSIZE Routine"
           handle hWin.
   accept h-font from standard object "default-font"
   ...
 
   move hWin   to textsize-window
   move h-font to textsize-font
   set textsize-strip-spaces to true
   inquire event-control-handle value in text-string
   call "W$TEXTSIZE" using text-string, textsize-data
   display message textsize-size-x  "  "
                   textsize-cells-x   "  "
                   textsize-base-x  "  "
                   textsize-size-y  "  "
                   textsize-cells-y  "  "
                   textsize-base-y.