CALL "C$SCWR" USING displayDesc textCharacters |
displayDesc | Group item | Group data item defined as follows: 01 DISPLAY-DESCRIPTION BINARY(2). 03 DISPLAY-VERSION PIC 9(4) VALUE 0. 03 DISPLAY-UNIT PIC 9(4) VALUE 0. 03 DISPLAY-LINE PIC 9(4). 03 DISPLAY-POSITION PIC 9(4). 03 DISPLAY-LENGTH PIC 9(4). 03 DISPLAY-EXCEPTION-CODE PIC 9(4). 03 DISPLAY-EXCEPTION-VALUE PIC 9(4). DISPLAY-VERSION must be set to a value of 0. DISPLAY-UNIT is the unit number of the terminal to which the display is directed. This value must be set to 0. DISPLAY-LINE is the one-relative line number in the current window where the text is to be displayed. If set to a value of 0, the display begins on the current line. DISPLAY-POSITION is the one-relative column number in the current window where the text is to be displayed. If set to a value of 0, the display begins at the current column. DISPLAY-LENGTH is the number of characters of text to display. If set to a value of 0 or omitted, the actual length of text-characters is used. DISPLAY-EXCEPTION-CODE is set to a value of 0 if this function succeeds. Otherwise, one of the below exception codes is returned. DISPLAY-EXCEPTION-VALUE is set to a value of 0 if this function succeeds. Otherwise, one of the below exception codes is returned. Exception codes: 1: Invalid DISPLAY-VERSION. This data item must be set to a value of 0. 2: Invalid or missing parameters. 3: DISPLAY-LINE is greater than the number of lines on the window or screen. 4: DISPLAY-POSITION is greater than the number of columns on the screen. |
textCharacters | PIC X(n) | Specifies the characters to be displayed. |
move 2 to display-line. move 2 to display-position. move "hello" to text-buffer. call "c$scwr" using display-description, text-buffer. |