[an error occurred while processing this directive]

HP OpenVMS Systems Documentation

Content starts here

OpenVMS/Hangul RTL Korean Screen Management (SMG$) Manual


Previous Contents

Example 7-4 shows the techniques used to call SMG$READ_KEYSTROKE from VAX COBOL.

Example 7-4 Using SMG$ Routines in VAX COBOL

IDENTIFICATION DIVISION.
PROGRAM-ID.    KEYSTROKE.
*
*  This routine creates a VIRTUAL DISPLAY and writes it to the PASTEBOARD.
*  Data is placed in the VIRTUAL DISPLAY using the routine SMG$PUT_LINE.
*  SMG$READ_KEYSTROKE is called to read a keystroke from the VIRTUAL KEYBOARD.
*
ENVIRONMENT DIVISION.
DATA DIVISION.
WORKING-STORAGE SECTION.
01  DISPLAY1           PIC 9(9)  COMP.
01  PASTE1             PIC 9(9)  COMP.
01  KEYBOARD1          PIC 9(9)  COMP.
01  ROWS               PIC S9(9) COMP    VALUE 7.
01  COLUMNS            PIC S9(9) COMP    VALUE 60.
01  DISPLAY_NAME       PIC X(13) VALUE " DISPLAY ONE ".
01  TERM_CHAR          PIC 9(4)  COMP.
01  T_TEXT             PIC X(6).
01  TEXT_OUTPUT        PIC X(24) VALUE " TERMINAL CHARACTER IS: ".
01  PROMPT             PIC X(2)  VALUE ">>".
01  LINE_1   PIC X(12) VALUE "Hit any key.".
01  LINE_2   PIC X(34) VALUE "This character will not be echoed.".
01  LINE_3   PIC X(47) VALUE "The terminal character equivalent is displayed.".
01  LINE_4   PIC X     VALUE " ".
01  THREE              PIC S9(9) COMP   VALUE 3.
01  NINE               PIC S9(9) COMP   VALUE 9.
01  SEVEN              PIC S9(9) COMP   VALUE 7.
01  TWENTY_FIVE        PIC S9(9) COMP   VALUE 25.
01  CHAR_SET            PIC S9(9) COMP   VALUE EXTERNAL SMG$C_HANGUL.
PROCEDURE DIVISION.
P0.

* Create the virtual display with a border.
        CALL "SMG$CREATE_VIRTUAL_DISPLAY" USING
                                       ROWS, COLUMNS, DISPLAY1,
                                       OMITTED, OMITTED, CHAR_SET.

* Create the pasteboard

        CALL "SMG$CREATE_PASTEBOARD" USING PASTE1.

* Create a virtual keyboard

        CALL "SMG$CREATE_VIRTUAL_KEYBOARD" USING KEYBOARD1.

* Paste the virtual display at row 3, column 9.

        CALL "SMG$LABEL_BORDER" USING DISPLAY1, BY DESCRIPTOR DISPLAY_NAME,
                                OMITTED, OMITTED, OMITTED, OMITTED, CHAR_SET.

        CALL "SMG$PASTE_VIRTUAL_DISPLAY" USING
                                         DISPLAY1, PASTE1, THREE, NINE.
* Place data in the virtual display

        CALL "SMG$PUT_LINE" USING DISPLAY1, BY DESCRIPTOR LINE_1,
                            OMITTED, OMITTED, OMITTED, OMITTED, CHAR_SET.
        CALL "SMG$PUT_LINE" USING DISPLAY1, BY DESCRIPTOR LINE_2,
                            OMITTED, OMITTED, OMITTED, OMITTED, CHAR_SET.
        CALL "SMG$PUT_LINE" USING DISPLAY1, BY DESCRIPTOR LINE_3,
                            OMITTED, OMITTED, OMITTED, OMITTED, CHAR_SET.
        CALL "SMG$PUT_LINE" USING DISPLAY1, BY DESCRIPTOR LINE_4.

