WINPRINT-SET-PAGE-COLUMN

This operation code describes how the columns appear when printed.

Usage

CALL "WIN$PRINTER"
    USING WINPRINT-SET-PAGE-COLUMN, WINPRINT-COLUMN
    GIVING RESULT

Parameters

WINPRINT-COLUMN Group item defined in winprint.def as follows:
01  WINPRINT-COLUMN, SYNC.
    03  WINPRINT-COL-START              PIC 9(7)V99 COMP-5.
    03  WINPRINT-COL-INDENT             PIC 9(7)V99 COMP-5.
    03  WINPRINT-COL-SEPARATION         PIC 9(7)V99 COMP-5.
    03  WINPRINT-COL-FONT               HANDLE OF FONT.
    03  WINPRINT-COL-UNITS              PIC 99 COMP-X.
    03  WINPRINT-COL-ALIGNMENT          PIC X.
    03  WINPRINT-TRANSPARENCY           PIC 99 COMP-X.
        88  WINPRINT-TRANSPARENT        VALUE 1, FALSE 0.
    03  WINPRINT-COL-FONTCOLOR          PIC 9(9) COMP-5 SYNC.
    03  WINPRINT-COL-FONTCOLOR-NEG      PIC 9(9) COMP-5 SYNC.

        78  WPRTUNITS-CELLS                     VALUE 0.
        78  WPRTUNITS-INCHES                    VALUE 1.
        78  WPRTUNITS-CENTIMETERS               VALUE 2.
        78  WPRTUNITS-PIXELS                    VALUE 3.
        78  WPRTALIGN-NONE                      VALUE SPACE.
        78  WPRTALIGN-LEFT                      VALUE "L".
        78  WPRTALIGN-RIGHT                     VALUE "R".
        78  WPRTALIGN-CENTER                    VALUE "C".
        78  WPRTALIGN-DECIMAL                   VALUE "D".
        78  WPRTALIGN-DECIMAL-SUPPRESS          VALUE "S".

Description

This is one of three op-codes that control the output by specifying the page layout. (This is similar to the DISPLAY-COLUMNS property of the LIST-BOX control.)

Each column of data is mapped to an output column in the print record: the first data column maps to the leftmost output column, the second data column to the next output column to the right, and so on. Each time WINPRINT-SET-PAGE-COLUMN is used, a new output column is defined. To reset the output columns, use WINPRINT-CLEAR-PAGE-COLUMNS as described below. Once set, output columns remain in effect until explicitly cleared or the runtime process shuts down.

Note: Changing the output device will also reset the columns (this occurs if you use of any of these op-codes: WINPRINT-SETUP, WINPRINT-SETUP-USE-MARGINS, WINPRINT-SET-SETTINGS, WINPRINT-SET-PRINTER).

If you describe a new column that starts in exactly the same position as a previously described column, then the new column replaces the previous column definition (replacement detection is calculated using output device units).

