VSETKEYLABEL [ HP Data Entry and Forms Management System (VPLUS/V) ] MPE/iX 5.0 Documentation
HP Data Entry and Forms Management System (VPLUS/V)
VSETKEYLABEL
Allows for temporarily setting, programmatically, a new label for a
function key.
Syntax
VSETKEYLABEL {comarea,formorglob,keynum,label}
Parameters
comarea Must be comarea name specified when the forms file was
opened with VOPENFORMF. If not already set, the
following comarea items must be set before calling
VSETKEYLABEL:
cstatus Set to zero.
language Set to the code identifying the
programming language of the calling
program.
comarealen Set to total number of two-byte words
in comarea.
VSETKEYLABEL may set the following comarea items:
cstatus Set to nonzero value if call is
unsuccessful.
formorglob Integer specifying which type of label is to be
temporarily set.
0 - Set global label.
1 - Set current form label.
keynum Integer from 1 to 8 corresponding to function key to be
set.
label A byte array containing the text for the label; must be
16 bytes long.
Discussion
VSETKEYLABEL is only a temporary setting of a new label for an individual
function key. Use of this intrinsic does not change the label definition
made in FORMSPEC. Note only one function key can be set with this
intrinsic. The labeloption must be set to one prior to VOPENFORMF.
The temporary label is displayed after the next call to VSHOWFORM. If the
temporary label is global, it remains active until the forms file is
closed or it is replaced by a new global label. If the temporary label
is for the current form only, it is replaced when the next form is
retrieved or when a new current form label is set.
If no global or current form labels have been defined with FORMSPEC or no
labels have been set with VSETKEYLABELS, the key label buffers are
cleared before the label being defined with this intrinsic is set.
Example
COBOL
77 FORM-OR-GLOB PIC S9(4)COMP.
77 KEY-NUM PIC S9(4)COMP.
77 KEY-LABEL PIC X(16).
:
MOVE 1 TO FORM-OR-GLOB.
MOVE 1 TO KEY-NUM.
MOVE "LABEL 1 " TO KEY-LABEL.
CALL "VSETKEYLABEL" USING COMAREA, FORM-OR-GLOB, KEY-NUM, KEY-LABEL.
BASIC
10 INTEGER F,N
20 DIM L$[16]
30 F=1
40 N=2
50 L$="LABEL 1 "
60 CALL VSETKEYLABEL(C[*],F,N,L$)
FORTRAN
INTEGER FORMORGLOB,KEYNUM
CHARACTER*16 LABEL
FORMORGLOB=1
LABEL="LABEL 1 "
CALL VSETKEYLABEL(COMAREA,FORMORGLOB,KEYNUM,LABEL)
SPL/PASCAL
INTEGER
FORM'OR'GLOB,
KEY'NUM;
BYTE ARRAY
KEY'LABEL(0:15);
:
FORM'OR'GLOB:=1;
KEY'NUM:=1;
MOVE KEY'LABEL:="LABEL 1 ";
VSETKEYLABEL(COMAREA,FORM'OR'GLOB,KEY'NUM,KEY'LABEL);
MPE/iX 5.0 Documentation