* Read a keystroke from the virtual pasteboard.

        CALL "SMG$READ_KEYSTROKE" USING KEYBOARD1, TERM_CHAR,
                         BY DESCRIPTOR PROMPT, OMITTED, BY REFERENCE DISPLAY1.

        CALL "SMG$PUT_LINE" USING DISPLAY1, BY DESCRIPTOR LINE_4.

* Convert the decimal value of TERM_CHAR to a decimal ASCII text string.

        CALL "OTS$CVT_L_TI" USING TERM_CHAR, BY DESCRIPTOR T_TEXT.

* Print out the decimal ASCII text string.

        CALL "SMG$PUT_LINE" USING DISPLAY1, BY DESCRIPTOR TEXT_OUTPUT.
        CALL "SMG$PUT_CHARS" USING DISPLAY1, BY DESCRIPTOR T_TEXT,
                                BY REFERENCE SEVEN, TWENTY_FIVE.

            STOP RUN.

The FORTRAN program shown in Example 7-5 uses SMG$READ_KEYSTROKE, as well as SMG$CREATE_VIRTUAL_DISPLAY, SMG$CREATE_PASTEBOARD, SMG$PASTE_VIRTUAL_DISPLAY, SMG$CREATE_VIRTUAL_KEYBOARD, and SMG$PUT_LINE.

Example 7-5 Using SMG$ Routines in DEC Fortran

C+
C This routine creates a virtual display and writes it to the PASTEBOARD.
C Data is placed in the virtual display using the routine SMG$PUT_CHARS.
C Include the SMG definitions. In particular, we want SMG$M_BORDER.
C-
        INCLUDE '($SMGDEF)'
        INTEGER SMG$CREATE_VIRTUAL_DISPLAY, SMG$CREATE_PASTEBOARD
        INTEGER SMG$PASTE_VIRTUAL_DISPLAY,
      1         SMG$CREATE_VIRTUAL_KEYBOARD
        INTEGER SMG$READ_KEYSTROKE, SMG$PUT_LINE
        INTEGER DISPLAY1, PASTE1, KEYBOARD1, ROWS, COLUMNS,
      1         TERM_CHAR
        CHARACTER*3 TEXT
        CHARACTER*27 TEXT_OUTPUT
C+
C Create the virtual display with a border.
C-
        ROWS = 7
        COLUMNS = 60

        ISTATUS = SMG$CREATE_VIRTUAL_DISPLAY
     1          (ROWS, COLUMNS, DISPLAY1, SMG$M_BORDER, , SMG$C_HANGUL)
C+
C Create the pasteboard.
C-
        ISTATUS = SMG$CREATE_PASTEBOARD (PASTE1)
C+
C Create a virtual keyboard.
C-
        ISTATUS = SMG$CREATE_VIRTUAL_KEYBOARD ( KEYBOARD1)
C+
C Paste the virtual display at row 3, column 9.
C-
        ISTATUS = SMG$PASTE_VIRTUAL_DISPLAY ( DISPLAY1, PASTE1, 3, 9)
        ISTATUS = SMG$PUT_LINE (DISPLAY1,
     1          'Enter the character K after the >> prompt.',
     1          , , , , SMG$C_HANGUL )
        ISTATUS = SMG$PUT_LINE (DISPLAY1,
     1          'This character will not be echoed as you type it.',
     1          , , , , SMG$C_HANGUL )
        ISTATUS = SMG$PUT_LINE (DISPLAY1,
     1  'The terminal character equivalent of K is displayed.',
     1          , , , , SMG$C_HANGUL )
        ISTATUS = SMG$PUT_LINE (DISPLAY1, ' ')
C+
C Read a keystroke from the virtual pasteboard.
C-
        ISTATUS = SMG$READ_KEYSTROKE ( KEYBOARD1, TERM_CHAR, '>>', ,
     1          DISPLAY1)

        ISTATUS = SMG$PUT_LINE (DISPLAY1, ' ')
C+
C Convert the decimal value of TERM_CHAR to a decimal ASCII text string.
C-
        ISTATUS = OTS$CVT_L_TI( TERM_CHAR, TEXT)

        TEXT_OUTPUT = ' TERMINAL CHARACTER IS: ' // TEXT