The fields in WINPRINT-COLUMN define the output column. The fields have the following meaning:

  • WINPRINT-COL-START - Sets the leftmost point of the column on the page. The units of measurement are defined by WINPRINT-COL-UNITS. The measurement is made with respect to the left margin of the page. This position is calculated at the time that the column is defined. However, it is always relative to the left margin, so changing the left margin will shift the columns. The column ends at the beginning of the next column or the right margin if there is no next column.

    You may use this with WPRTUNITS-CELLS-ABS, WPRT-CENTIMETERS-ABS, or WPRTUNITS-INCHES-ABS to set the start position using an absolute value from the left edge of the paper.

  • WINPRINT-COL-INDENT - Modifies the left edge of the column by adding its value to the WINPRINT-COL-START value. The units of measurement are defined by WINPRINT-COL-UNITS. The indent is normally set to zero. You can use a non-zero value to specify an indented column in a convenient fashion. You would typically use this when you wanted to indent a column for a particular set of output lines. Otherwise, you would have to clear all the columns and redefine them in order to change the left edge of one column.
    Note: The values of WPRTUNITS-CENTIMETERS-ABS, WPRTUNITS-INCHES-ABS, and WPRTUNITS-CELLS-ABS do not affect this field because the field is always calculated as the given value.
  • WINPRINT-COL-SEPARATION - Defines the width of the separation zone. This zone appears at the rightmost edge of the column. This zone is generally kept blank, but see WINPRINT-COL-ALIGNMENT for exceptions. The value specified is the width of this zone (which must be less than the width of the column). It is expressed in the units defined by WINPRINT-COL-UNITS.
    Note: The values of WPRTUNITS-CENTIMETERS-ABS, WPRTUNITS-INCHES-ABS, and WPRTUNITS-CELLS-ABS do not affect this field because the field is always calculated as the given value.
  • WINPRINT-COL-FONT - Sets the handle of the font to be used when printing the column. Set to NULL to use the font currently selected for the printer (this is the default). If you place a valid printer font handle in this field, then that font is used when printing this column regardless of the printer's font. Note that the printer's font still defines the height of the line.
  • WINPRINT-COL-UNITS - Defines the measurement units used for WINPRINT-COL-START, WINPRINT-COL-INDENT and WINPRINT-COL-SEPARATION.

    The following values are valid:

    WPRTUNITS-CELLS Values are measured using the cell size of the currently selected font. A font's cell size is the size of the '0' digit in the font. This is roughly equivalent to measuring in characters.

    If you use a proportional font, it is common for uppercase characters to be wider than this measurement. If a column contains mostly uppercase data, you will need to make it wider than the number of characters in the data if you do not want to truncate the text. If a column contains numbers or mixed-case data, you can usually just set the column width to be the same as the number of characters in the data when measuring in cells. Non-integer values are allowed in the measurements.

    WPRTUNITS-INCHES Values are measured using inches.
    WPRTUNITS-CENTIMETERS Values are measured using centimeters.
    WPRTUNITS-PIXELS Values are measured using the resolution of the output device. Only integer values are allowed in the measurements. Note that the device resolution varies from device to device, and so these units are rarely used.

    To measure units using an absolute value from the left edge of the page, you use WPRTUNITS-CELLS-ABS. To specify an absolute value from the left edge of the page for WINPRINT-COL-START only, you can use the following counterparts:

    • WPRTUNITS-CELLS-ABS
    • WPRTUNITS-INCHES-ABS
    • WPRTUNITS-CENTIMETERS-ABS

    Other settings of WINPRINT-COL-UNITS are invalid.

  • WINPRINT-COL-ALIGNMENT - Describes how data should be aligned in the column. The following values are allowed:

    Any other setting of WINPRINT-COL-ALIGNMENT is invalid.

    WPRTALIGN-NONE No alignment is performed on the data, it is printed as is. In addition, the data is not truncated to fit the column. Any data that extends into the next column will be visible if you are printing with transparent text background, otherwise it may not be visible, as it will be overwritten when the following column is written.
    WPRTALIGN-LEFT Leading and trailing spaces are removed from the data and it is printed left aligned in the column. The text is truncated so that it does not extend into the separation zone.
    WPRTALIGN-CENTER Leading and trailing spaces are removed from the data and it is printed centered between the start of the column and the start of the column's separation zone. Text is truncated so that it does not extend into the separation zone.
    WPRTALIGN-RIGHT Leading and trailing spaces are removed from the data and it is right aligned with respect to the beginning of the separation zone. Leading text is truncated so that it does not extend past the left edge of the column.
    WPRTALIGN-RIGHT-SIGN This is identical to WPRTALIGN-RIGHT, with the additional trait that space padding is automatically added to accommodate a trailing negative sign ("-"). For example, when printing a variable defined as PIC ZZZ9-, WPRTALIGN-RIGHT would align the column as follows:

    WPRTALIGN-RIGHT-SIGN would align the column as follows:

    22O
    220-

    WPRTALIGN-DECIMAL Leading and trailing spaces are removed from the data. The data is then examined to find the leftmost occurrence of the runtime's current notion of the decimal point character. The rightmost edge of the decimal point is aligned with the beginning of the separation zone. If no decimal point is found, the right edge of the data is aligned there instead. Data may extend into the separation zone and is truncated at the beginning and end of the column.
    WPRTALIGN-DECIMAL-SUPPRESS This is identical to WPRTALIGN-DECIMAL, with the additional trait that the decimal point used to align the data is replaced by a space when the data is printed. Columns with this style are limited to 256 data characters.

    Any other setting of WINPRINT-COL-ALIGNMENT is invalid.

  • WPRTDATA-TRANSPARENCY - When the level 88 item WPRTDATA-TRANSARENT is set to true, then the column's foreground text is printed, but its background is left alone. This allows you to print text over something else, such as a bitmap, without erasing it. When WPRTDATA-TRANSPARENT is set to false, then the column's background is also printed, writing over anything else on the page. Note that only the background behind the actual text printed is affected. Suppressed leading and trailing spaces are not printed.
  • WINPRINT-COL-FONTCOLOR - This member of WINPRINT-COLUMN is used to specify a column's font color. This member should be set to a COLORREF (real color) value. See the Color Reference section below for details. If this member is 0 (NULL), it defaults to the color black. If this color is set, it will only be applied to the print of the column that it is associated with. It is a foreground color only.

    For example, to make the entire contents of a column blue, set all other WINPRINT-COLUMN members first then code the following:

    INITIALIZE WINPRINT-COL-FONTCOLOR-NEG.
    MOVE  16711680 TO WINPRINT-COL-FONTCOLOR.
    CALL  "WIN$PRINTER"    USING 
    WINPRINT-SET-PAGE-COLUMN
    WINPRINT-COLUMN.

    See the Columns with Color code example for a detailed demonstration of printing columns and values in color.

  • WINPRINT-COL-FONTCOLOR-NEG - This member of WINPRINT-COLUMN enables you to specify an alternate color for negative numbers in a column. where the text terminates with the negative symbol, as defined on the host computer. This member should be set to a COLORREF (real color) value. See the Color Reference section below for details. If this member is 0 (NULL), it defaults to the color black. If this color is set and the last symbol of the column text equals the computer negative sign, it will overrule a possible use of WINPRINT-COL-FONTCOLOR and be applied only to the text that is about to be printed. It is a foreground color only.

    For example, to make negative values red, set all other WINPRINT-COLUMN members first then code the following:

    INITIALIZE WINPRINT-COL-FONTCOLOR.
    MOVE       X#000000FF TO 
          WINPRINT-COL-FONTCOLOR-NEG.
    CALL  "WIN$PRINTER" USING 
    WINPRINT-SET-PAGE-COLUMN
    WINPRINT-COLUMN.

    See the Columns with Color code example for a detailed demonstration of printing columns and values in color.