C+
C Print the decimal ASCII text string.
C-
        ISTATUS = SMG$PUT_LINE (DISPLAY1, TEXT_OUTPUT, , , , , SMG$C_HANGUL)
        ISTATUS = SMG$PUT_CHARS (DISPLAY1, TEXT, 7, 25, , , , SMG$C_HANGUL)

        END

The VAX MACRO program shown in Example 7-6 demonstrates the precise steps required to call SMG$READ_KEYSTROKE from a low-level language.

Example 7-6 Using SMG$ Routines in VAX MACRO

        .TITLE  SMG_DEMO
;+
; This program demonstrates the use of the SMG$ routines, in particular
; SMG$READ_KEYSTROKE.
;-
        $DSCDEF         ; Declare DSC$ symbols
        $SMGDEF         ; Declare SMG$ symbols
;+
; Declare external routines.
;-
        .EXTRN  SMG$CREATE_PASTEBOARD
        .EXTRN  SMG$CREATE_VIRTUAL_DISPLAY
        .EXTRN  SMG$CREATE_VIRTUAL_KEYBOARD
        .EXTRN  SMG$PUT_LINE
        .EXTRN  SMG$READ_KEYSTROKE
;+
; Declare data PSECT and objects.
;-
        .PSECT  $DATA RD,WRT,NOEXE,NOSHR,PIC

LINE1:  .ASCID  "Enter the character K after the prompt."
LINE2:  .ASCID  "This character will not be echoed as you type it."
LINE3:  .ASCID  "The terminal character equivalent of K is displayed."
PROMPT: .ASCID  ">>"
BLANK:  .ASCID  " "
FAOSTR: .ASCID  "TERMINAL CHARACTER IS !UL"

TEXT:   .BLKB   80      ; Buffer for formatted text
TEXT_LEN = . - TEXT     ; Length of TEXT
TEXT_DSC:               ; Descriptor for TEXT string
        .WORD   TEXT_LEN        ; DSC$W_LENGTH
        .BYTE   DSC$K_DTYPE_T   ; DSC$B_DTYPE
        .BYTE   DSC$K_CLASS_S   ; DSC$B_CLASS
        .ADDRESS TEXT           ; DSC$A_POINTER
CHAR_SET:
        .LONG  SMG$C_HANGUL      ; Character set value

TERM_CHAR:
        .BLKL           ; Space for terminator character code
PASTEBOARD_1:
        .BLKL           ; Pasteboard ID
DISPLAY_1:
        .BLKL           ; Display ID
KEYBOARD_1:
        .BLKL           ; Keyboard ID

;+
; Declare PSECT for code.
;-

        .PSECT  $CODE RD,NOWRT,EXE,SHR,PIC
;+
; Begin main routine.
;-
        .ENTRY  SMG_DEMO, ^M<>  ; Save no registers
;+
; Create virtual display.
;-
        PUSHL   #SMG$M_BORDER   ; Put flag on stack
        PUSHL   #60             ; Put columns on stack
        PUSHL   #7              ; Put rows on stack
        PUSHAB  L^CHAR_SET      ; Address of character set
        PUSHL   #0              ; Do not specify video attribute
        PUSHAB  16(SP)          ; Address of flag
        PUSHAB  L^DISPLAY_1     ; Address of display ID
        PUSHAB  20(SP)          ; Address of columns
        PUSHAB  20(SP)          ; Address of rows
        CALLS   #6, G^SMG$CREATE_VIRTUAL_DISPLAY
        ADDL2   #12, SP         ; Pop off temporaries

; Create pasteboard.
        PUSHAB  L^PASTEBOARD_1  ; Address of pasteboard
        CALLS   #1, G^SMG$CREATE_PASTEBOARD

; Create virtual keyboard.
        PUSHAB  L^KEYBOARD_1    ; Address of keyboard
        CALLS   #1, G^SMG$CREATE_VIRTUAL_KEYBOARD

; Paste the virtual display at row 3, column 9.
        PUSHL   #9              ; Put column on stack
        PUSHL   #3              ; Put row on stack
        PUSHAB  4(SP)           ; Address of column
        PUSHAB  4(SP)           ; Address of row
        PUSHAB  L^PASTEBOARD_1  ; Address of pasteboard
        PUSHAB  L^DISPLAY_1     ; Address of display
        CALLS   #4, G^SMG$PASTE_VIRTUAL_DISPLAY
        ADDL2   #8, SP          ; Pop off temporaries

; Write instructions.
        PUSHAB  L^CHAR_SET      ; Character set
        PUSHL   #0              ; Neglect optional parameters
        PUSHL   #0              ; Neglect optional parameters
        PUSHL   #0              ; Neglect optional parameters
        PUSHL   #0              ; Neglect optional parameters
        PUSHAB  L^LINE1         ; "Enter the character..."
        PUSHAB  L^DISPLAY_1     ; Display ID
        CALLS   #7, G^SMG$PUT_LINE
        PUSHAB  L^CHAR_SET      ; Character set
        PUSHL   #0              ; Neglect optional parameters
        PUSHL   #0              ; Neglect optional parameters
        PUSHL   #0              ; Neglect optional parameters
        PUSHL   #0              ; Neglect optional parameters
        PUSHAB  L^LINE2         ; "This character will not..."
        PUSHAB  L^DISPLAY_1     ; Display ID
        CALLS   #7, G^SMG$PUT_LINE
        PUSHAB  L^CHAR_SET      ; Character set
        PUSHL   #0              ; Neglect optional parameters
        PUSHL   #0              ; Neglect optional parameters
        PUSHL   #0              ; Neglect optional parameters
        PUSHL   #0              ; Neglect optional parameters
        PUSHAB  L^LINE3         ; "The terminal character..."
        PUSHAB  L^DISPLAY_1     ; Display ID
        CALLS   #7, G^SMG$PUT_LINE
        PUSHAB  L^BLANK         ; Blank line
        PUSHAB  L^DISPLAY_1     ; Display ID
        CALLS   #2, G^SMG$PUT_LINE

; Read a keystroke from the virtual keyboard.
        PUSHAB  L^DISPLAY_1     ; Display ID
        CLRL    -(SP)           ; No timeout
        PUSHAB  L^PROMPT        ; Prompt string
        PUSHAB  L^TERM_CHAR     ; Longword for terminator code
        PUSHAB  L^KEYBOARD_1    ; Keyboard ID
        CALLS   #5, G^SMG$READ_KEYSTROKE
; Format the terminator code using $FAO.
        $FAO_S  CTRSTR=L^FAOSTR,-                       ; FAO control string
                OUTLEN=L^TEXT_DSC+DSC$W_LENGTH,-        ; Output string length
                OUTBUF=L^TEXT_DSC,-                     ; Output buffer
                P1=L^TERM_CHAR                          ; Value to format

; Display the formatted text.
        PUSHAB  L^BLANK         ; Blank line
        PUSHAB  L^DISPLAY_1     ; Display ID
        CALLS   #2, G^SMG$PUT_LINE
        PUSHAB  L^CHAR_SET      ; Character set
        PUSHL   #0              ; Neglect optional parameters
        PUSHL   #0              ; Neglect optional parameters
        PUSHL   #0              ; Neglect optional parameters
        PUSHL   #0              ; Neglect optional parameters
        PUSHAB  L^TEXT_DSC      ; Text to display
        PUSHAB  L^DISPLAY_1     ; Display ID
        CALLS   #7, G^SMG$PUT_LINE

; Return with status from last call.
        RET

        .END    SMG_DEMO        ; Specify SMG_DEMO as main program

Example 7-7 uses SMG$READ_KEYSTROKE from VAX Pascal. It also demonstrates the use of SMG$CREATE_VIRTUAL_DISPLAY, SMG$CREATE_PASTEBOARD, SMG$CREATE_VIRTUAL_KEYBOARD, SMG$PASTE_VIRTUAL_DISPLAY, and SMG$PUT_LINE.

Example 7-7 Using SMG$ Routines in VAX Pascal

{ This program demonstrates the use of the SMG$ routines, in particular }
{ SMG$READ_KEYSTROKE. }