Real Colors (COLORREF)

COLORREF is a Windows native data item and should be declared in working storage as a PIC X(4) COMP-N item. You may also apply the SYNC clause when used internal to a group.

COLORREF is a value that can be created from the RGB (See WPAL-RED, WPAL-GREEN and WPAL-BLUE in palette.def) colors returned from the palette dialog. You can do this by using the following COMPUTE statement:

COMPUTE COLORREF-VAR  =
    WPAL-RED)    +
    WPAL-GREEN * 256)  +
    WPAL-BLUE * 65536).

You can also create it yourself. For instance, to create a blue color:

MOVE X#00FF0000 TO COLORREF-VAR.

To get a green color:

MOVE X#0000FF00 TO COLORREF-VAR.

To get a red color:

MOVE X#000000FF TO COLORREF-VAR.

If you want colors in between, just mix between the three values. Remember you only use 3 byte colors, so the most significant byte should be NULL.

Columns with Colors Code Example

The following code example demonstrates the use of several WIN$PRINTER operation codes and their members including: WINPRINT-SET-PAGE-COLUMN and its members: WINPRINT-COL-FONTCOLOR; WINPRINT-COL-FONTCOLOR-NEG.

The output of the program is three columns of data where the first column is blue, the second column is black, and the third column is negative numbers red, positive numbers black. Like this:

Amount 1: 500.00 1,500.00-
Amount 2: 2,500.00- 2,500.00
Amount 3: 33,500.00 33,500.00-
Amount 4: 444,500.00- 444,500.00
PROGRAM-ID. ColumnWithColors.

       FILE-CONTROL.
       SELECT      PRINT-FILE       ASSIGN TO "-P SPOOLER"
                   ORGANIZATION     IS LINE SEQUENTIAL.

       FILE SECTION.
       FD PRINT-FILE.
       01 PRINT-LINE                PIC X(80).

       WORKING-STORAGE SECTION.
       COPY "WINPRINT.DEF".
       COPY "FONTS.DEF".
       77  COLUMN-FONT             HANDLE OF FONT.
       77  STANDARD-FONT           HANDLE OF FONT.

       PROCEDURE DIVISION.
       MAIN.        

           INITIALIZE               WINPRINT-SELECTION.
           CALL    "WIN$PRINTER"    USING 
                   WINPRINT-GET-CURRENT-INFO-EX
                   WINPRINT-SELECTION.
           SET     WPRT-COLOR       TO TRUE.
           CALL    "WIN$PRINTER"    USING 
                   WINPRINT-SET-PRINTER-EX
                   WINPRINT-SELECTION.

           OPEN    OUTPUT           PRINT-FILE.
           INITIALIZE               WFONT-DATA 
                     STANDARD-FONT.
           MOVE    "Courier New"    TO WFONT-NAME.
           MOVE    12               TO WFONT-SIZE.
           SET     WFONT-BOLD       TO FALSE.
           SET     WFDEVICE-WIN-PRINTER TO TRUE.
           CALL    "W$FONT"         USING 
                   WFONT-GET-FONT
                   STANDARD-FONT
                   WFONT-DATA.
           INITIALIZE               WINPRINT-DATA        
           MOVE    STANDARD-FONT    TO WPRTDATA-FONT
           CALL    "WIN$PRINTER"    USING 
                   WINPRINT-SET-FONT
                   WINPRINT-DATA.

           INITIALIZE               WFONT-DATA 
                                    COLUMN-FONT.
           MOVE    "Arial"          TO WFONT-NAME.
           MOVE    12               TO WFONT-SIZE.
           SET     WFONT-BOLD       TO TRUE.
           SET     WFDEVICE-WIN-PRINTER TO TRUE.
           CALL    "W$FONT"         USING 
                   WFONT-GET-FONT
                   COLUMN-FONT
                   WFONT-DATA.                   

           WRITE   PRINT-LINE       FROM
                   "This demo requires a COLOR printer to show colors."
                   BEFORE ADVANCING 1 LINE.
           WRITE   PRINT-LINE       FROM
                   "It is also required with 8.1 runtime version"
                   BEFORE ADVANCING 1 LINE.
           WRITE   PRINT-LINE       FROM
                   "The first column should be blue."
                   BEFORE ADVANCING 1 LINE.
           WRITE   PRINT-LINE       FROM
                   "The second column should print the regular black."
                   BEFORE ADVANCING 1 LINE.
           WRITE   PRINT-LINE       FROM
                   "The third column should print the regular black,"
                   BEFORE ADVANCING 1 LINE.
           WRITE   PRINT-LINE       FROM
                   "except of negative numbers, they should be in red."
                   BEFORE ADVANCING 1 LINE.
           WRITE   PRINT-LINE       FROM
                   "Column 3 is using ARIAL font, the rest is Courier."
                   BEFORE ADVANCING 2 LINES.
      
           CALL    "WIN$PRINTER"    USING 
                   WINPRINT-SET-DATA-COLUMNS
                   1
                   12
                   24.
      
           INITIALIZE               WINPRINT-COLUMN
                                    WINPRINT-COL-UNITS
                                    WINPRINT-COL-FONTCOLOR
                                    WINPRINT-COL-FONTCOLOR-NEG.
           MOVE    1                TO WINPRINT-COL-START.
           MOVE    0.2              TO WINPRINT-COL-SEPARATION.
           MOVE    WPRTALIGN-LEFT   TO WINPRINT-COL-ALIGNMENT.
           MOVE    1                TO WINPRINT-TRANSPARENCY.
           MOVE    ZEROS            TO WINPRINT-COL-INDENT.
           
           MOVE    16711680         TO WINPRINT-COL-FONTCOLOR.
           CALL    "WIN$PRINTER"    USING 
                   WINPRINT-SET-PAGE-COLUMN
                   WINPRINT-COLUMN.

           MOVE    5                TO WINPRINT-COL-SEPARATION.
           MOVE    WPRTALIGN-DECIMAL TO WINPRINT-COL-ALIGNMENT.
           MOVE    0                TO WINPRINT-COL-FONTCOLOR.           
           MOVE    12               TO WINPRINT-COL-START.

           CALL    "WIN$PRINTER"    USING 
                   WINPRINT-SET-PAGE-COLUMN
                   WINPRINT-COLUMN.

           MOVE    COLUMN-FONT      TO WINPRINT-COL-FONT.
           MOVE    WPRTALIGN-RIGHT-SIGN TO 
                   WINPRINT-COL-ALIGNMENT.
           MOVE    28               TO WINPRINT-COL-START.
           MOVE    0                TO WINPRINT-COL-FONTCOLOR.
           MOVE    255              TO WINPRINT-COL-FONTCOLOR-NEG.
           CALL    "WIN$PRINTER"    USING 
                   WINPRINT-SET-PAGE-COLUMN
                   WINPRINT-COLUMN.

           MOVE    50               TO WINPRINT-COL-START.
           INITIALIZE               WINPRINT-COL-FONTCOLOR
                                    WINPRINT-COL-FONTCOLOR-NEG.
           CALL    "WIN$PRINTER"    USING 
                   WINPRINT-SET-PAGE-COLUMN
                   WINPRINT-COLUMN.

           MOVE "Amount 1:      500.00     1,500.00- " TO PRINT-LINE.
           WRITE PRINT-LINE BEFORE ADVANCING 1 LINE.
           MOVE "Amount 2:    2,500.00-    2,500.00  " TO PRINT-LINE.
           WRITE PRINT-LINE BEFORE ADVANCING 1 LINE.
           MOVE "Amount 3:   33,500.00    33,500.00- " TO PRINT-LINE.
           WRITE PRINT-LINE BEFORE ADVANCING 1 LINE.
           MOVE "Amount 4:  444,500.00-  444,500.00  " TO PRINT-LINE.
           WRITE PRINT-LINE BEFORE ADVANCING 1 LINE.
           
           CALL "WIN$PRINTER" USING WINPRINT-CLEAR-DATA-COLUMNS.
      
           CLOSE PRINT-FILE.