[INHERIT('SYS$LIBRARY:STARLET')]
PROGRAM SMG_DEMO;

TYPE
    UNSIGNED_WORD = [WORD] 0..65535;

FUNCTION SMG$CREATE_VIRTUAL_DISPLAY (
    ROWS, COLUMNS: INTEGER;
    VAR DISPLAY_ID: INTEGER;
    DISPLAY_ATTRIBUTES, VIDEO_ATTRIBUTES, CHAR_SET: UNSIGNED
        := %IMMED 0): UNSIGNED; EXTERN;

FUNCTION SMG$CREATE_PASTEBOARD (
    VAR PASTEBOARD_ID: INTEGER;
    OUTPUT_DEVICE: PACKED ARRAY [A..B:INTEGER] OF CHAR := %IMMED 0;
    ROWS, COLUMNS: INTEGER := %IMMED 0;
    PRESERVE_SCREEN_FLAG: BOOLEAN := %IMMED 0) : UNSIGNED; EXTERN;

FUNCTION SMG$CREATE_VIRTUAL_KEYBOARD (
    VAR KEYBOARD_ID: INTEGER;
    FILESPEC: PACKED ARRAY [A..B:INTEGER] OF CHAR := %IMMED 0;
    DEFAULT_FILESPEC: PACKED ARRAY [C..D:INTEGER] OF CHAR := %IMMED 0;
    RESULTANT_FILESPEC: PACKED ARRAY [E..F:INTEGER] OF CHAR := %IMMED 0
    ): UNSIGNED; EXTERN;

FUNCTION SMG$PASTE_VIRTUAL_DISPLAY (
    DISPLAY_ID, PASTEBOARD_ID: INTEGER;
    ROW, COLUMN: INTEGER): UNSIGNED; EXTERN;

FUNCTION SMG$READ_KEYSTROKE (
    KEYBOARD_ID: INTEGER;
    VAR TERMINATOR_CODE: UNSIGNED_WORD;
    PROMPT: PACKED ARRAY [A..B:INTEGER] OF CHAR := %IMMED 0;
    TIMEOUT, DISPLAY_ID: INTEGER := %IMMED 0): UNSIGNED; EXTERN;

FUNCTION SMG$PUT_LINE (
    DISPLAY_ID: INTEGER;
    TEXT: PACKED ARRAY [A..B:INTEGER] OF CHAR;
    LINE_ADVANCE: INTEGER := %IMMED 0;
    RENDITION_SET, RENDITION_COMPLEMENT: UNSIGNED := %IMMED 0;
    WRAP_FLAG: BOOLEAN := %IMMED 0;
    CHAR_SET: UNSIGNED := %IMMED 0): UNSIGNED; EXTERN;

var
    PASTEBOARD_1, DISPLAY_1, KEYBOARD_1: INTEGER;
    TERMINATOR: UNSIGNED_WORD;

BEGIN
    { Create virtual display, pasteboard and virtual keyboard }

    SMG$CREATE_VIRTUAL_DISPLAY (ROWS := 7, COLUMNS := 60,
        DISPLAY_ID := DISPLAY_1,
        DISPLAY_ATTRIBUTES := SMG$M_BORDER,
        CHAR_SET := SMG$C_HANGUL);
    SMG$CREATE_PASTEBOARD (PASTEBOARD_ID := PASTEBOARD_1);
    SMG$CREATE_VIRTUAL_KEYBOARD (KEYBOARD_ID := KEYBOARD_1);

    { Paste the virtual display at row 3, column 9 }

    SMG$PASTE_VIRTUAL_DISPLAY (DISPLAY_ID := DISPLAY_1,
        PASTEBOARD_ID := PASTEBOARD_1, ROW := 3, COLUMN := 9);

    { Write the instructions to the virtual display }

    SMG$PUT_LINE (DISPLAY_ID := DISPLAY_1,
        TEXT := 'Enter the character K after the >> prompt.',
        CHAR_SET := SMG$C_HANGUL);
    SMG$PUT_LINE (DISPLAY_ID := DISPLAY_1,
        TEXT := 'This character will not be echoed as you type it.',
        CHAR_SET := SMG$C_HANGUL);
    SMG$PUT_LINE (DISPLAY_ID := DISPLAY_1,
        TEXT := 'The terminal character equivalent of K is displayed.',
        CHAR_SET := SMG$C_HANGUL);
    SMG$PUT_LINE (DISPLAY_ID := DISPLAY_1,
        TEXT := ' ',
        CHAR_SET := SMG$C_HANGUL);

    { Read the keystroke from the virtual keyboard }

    SMG$READ_KEYSTROKE (KEYBOARD_ID := KEYBOARD_1,
        DISPLAY_ID := DISPLAY_1,
        TERMINATOR_CODE := TERMINATOR, PROMPT := '>>');

    { Display the decimal value of the terminator code }

    SMG$PUT_LINE (DISPLAY_ID := DISPLAY_1,
        TEXT := ' ',
        CHAR_SET := SMG$C_HANGUL);
    SMG$PUT_LINE (DISPLAY_ID := DISPLAY_1,
        TEXT := 'TERMINAL CHARACTER IS ' + DEC(TERMINATOR,5,1),
        CHAR_SET := SMG$C_HANGUL);
END.

The program shown in Example 7-8 calls SMG$READ_KEYSTROKE from VAX PL/I.

Example 7-8 Using SMG$ Routines in VAX PL/I

/*
 *  Example of SMG$READ_KEYSTROKE.
 */

/*
 *  Declare the RTL entry points.
 */
declare
    SMG$CREATE_VIRTUAL_KEYBOARD external entry(
        fixed binary(31),       /* new-keyboard-id */
        character(*),           /* filespec */
        character(*),           /* default-filespec */
        character(*) varying )  /* resultant-filespec */
        returns(fixed binary(31)) options(variable);

declare
    SMG$DELETE_VIRTUAL_KEYBOARD external entry(
        fixed binary(31) )       /* keyboard-id */
        returns(fixed binary(31));

declare
    SMG$READ_KEYSTROKE external entry(
        fixed binary(31),       /* keyboard-id */
        fixed binary(15),       /* terminator-code */
        character(*),           /* prompt-string */
        fixed binary(31),       /* timeout */
        fixed binary(31) )      /* display-id */
        returns(fixed binary(31)) options(variable);

/*
 *  Get the value of the SMG constants from PLISTARLET.
 */
%include $SMGDEF;
declare SMG$_EOF globalref value fixed binary(31);

/*
 *  Misc. constants.
 */
%replace false by '0'b;
%replace true  by '1'b;

/*
 *  The following compile-time routine will signal an error at run-time
 *  if the status value that it is passed does not have success or
 *  informational severity.  (i.e. if the low bit is not set.)
 */
%signal_if: procedure (status_val) returns(character);
    %declare status_val character;
    %return( 'if posint(' || status_val || ',1,1) = 0 ' ||
                'then signal vaxcondition(' || status_val || ')' );
    %end;

main: proc options(main, ident('V4.2'));

    declare exit bit initial(false);
    declare status fixed binary(31);
    declare keyboard_id fixed binary(31);
    declare terminator fixed binary(15);

    /*
     *  Create the virtual keyboard necessary for the read.
     */
    status = smg$create_virtual_keyboard( keyboard_id );
    signal_if( status );
    /*
     *  Read a single keystroke.  If that keystroke is an end-of-file,
     *  then exit.  Otherwise, SELECT the appropriate action based on
     *  the key.
     */
    do while(^exit);

        status = smg$read_keystroke( keyboard_id, terminator,
            'Command: ', 20 );

        if status = SMG$_EOF
            then exit = true;

            else do;
                signal_if( status );

                select (terminator);

                    when (SMG$K_TRM_PF2,
                          SMG$K_TRM_HELP,
                          rank('H'),
                          rank('h'),
                          rank('?') )   call display_help;

                    when(SMG$K_TRM_DO)  call do_command;

                    when(rank('E'),
                         rank('e'))     exit = true;

                    otherwise           call command_error;

                       end;
                end;
        end;

    /*
     *  We're done, so delete the virtual keyboard.
     */
    status = smg$delete_virtual_keyboard( keyboard_id );
    signal_if( status );

    end main;

display_help: procedure;

    put skip edit('This program uses single keystroke commands.') (A);
    put skip edit('The following keys are valid:') (A);
    put skip;
    put skip edit('     Key             Function') (A);
    put skip edit('     E/e             Exit') (A);
    put skip edit('     <DO>  Your choice...') (A);
    put skip edit('     ?/H/h/<HELP> Help') (A);
    put skip;

    end display_help;

do_command: procedure;

    put skip edit('The DO key was pressed') (A);
    put skip;

    end do_command;

command_error: procedure;

    put skip edit('The key pressed was not valid - please try again.') (A);
    put skip edit('(H for HELP).' ) (A);
    put skip;

    end command_error;

Example 7-9 demonstrates how to call SMG$READ_KEYSTROKE from VAX RPG II. This program also uses SMG$CREATE_VIRTUAL_KEYBOARD and SMG$DELETE_VIRTUAL_KEYBOARD.

This RPG II program displays the following if the cursor positioning and control keys are typed:


UP DOWN RIGHT LEFT

These keys include the arrow keys (up, down, right, and left) and Ctrl/Z.

Example 7-9 Using SMG$ Routines in VAX RPG II

    0    |    1    |    2    |    3    |    4    |    5    |    6    |
1234567890123456789012345678901234567890123456789012345678901234567890

     F*+
     F* This RPG II program demonstrates the use of the RTL routine
     F* SMG$READ_KEYSTROKE to read a keystroke from the terminal.
     F*
     F* The program takes input from the terminal until Ctrl/Z is
     F* typed.  If any of the four cursor positioning keys is typed,
     F* a string is displayed corresponding to the key.
     F*
     F* Build this program using the following commands:
     F*
     F* $ RPG READ_KEY
     F* $ CREATE SMGDEF.MAR
     F*        .TITLE SMGDEF - Define SMG$ constants
     F*        .Ident /1-000/
     F*
     F*        $SMGDEF GLOBAL
     F*        .END
     F* $ MACRO SMGDEF
     F* $ LINK READ_KEY,SMGDEF
     F*-
     FTTY     D   V       5            TTY
     C* External definitions for SMG routines.
     C           CREKB     EXTRN'SMG$CREATE_VIRTUAL_KEYBOARD'
     C           DELKB     EXTRN'SMG$DELETE_VIRTUAL_KEYBOARD'
     C           REAKEY    EXTRN'SMG$READ_KEYSTROKE'
     C* External definitions for SMG terminators.
     C           T_UP      EXTRN'SMG$K_TRM_UP'
     C           T_DOWN    EXTRN'SMG$K_TRM_DOWN'
     C           T_LEFT    EXTRN'SMG$K_TRM_LEFT'
     C           T_RIGHT   EXTRN'SMG$K_TRM_RIGHT'
     C           T_CTRLZ   EXTRN'SMG$K_TRM_CTRLZ'
     C* Create the virtual keyboard.
     C  N99                CALL CREKB
     C                     PARM           KB_ID   90 WL
     C                     SETON                     99
     C* Read a keystroke.
     C                     CALL REAKEY
     C                     PARM           KB_ID   90 RL
     C                     PARM           T_CODE  50 WW
     C* Turn on an indicator if a cursor positioning key was typed.
     C           T_CODE    COMP T_UP                     01
     C           T_CODE    COMP T_DOWN                   02
     C           T_CODE    COMP T_LEFT                   03
     C           T_CODE    COMP T_RIGHT                  04
     C* Turn on LR to quit if Ctrl/Z was typed.
     C           T_CODE    COMP T_CTRLZ                  LR
     C* Display a message if a cursor positioning key was typed.
     C   01      'UP'      DSPLYTTY
     C   02      'DOWN'    DSPLYTTY
     C   03      'LEFT'    DSPLYTTY
     C   04      'RIGHT'   DSPLYTTY
     C* Delete the virtual keyboard.
     CLR                   CALL DELKB
     CLR                   PARM           KB_ID   90 RL


Previous Next Contents