Author | : | A J Marston |
Date Created | : | March, 1988 |
Date Revised | : | February, 1993 |
Version | : | 01.010.009 |
Although there are many different applications, and many different programs within each application, there are certain low-level functions that appear from time to time which can be satisfied by a common set of standard routines or utilities.
The advantage of having a library of standard utilities should be obvious - each routine is developed (and thoroughly tested) just once, and is then available for immediate use within any application without the need for any further effort.
The inclusion of any standard routines into an application is made even easier due to the fact that most of the communication areas have already been defined in the standard COMMON-LINKAGE area, and the various call statements have been defined in the standard COBOL macro file.
For Compatibility Mode development the following files are needed:
MENUSON.USL | relocatable library |
SL.PROG | run-time library |
STANDARD.LIB | COMMON-LINKAGE area |
STDMACRO.LIB | standard COBOL macros |
For Native Mode development the following files are needed:
STDRL.NMOBJ | relocatable library |
STDXL.NMPROG | run-time library |
STANDARD.NMLIB | COMMON-LINKAGE area |
STDMACRO.NMLIB | standard COBOL macros |
Also included in this document are various stand-alone programs and jobstreams which may prove useful.
If something happens during the processing of a program that makes it impossible to continue then this routine should be called in order to produce a diagnostic report and terminate the program.
The diagnostic report will use information from the COMMON-LINKAGE area, which contains all the communication areas used by the VPLUS, IMAGE and KSAM intrinsics, plus most of the standard utility routines. The report will be displayed on the $STDLIST device as well as being output to a print file with the name ERROR.
After producing the report UERROR will call USERCLOSE
in case any application-specific data needs to be appended to the report, then it will call the QUITPROG
intrinsic to abort the program. UERROR will never return control to the calling program.
Most of the standard COBOL macros will automatically call UERROR if an unexpected condition occurs, therefore its use should be transparent.
A large number of applications interface with CODA-IAS which requires an additional communication area to be defined within the USER-LINKAGE area, for use by the IASLINK routines. In the event of an error this routine will append IAS details to the diagnostic reports (both the $STDLIST and printed versions) produced by UERROR.
This routine is invoked with the %PRINTIASERROR
macro, which must be included in USERCLOSE
before the %CLOSEIAS
macro. It will be ignored unless there is an IAS failure to report.
This set of routines is used to manipulate dates by converting from GREGORIAN format (CCYYMMDD) to JULIAN format (DDDDDDDDD), and back again.
GREGORIAN dates are named after Pope Gregory who implemented the rule that every 4th year is a leap, except every 100th year (which is not), except every 400th year (which is!).
JULIAN dates are named after Julius Caesar, but don't ask me why. They represent a value which is expressed as a number of days since the base date, which is January 1st of the year 1. You should be aware that some systems use a different base date (eg: January 1st 1900), and some others use the format YYDDD where YY is the year number and DDD is the day number (between 1 and 366). However, as we use the Julian number only for intermediate calculations and not for storage its content is irrelevant.
Here are some examples of how to use Julian dates:
A by-product of obtaining the Julian number for a date is that it can provide the day of week - simply divide the number by 7 and examine the remainder:
Some systems require the use of week numbers in the format YYWW, where YY is the year number and WW is the week number (between 1 and 53). According to international standards each week starts on a Monday, and week number 1 of any year is the 1st week of that year that contains a Thursday. The UWEEK routine uses these standards as the default, but they may be overridden if required.
The WEEKENDING routine will return with the date of the last day in the week. This uses the default of Monday for the 1st day of the week but this may be overridden if required.
The following routines use the UDATE-
areas which are defined within the COMMON-LINKAGE copylibrary entry. Upon returning from any of these routines the contents of UDATE-STATUS
should be examined. If the value is not zero then the routine found an error, with the relevant error message being placed in VIEW-WINDOW
.
This will take the contents of GREGORIAN-DATE
and convert it to a number which will be returned in JULIAN-DAYS
. A value will also be inserted in UDATE-DAY-OF-WEEK
indicating the day name.
This will take the contents of JULIAN-DAYS
and convert it to a date which will be returned in GREGORIAN-DATE
.
This will take the contents of GREGORIAN-DATE
and convert it to a week number which will be returned in WEEK-NUMBER
. This uses the contents of UDATE-DAY1-OF-WEEK
to signify the 1st day of the week (default value is 1 for Monday), and UDATE-WEEK1-CONTAINS
to signify the day that must be contained within the 1st week of the year (default value is 4 for Thursday). Either of these default values may be changed if required.
This will take the contents of GREGORIAN-DATE
and convert it to the date for the end of that week, returned in GREGORIAN-DATE
. This uses the contents of UDATE-DAY1-OF-WEEK
to signify the 1st day of the week (default value is 1 for Monday), which may be changed if required.
This is a stand-alone program that demonstrates the values that will be output by the various date routines for a given date.
It is invoked with the following MPE command:-
:run DATES.NMPROG.STANDARD
(1) | Display: | This program uses the following default values:- - the week starts on a MONDAY - week 1 contains the 1st THURSDAY in January Do you wish to make changes? (N/Y): |
Enter: | If not "Y" then skip to (3) | |
(2) | Display: | Use the following numbers to represent the DAY:
MON TUE WED THU FRI SAT SUN 1 2 3 4 5 6 0 |
Display: | Enter new value for DAY1 (0-6): | |
Enter: | day number to represent the start of the week | |
Display: | Enter new value for WEEK1 (0-6): | |
Enter: | day number to represent the contents of the 1st week | |
(3) | Display: | Enter date in format CCYYMMDD: |
Enter: | a valid date, or spaces to terminate | |
Display: | Date=CCYYMMDD,Julian=DDDDDDDDD,Week=YYWW,Day=<dow>,W/E=CCYY/MM/DD
where:- CCYYMMDD = the input date, echoed back DDDDDDDDD = the equivalent Julian day number YYWW = the year and week number <dow> = the day-of-week (Monday, Tuesday, etc) CCYY/MM/DD = the week-ending date |
The program will repeat from (3) until a blank line is entered.
This is a standalone program that prints the calendar for a given year on a single page. It shows the months across the page in three rows of four months each as in the following sample:-
Jan | Feb | Mar | Apr |
May | Jun | Jul | Aug |
Sep | Oct | Nov | Dec |
Each month is arranged into separate weeks from top-to-bottom, left-to-right, with the day-of-week shown on the left of the page, as in the following sample:-
J A N U A R Y MON 6 13 20 27 TUE 7 14 21 28 WED 1 8 15 22 29 THU 2 9 16 23 30 FRI 3 10 17 24 31 SAT 4 11 18 25 SUN 5 12 19 26
It is invoked with the following MPE command:-
:file CALENDAR;dev=LASER :run CALENDAR.NMPROG.STANDARD
Display: | Enter year in format CCYY: |
Enter: | the year number |
Before the advent of COBOL'85 with its de-edited MOVE statement it was difficult to convert a number in display format (usually from a VPLUS screen buffer) to internal format (COMP or COMP-3) so that it could be used in calculations or stored on a file.
The UNUMBER routines were specially written to deal with numbers which are entered via a VPLUS screen. They all rely on the fact that the VPLUS edit processing will only allow numeric values (including the minus sign and a decimal point). The field must also be SET to itself so that it contains the correct number of decimal places. The output field to these routines must be defined with the same number of implied decimal places (eg: if the input field is NUM2 then the output field must end in V99).
The size of the output field decides which of the various entry points to call. If the input field contains more digits (including leading zeros) that can be held in the output field then the value cannot be transferred, and the result will be zero.
The BNUMBER routines were a later addition and allow for the input of numbers which are not pre-validated by VPLUS (eg: when input to a batch program). Extra parameters include a status area, indicating if the input field contains non-numeric characters, and the number of decimal places.
The calling sequence is:
MOVE <input-field> TO UNUMBER-INPUT CALL "UNUMBERn" USING UNUMBER-INPUT, <output-field>.
UNUMBER-INPUT
is defined in COMMON-LINKAGE as PIC X(20).UNUMBER1 = 1 WORD = PIC S9(04) COMP UNUMBER2 = 2 WORDS = PIC S9(09) COMP UNUMBER4 = 4 WORDS = PIC S9(18) COMP UNUMBERP8 = 2 WORDS = PIC S9(07) COMP-3 UNUMBERP12 = 3 WORDS = PIC S9(11) COMP-3
The calling sequence is:
MOVE <input-field> TO UNUMBER-INPUT MOVE <decimal-places> TO UNUMBER-DECIMALS CALL "BNUMBERn" USING UNUMBER-INPUT, <output-field>, UNUMBER-DECIMALS, UNUMBER-STATUS.
BNUMBER1 = 1 WORD = PIC S9(4) COMP BNUMBER2 = 2 WORDS = PIC S9(9) COMP BNUMBER3 = 3 WORDS = PIC S9(11) COMP-3 BNUMBER4 = 4 WORDS = PIC S9(18) COMP
This set of routines allows the program to manipulate strings of text similar to those functions that are available in VPLUS processing specifications.
The calling sequence for these routines is as follows:
MOVE <length> TO USTRING-LENGTH CALL "routine" USING <input-string> <output-string> USTRING-LENGTH.
The "routine" names are as follows:-
Shift the non-blank characters into the centre of the string.
Shift the non-blank characters to the right of the string.
Shift the non-blank characters to the left of the string.
Shift all alpha characters from lower to upper case.
Shift all alpha characters from upper to lower case.
The smallest area that can be manipulated within a COBOL program is a single byte or character, which is comprised of 8 bits. However, there are times when it becomes necessary to set/unset/test individual bits, which is made possible by this set of routines.
The calling sequence for these routines is as follows:
CALL "routine" USING <target-word> BIT-NUMBER BIT-RESULT
BIT-NUMBER
identifies the bit to be processed. It must be in the range 0 to 15. Only one bit can be processed with each call.BIT-RESULT
will contain the result: 0 is OFF, 1 is ON.The "routine" names are as follows:-
This will ensure that the bit identified by BIT-NUMBER
is set ON. The contents of <target-word> will be changed accordingly.
This will ensure that the bit identified by BIT-NUMBER
is set OFF. The contents of <target-word> will be changed accordingly.
This will examine the bit identified by BIT-NUMBER
and place the result in BIT-RESULT
. The contents of <target-word> will be unchanged.
Anyone who reads the VPLUS manual will be overwhelmed by the enormous number of intrinsics that are required to perform all the functions necessary for the processing of a screen. However, it should quickly become apparent that certain high-level functions (eg: get a form, display a form, accept user's response) require a particular subset of these intrinsics to be executed in a particular sequence. Each of the following routines performs one of these high-level functions, and contains calls to the relevant set of VPLUS intrinsics.
All the data areas required by these routines have been defined in the COMMON-LINKAGE copylibrary member, therefore no additional data areas are required. In the event of a fatal error being detected each routine will call UERROR to produce a diagnostic report, then abort without returning control to the calling program.
The only VPLUS intrinsics that are not contained within any of these routines are VPUTBUFFER
and VGETBUFFER
. These must be called directly as they require access to the working storage area that holds a copy of the current screen contents, which is unique to each screen and which therefore cannot be defined in COMMON-LINKAGE.
This will load and initialise a new form, identified in VIEW-NFNAME
.
If the new form is a child or sibling to the previous form then data values from the previous form will be transferred to the new form before any initialisation processing takes place.
Calling sequence:
%SAVINITFORM(Para#,Formname#).
Processing:
Initialize VIEW-NUMERRS. Initialize VIEW-REPEATAPP, VIEW-FREEZAP. Call VGETNEXTFORM. Call VINITFORM. If VEDIT-ERRORS Call VERRMSG End-if. Set function key labels: 1-5=blank, 6=PRINT, 7=HELP, 8=EXIT
This will display the current form (including the data, window line and function key labels), wait for the user's response, then process it. By default the cursor will be placed on the first available entry field on the current screen, but this can be changed to a different field by placing the desired field name into VIEW-FIELD-NAME
before calling this routine.
If the user presses the PRINT or HELP key it will be processed before asking for another response. If the user presses the ENTER key his input will be validated, and input re-prompted if there are errors.
Calling sequence:
MOVE "<label>" TO VIEW-LABEL(n) < optional > MOVE "<message>" TO VIEW-WINDOW < optional > MOVE "<name>" TO VIEW-FIELD-NAME < optional > %ACCEPTENTER(Para#).
Processing:
If VIEW-WINDOW = spaces Set VIEW-WINDOW to "Type in details and press ENTER" End-if. Translate VIEW-WINDOW from message number to text (if required). Call VPUTWINDOW, set VIEW-WINDOW to spaces. Translate VIEW-LABELS from message numbers to text (if required). Call VSETKEYLABELS. Load standard screen headings into fields STD-HDG-1 and STD-HDG-2. Call VSHOWFORM. If VIEW-FIELD-NAME <> spaces Call VPLACECURSOR to position cursor on desired field End-if. Call VREADFIELDS. Initialize VIEW-SHOWCONTROL. If f8 then EXIT. If f7 then call UHELP, repeat from line 1. If f6 then call VPRINTFORM, repeat from line 1. Reject any function key if corresponding label is blank. If f0 (ENTER key) Call VFIELDEDITS If NO-VEDIT-ERRORS Call VFINISHFORM End-if If VEDIT-ERRORS Call VERRMSG Repeat from line 1 End-if End-if.
This is the same as SB1-ACCEPT-ENTER-KEY except for the following:
Calling sequence:
%ACCEPTFUNCTION(Para#).
This will set the error flag of the specified field and increment VIEW-NUMERRS
. This is used if an error is detected with user input when validation is performed within the program instead of within the forms file.
Note that this should not be called more than once before returning to the previous %ACCEPTENTER
otherwise the window line will contain the error message associated with the last call, not the first one.
Calling sequence:
MOVE "<message>" TO VIEW-WINDOW MOVE "<name>" TO VIEW-FIELD-NAME %SCVETERROR(Para#) Return to previous %ACCEPTENTER.
Processing:
Call VGETFIELDINFO to convert VIEW-FIELD-NAME to VIEW-FIELD-NUM. Call VSETERROR. Set VIEW-FIELD-NAME to spaces.
This will replace the contents of a single field on the current form, unlike VPUTBUFFER
which replaces the entire buffer.
Note that if the error flag was previously set for the field that it will be unset.
Calling sequence:
MOVE "<data>" TO VIEW-FIELD-DATA MOVE "<name>" TO VIEW-FIELD-NAME %SDVPUTFIELD(Para#)
Processing:
Call VGETFIELDINFO to convert VIEW-FIELD-NAME to VIEW-FIELD-NUM. Call VPUTFIELD. Set VIEW-FIELD-NAME to spaces.
This will cause a message to be displayed in the window line which will blink until the next time the screen is displayed. If no message is provided then a standard default will be used.
This is typically used when the user initiates an action that may take some time. It not only tells him that the activity has started, but locks the keyboard (rejecting any further key strokes) until the activity has completed.
Calling sequence:
MOVE "<message>" TO VIEW-WINDOW < optional > %BLINKMSG(Para#)
Processing:
If VIEW-WINDOW = spaces Set VIEW-WINDOW to "Processing - please wait" End-if. Translate VIEW-WINDOW from message number to text (if required). Call VPUTWINDOW, set VIEW-WINDOW to spaces. Translate VIEW-LABELS from message numbers to text (if required). Call VSETKEYLABELS. Load standard screen headings into fields STD-HDG-1 and STD-HDG-2. Call SETABIT to set the blink option on the window line. Call SETABIT to lock the keyboard. Call VSHOWFORM. Call UNSETABIT to unlock the keyboard. Call UNSETABIT to unset the blink option on the window line.
Under normal circumstances if the user changes any data on the screen and presses a function key instead of the ENTER key the current screen contents are not transferred to the internal copy of the screen. This means that a call to VGETBUFFER
will not transfer the current screen contents into the calling program's working storage area, only the previous screen contents. The program will therefore not be made aware of any changes that may have taken place.
However, it is possible to capture the current screen contents by invoking the auto-read option on VREADFIELDS
. This acts as if the user pressed the ENTER key without any user intervention, thereby making the current data buffer available to VGETBUFFER
.
Unlike the %AUTOREAD
macro this also includes calls to VFIELDEDITS
and VFINISHFORM
, which means that the calling program should test for possible validation failures before proceeding further.
Calling sequence:
%SFAUTOREAD(Para#) If VEDIT-ERRORS repeat END-if
Processing:
Call SETABIT to turn auto-read option on. Call VREADFIELDS <returns immediately>. Call UNSETABIT to turn auto-read option off Call VFIELDEDITS If NO-VEDIT-ERRORS Call VFINISHFORM End-if If VEDIT-ERRORS Call VERRMSG End-if.
This routine allows the characteristics of a field on the current form to be temporarily changed without the need for a new form.
For each field it is possible to change any of the following:
enhancement | (TYPE = 1 or 4) (SPEC = H, I, B, U or NONE) |
field type | (TYPE = 2 or 5) (SPEC = O, D, P, R) |
data type | (TYPE = 3 or 6) (SPEC = CHAR, DIG, IMPn, NUM[n], DMY, MDY or YMD) |
Note the following:
Calling sequence:
MOVE "<name>" TO VIEW-FIELD-NAME MOVE 1/2/3 TO VIEW-CHANGEFIELD-ENTRIES MOVE n TO VIEW-CHNGFLD-TYPE(1) MOVE "<spec>" TO VIEW-CHNGFLD-SPEC(1) MOVE n TO VIEW-CHNGFLD-TYPE(2) < optional > MOVE "<spec>" TO VIEW-CHNGFLD-SPEC(2) < optional > MOVE n TO VIEW-CHNGFLD-TYPE(3) < optional > MOVE "<spec>" TO VIEW-CHNGFLD-SPEC(3) < optional > %SGVCHANGEFIELD(Para#)
Processing:
Call VGETFIELDINFO to convert VIEW-FIELD-NAME to VIEW-FIELD-NUM. Call VCHANGEFIELD. Set VIEW-FIELD-NAME to spaces.
Within an online function that uses a VPLUS screen there is a facility that enables the user to select his next transaction without having to exit back to a menu screen. This is done by calling USELECT
to display a list of options on the function key labels. The user selects one of the options by pressing the relevant function key, and the associated transaction code is loaded into MENU-AUTO-SELECT
. This will be processed as soon as the current transaction exits back to the menu program.
The options to be displayed are defined on the D-OTHER-OPTIONS dataset of the menu database (maintained by transaction MGR12) where the key value is the identity of the transaction code containing the call to USELECT
. Up to 18 different options may be defined, each consisting of a LABEL and a CODE. This mechanism enables the list of options to be varied without having to make changes to any program code.
It is usual to set aside a function key at certain points within the program, and to give it the label "OTHER OPTIONS". This allows the user to decide for himself when to invoke the selection mechanism.
Please also refer to the following:
When the USELECT routine is invoked the following actions take place:-
PROCEDURE DIVISION USING COMMON-LINKAGE, USER-LINKAGE. A-CL020-CONTROL SECTION. A-10-ENTRY. %VERSION(CL020#,01.005.001#,CR012#). PERFORM C-SELECT-CLAIM UNTIL F8 OR MENU-AUTO-SELECT NOT = SPACES. <<================ A-EXIT. GOBACK. C-SELECT-CLAIM SECTION. C-10-INIT. * load the form CMA02 and get search criteria. %SAVINITFORM(C-10#,CMA02#). INITIALIZE CMA02-BUFFER. MOVE "OTHER OPTIONS" TO VIEW-LABEL(4). <<================ C-20-ACCEPT. %VPUTBUFFER(C-10#,CMA02-BUFFER#). %ACCEPTENTER(C-20#) IF F8 GO TO C-EXIT. IF F4 <<================ %USELECT(C-20-ACCEPT#,C-EXIT#) <<================ END-IF. <<================ PERFORM CA-VALIDATE-SELECTION. IF VEDIT-ERRORS GO TO C-20-ACCEPT. PERFORM D-DISPLAY-DETAILS. C-EXIT. EXIT.
It is defined in the standards that no transaction should pass control to another transaction by a hard-coded CALL statement as this could lead to stack problems and uncontrolled system aborts. Instead the recommended procedure is to use the transaction auto selection mechanism to exit the current transaction before passing control to the next transaction, eventually returning to the first transaction.
This removes the possibility of stack overflows as each transaction's working storage is released before the next transaction is loaded. However, when returning to a transaction it's processing cannot resume from where it left off, it must always start from the very beginning.
This is not too much of a problem if the transaction's screen contains details from a single entity as the transaction is able to skip the initial user response and reload the screen details from the key value which is held in USER-LINKAGE. This gives the appearance that the transaction was resumed from its previous execution, even though it actually was not.
The problem arises when a screen is constructed from several entities, typically an enquiry screen that shows multiple pages of details. When the user returns to that screen he will want it to resume from the previously selected page, not restart from the first page. This problem can be solved by using the USCREENIN and USCREENOUT procedures.
USCREENOUT | will copy a designated portion of the program's working storage area to a temporary disk file. |
USCREENIN | will transfer the contents of this temporary disk file into the program's working storage area. |
The working storage area to be dumped is identified by delimiting it with two special items, called USCREEN-START
and USCREEN-FINISH
, each with a picture of PIC S9(9) COMP. Typically this would encompass the entire screen buffer and any dataset pointers.
The name of the temporary disk file used by these two routines will be the same as the current transaction code, which allows screen dumps for more than one transaction to exist at any one time. To allow for those circumstances where a dump file is created but the transaction sequence is abandoned by pressing the f8 EXIT key the menu program contains code that will delete any temporary file that exists with the same name as the transaction code.
IT IS VITAL, THEREFORE, THAT NO APPLICATION MODULE USES ITS OWN TEMPORARY FILE WHICH HAS THE SAME NAME AS ITS TRANSACTION CODE. |
USCREENOUT will copy the designated portion of the program's working storage area to a temporary disk file. This should be the last step in the transaction before it exits and passes control to the next transaction via the auto-select mechanism. If the user leaves the transaction by pressing the f8 EXIT key this routine should not be called.
USCREENIN will transfer the contents of this temporary file back into working storage, thus restoring all previous values, then delete the file. If the file does not exist then the working storage area will not be overwritten, and USCREEN-START
will be set to zero. This should be the first step in the transaction before it performs any screen processing. Because the program will be starting from the very beginning it must contain code to recognise that it should resume from a later point, and proceed to that particular point.
WORKING-STORAGE SECTION. 01 USCREEN-START PIC S9(9) COMP. <<============= 01 CMA02-BUFFER VALUE SPACES. 03 ...... 03 CMA02-LINE OCCURS 10. 05 ...... 01 W01-POINTERS. 03 W01-PAGE-COUNT PIC S9(9) COMP SYNC VALUE ZERO. 03 W01-NEXT-PAGE PIC S9(9) COMP SYNC VALUE ZERO. 03 W01-ADDR-CURR PIC S9(9) COMP SYNC VALUE ZERO. 01 USCREEN-FINISH PIC S9(9) COMP. <<============= LINKAGE SECTION. COPY COMAREA IN STANDARD NOLIST. COPY USERLINK IN COPYLIB. PROCEDURE DIVISION USING COMMON-LINKAGE, USER-LINKAGE. A-CL020-CONTROL SECTION. A-10-ENTRY. %VERSION(CL020#,01.005.001#,CR012#). * Restore values from previous selection (if available) <<======== %USCREENIN(A-10#). <<======== PERFORM C-SELECT-CLAIM UNTIL F8 OR MENU-AUTO-SELECT NOT = SPACES. IF MENU-AUTO-SELECT NOT = SPACES <<======== IF MENU-AUTO-SELECT NOT = "-1" <<======== ************ store values for use when program resumes <<======== %USCREENOUT(A-10#) <<======== END-IF <<======== END-IF. <<======== A-EXIT. GOBACK. C-SELECT-CLAIM SECTION. ****************************************************************** * Allow user to enter his selection criteria. ****************************************************************** C-10-INIT. * load the form CMA02 and get search criteria. %SAVINITFORM(C-10#,CMA02#). * Skip next bit if we are restarting from previous screen <<====== IF USCREEN-START NOT = ZERO <<====== GO TO C-30-DISPLAY. <<====== * initialize the screen buffer area. INITIALIZE CMA02-BUFFER. INITIALIZE W01-POINTERS. C-20-ACCEPT. %VPUTBUFFER(C-10#,CMA02-BUFFER#). %ACCEPTENTER(C-20#) IF F8 GO TO C-EXIT. PERFORM CA-VALIDATE-SELECTION. IF VEDIT-ERRORS GO TO C-20-ACCEPT. C-30-DISPLAY. PERFORM D-DISPLAY-DETAILS. C-EXIT. EXIT. D-DISPLAY-DETAILS SECTION. ****************************************************************** * Display details that meet user's selection criteria. ****************************************************************** D-10-INIT. IF USCREEN-START NOT = ZERO <<============= ******** resume from previous display <<============= MOVE ZERO TO USCREEN-START <<============= ELSE <<============= ******** load a new page of details <<============= PERFORM DB-GET-NEXT-PAGE <<============= END-IF. <<============= %SAVINITFORM(D-10#,CMA02A#). D-20-ACCEPT. IF W01-PAGE-COUNT > 1 MOVE "PREVIOUS PAGE" TO VIEW-LABEL(1). IF W01-NEXT-PAGE = 1 MOVE "NEXT PAGE" TO VIEW-LABEL(2). MOVE "REFRESH PAGE" TO VIEW-LABEL(3). MOVE "RESTART" TO VIEW-LABEL(4). %VPUTBUFFER(D-20#,CMA02-BUFFER#). %ACCEPTENTER(D-20#). EVALUATE TRUE WHEN F0 PERFORM DA-VALIDATE-SELECTION WHEN F1 PERFORM DC-GET-PREV-PAGE WHEN F2 PERFORM DB-GET-NEXT-PAGE WHEN F3 PERFORM DD-REFRESH-PAGE END-EVALUATE. IF NOT (F8 OR F4) IF VEDIT-ERRORS OR MENU-AUTO-SELECT = SPACES GO TO D-20-ACCEPT END-IF END-IF. D-EXIT. EXIT.
If it should become necessary to replace the standard jobstream processing screen within the menu system with a customised version the following set of routines will be needed:
USTREAMFIND | transfers the jobstream from the menu command file to the temporary file $OLDPASS |
USTREAMVALIDATE | validates the printer and user input values |
USTREAMXEQ | places user values into the job and streams it |
The communication area for these routines is contained within the entry USTREAM
of the STANDARD copylibrary. This also includes the COBOL macros and full documentation.
The communication area is defined as follows:-
01 USTREAM-AREA. 03 USTREAM-TRAN-CODE PIC X(8). 03 USTREAM-PARAM PIC X(72) OCCURS 15. 03 USTREAM-PRINTER PIC X(8). 03 USTREAM-SCHEDULE PIC X(16). 03 USTREAM-CIERR PIC S9(4) COMP. 03 USTREAM-COMMENT PIC X(50). 03 USTREAM-PRINTER-STATUS PIC S9(4) COMP. 03 USTREAM-PRINTER-CLASS PIC X(72). 03 USTREAM-PROMPT PIC X(30) OCCURS 15. 03 USTREAM-VALIDATION PIC X(72) OCCURS 15. 03 USTREAM-PARAM-STATUS PIC S9(4) COMP.
This will locate the definition of the required jobstream on the MENU database and load it USTREAM-AREA
.
Calling sequence:-
MOVE <tran-code> TO USTREAM-TRAN-CODE CALL "USTREAMFIND" USING COMMON-LINKAGE, USER-LINKAGE, USTREAM-AREA.
VIEW-NUMERRS
<> zero then VIEW-WINDOW
will contain an error message, otherwise the following will be true:-USTREAM-SCHEDULE
will contain the contents of ENTRYPOINT
for the selected transaction code.USTREAM-PROMPT(1)-(15)
will contain the prompt text extracted from the jobstream, identified by the keywords PARM01
to PARM15
. These can then be loaded into the screen display.USTREAM-VALIDATION(1)-(15)
will contain the validation specifications associated with each parameter. These optional specifications are contained within each PARMnn
line after the prompt text and delimited by "[" and "]".This will display the jobstream parameter screen, wait for the user's input, then validate it.
Calling sequence:-
MOVE <printer> TO USTREAM-PRINTER MOVE <user-input> TO USTREAM-PARAM(1)-(15) CALL "USTREAMVALIDATE" USING COMMON-LINKAGE, USER-LINKAGE, USTREAM-AREA.
PRINTER-STATUS
<> zero it means that <printer> is invalid, with the error message loaded into VIEW-WINDOW
. If the printer is valid then the characteristics will be loaded into PRINTER-CLASS
(for use by USTREAMXEQ).PARAM-STATUS
<> zero then the corresponding line of input data has failed its validation. VIEW-WINDOW
will contain the error message.This will insert the user's input into the jobstream and pass it to the operating system for processing.
Calling sequence:-
MOVE <schedule> TO USTREAM-SCHEDULE < optional > CALL "USTREAMXEQ" USING COMMON-LINKAGE, USER-LINKAGE, USTREAM-AREA.
USTREAM-SCHEDULE
<> spaces then this will be appended to the STREAM command in order to delay the start time of the job. If the STREAM command is successful the job number will be displayed on the $STDLIST device. The VPLUS screen must therefore have available a 14 character field into which the job number can be written.USTREAM-COMMENT
will contain a message, either OK, a warning, or an error. This should be displayed somewhere on the screen (but not the window line).USTREAM-CIERR
<> zero then VIEW-WINDOW
will contain an error message.$CONTROL SOURCE,DYNAMIC $INCLUDE STDMACRO $INCLUDE USERMACR %ID(UJOBTEST#,Tony Marston#,26th June 1985#). $TITLE "Accept jobstream parameters from screen" ****************************************************************** * REMARKS: * * This tests the jobstream facility from a user application. * * USTREAMFIND is called to build the job in file $OLDPASS. * * USTREAMVALIDATE validates printer and user input. * * USTREAMXEQ inserts the user parameters and streams the job. * ****************************************************************** * VPLUS FORMS: * * MK02 - parameter substitution * MK02A - display job number * ****************************************************************** * AMENDMENT HISTORY: * * 1) Use new routines instead of USTREAM1 and USTREAM2. * Tony Marston - 22/05/91 - version 01.001.000 * ****************************************************************** %ED. DATA DIVISION. WORKING-STORAGE SECTION. * Subscript for PARM numbers 01 W01-PARM-NUMBER PIC 99. 01 MK02-BUFFER VALUE SPACES. 03 MK02-STD-HEAD-1 PIC X(78). 03 MK02-STD-HEAD-2 PIC X(78). 03 MK02-DATA. 05 MK02-PRINTER-ID PIC X(08). 05 MK02-LINES OCCURS 15. 07 MK02-DISPLAY PIC X(30). 07 MK02-ACCEPT PIC X(30). 05 MK02-COMMENT PIC X(50). 05 MK02-JOB-NUMBER PIC -(13)9. COPY USTREAM IN STANDARD. LINKAGE SECTION. COPY COMAREA IN STANDARD NOLIST. COPY USERLINK IN STANDARD NOLIST. PROCEDURE DIVISION USING COMMON-LINKAGE, USER-LINKAGE. %DEBUG(UJOBTEST#) A-UJOBTEST-CONTROL SECTION. A-10-START. %VERSION(UJOBTEST#,01.001.000#, #). PERFORM B-PROCESS-PARAMETERS. IF NOT F8 PERFORM C-STREAM-JOB END-IF. A-EXIT. GOBACK. B-PROCESS-PARAMETERS SECTION. ****************************************************************** * Display prompts from any PARMnn lines and accept user's input. ****************************************************************** B-10-INIT. %SAVINITFORM(B-10#,MK02#). PERFORM BA-LOAD-PARAMETERS. B-20-ACCEPT. %ACCEPTENTER(B-20#). IF ENTER-KEY PERFORM BB-VALIDATE IF VEDIT-ERRORS GO TO B-20-ACCEPT END-IF END-IF. B-EXIT. EXIT. BA-LOAD-PARAMETERS SECTION. ****************************************************************** * Load the default printer and the prompt text into the screen. ****************************************************************** BA-10-PRINTER. * Load the default printer identity MOVE MENU-PRINTER-ID TO MK02-PRINTER-ID. %VPUTBUFFER(BA-10#,MK02-BUFFER#). BA-20-JOBSTREAM. INITIALIZE USTREAM-AREA. * Load the jobstream into $OLDPASS MOVE <jobstream name> TO USTREAM-TRAN-CODE. %USTREAMFIND(BA-20#). IF VEDIT-ERRORS GO TO BA-EXIT. BA-30-PARAMS. * Load the parameters into the screen PERFORM VARYING W01-PARM-NUMBER FROM 1 BY 1 UNTIL W01-PARM-NUMBER > 15 MOVE USTREAM-PROMPT(W01-PARM-NUMBER) TO MK02-DISPLAY(W01-PARM-NUMBER) END-PERFORM. %VPUTBUFFER(BA-30#,MK02-BUFFER#). BA-EXIT. EXIT. BB-VALIDATE SECTION. ****************************************************************** * Validate the printer id and user input ****************************************************************** BB-10-INIT. %VGETBUFFER(BB-10#,MK02-BUFFER#). %BLINKMSG(BB-10#). * Load printer identity MOVE MK02-PRINTER-ID TO USTREAM-PRINTER. * This line is entirely optional MOVE "AT=23:00" TO USTREAM-SCHEDULE. * Transfer user's input to the communication area PERFORM VARYING W01-PARM-NUMBER FROM 1 BY 1 UNTIL W01-PARM-NUMBER > 15 MOVE MK02-ACCEPT(W01-PARM-NUMBER) TO USTREAM-PARAM(W01-PARM-NUMBER) END-PERFORM. %USTREAMVALIDATE(BB-10#). BB-20-CHECK-PRINTER. IF USTREAM-PRINTER-STATUS <> ZERO MOVE "PRINTER-ID" TO VIEW-FIELD-NAME %SCVSETERROR(BB-20#) GO TO BB-EXIT END-IF. BB-30-CHECK-PARAMS. IF USTREAM-PARAM-STATUS <> ZERO MOVE USTREAM-PARAM-STATUS TO W01-PARM-NUMBER STRING "ACCEPT" W01-PARM-NUMBER DELIMITED BY SIZE INTO VIEW-FIELD-NAME END-STRING %SCVSETERROR(BB-30#) END-IF. BB-EXIT. EXIT. C-STREAM-JOB SECTION. ****************************************************************** * Call USTREAMXEQ to stream this job. ****************************************************************** C-10-INIT. * All fields are display-only except for JOB-NUMBER %SAVINITFORM(C-10#,MK02A#). %BLINKMSG(C-10#). * Insert user parameters and stream the job %USTREAMXEQ(C-10#). C-20-DISPLAY. * Get the job number issued by MPE %VAUTOREAD(C-20#). %VGETBUFFER(C-20#,MK02-BUFFER#). * Comment area indicates success or failure MOVE USTREAM-COMMENT TO MK02-COMMENT. IF USTREAM-CIERR <> ZERO MOVE USTREAM-CIERR TO MK02-JOB-NUMBER END-IF. * Display job number and wait for user's response %VPUTBUFFER(C-20#,MK02-BUFFER#). %ACCEPTFUNCTION(C-20#). C-EXIT. EXIT.
Each application runs as a child process under the MENU application, but none of these child processes is allowed to open and access the MENU database directly. However, it can be accessed indirectly by this set of routines.
These routines work by passing control back to the father process (the MENU program) in order to retrieve the requested record, which puts the results into an extra data segment before passing control back to the calling program (the MENUSON program).
The following routines are currently available:-
GET-MENU-TRAN | retrieves an entry from the M-TRAN dataset |
GET-MENU-USER | retrieves an entry from the M-USER dataset |
GET-MENU-PRINTER | retrieves an entry from the M-PRINTER dataset |
The following dataset definition is required in working storage:
COPY MENUMC IN STANDARD.
Calling sequence:
MOVE <trancode> TO MC-TRAN-CODE CALL "GET-MENU-TRAN" USING COMMON-LINKAGE, USER-LINKAGE, M-TRAN-DATA. IF IMAGE-NO-ENTRY <entry does not exist> END-IF.
The following dataset definition is required in working storage:
COPY MENUMD IN STANDARD.
Calling sequence:
MOVE <userid> TO USER OF MD-USER CALL "GET-MENU-USER" USING COMMON-LINKAGE, USER-LINKAGE, M-USER-DATA. IF IMAGE-NO-ENTRY <entry does not exist> END-IF.
The following dataset definition is required in working storage:
COPY MENUME IN STANDARD.
Calling sequence:
MOVE <printer> TO ME-PRINTER-ID CALL "GET-MENU-PRINTER" USING COMMON-LINKAGE, USER-LINKAGE, M-PRINTER-DATA. IF IMAGE-NO-ENTRY <entry does not exist> END-IF.
This routine will examine a string of up to 40 characters and extract 4 keywords of up to 16 characters each. It is used where a name needs to be broken down into separate words in order to provide alternative keys for a search mechanism (eg: via a KSAM file).
The input string is examined for individual words which are terminated by a space, a comma, or a period. Any word of less than 4 characters is ignored. All keywords will be upshifted.
For example, the string "Thomas, Richard and Harold" would yield the following keywords: "THOMAS", "RICHARD", "HAROLD" and " ".
This routine requires the following area in working storage:
01 UEXTRACT-AREA. 03 UEXTRACT-INPUT-STRING PIC X(40). 03 UEXTRACT-SEARCH-KEY PIC X(16) OCCURS 4.
Calling sequence:
MOVE <string> TO UEXTRACT-INPUT-STRING CALL "UEXTRACT" USING UEXTRACT-AREA.
This routine is called before initiating a read of a KSAM file to determine whether the key value provided by the user requires an exact match or a generic match. A generic match is indicated when the input string is terminated with a single "*" (asterisk). For example, "FRED" will look for an exact match, whereas "FRED*" will match only the 1st 4 characters. The values "*FRED" and "FR*ED" are invalid.
This routine requires the following area in working storage:
01 USTRING-AREA. 03 USTRING-INPUT-STRING PIC X(80). 03 USTRING-MAX-LENGTH PIC S9(4) COMP. 03 USTRING-LENGTH PIC S9(4) COMP. 03 USTRING-STATUS PIC 9. 88 USTRING-EXACT VALUE 0. 88 USTRING-GENERIC VALUE 1. 88 USTRING-INVALID VALUE 2. 03 FILLER PIC X.
Calling sequence:
MOVE <string> TO USTRING-INPUT-STRING MOVE <keylength) TO USTRING-MAX-LENGTH. CALL "USTRING" USING USTRING-AREA. IF USTRING-INVALID < invalid format for a generic key IF USTRING-EXACT MOVE USTRING-MAX-LENGTH TO KSAM-KEYLEN ELSE MOVE USTRING-LENGTH TO KSAM-KEYLEN END-IF. %CKSTART(A#,KSAM#,EQ#,USTRING-INPUT-STRING#,1#,KSAM-KEYLEN#). IF KSAM-NO-RECORD < no records found > PERFORM UNTIL KSAM-END-OF-FILE %CKREAD(A#,KSAM#) IF KSAM-OK IF ksam-value(1:KSAM-KEYLEN) = input(1:KSAM-KEYLEN) < record is valid - process it > ELSE SET KSAM-END-OF-FILE TO TRUE END-IF END-IF END-PERFORM.
The SOUNDEX routine will take a string of text (up to 80 characters in length) and produce a result in the format Xnnn (1 alpha followed by 3 numerics). This is typically used to create a soundex key from a name, where similar sounding names will produce the same soundex value. This can be built as a search mechanism in an IMAGE database, thus avoiding the overhead of a separate KSAM file.
The formula for deriving the soundex value is as follows:-
Calling sequence:
01 SOUNDEX-VALUE PIC X(4). MOVE <input-string> TO UTEXT-INPUT. CALL "USOUNDEX" USING COMMON-LINKAGE, SOUNDEX-VALUE.
This will issue a conditional lock (mode 6) using the contents of the standard communication area (COMAREA). If any part of the lock is unable to be established then the following will take place:-
This program will create copy library entries for IMAGE datasets or VPLUS forms. Each entry will be added to a text file called COPYLIST, which can be copied into any copy library. As this file is in copylib format (ie: columns 73/80 contain the module names) the entire file can be copied in a single operation.
Program dialog:
(1) | Display: | Generate Form file or Database layout (F/D) ? |
Enter: | "F" or "D" | |
If "F": | Display: | Enter Forms File name |
Form name ? | ||
Prefix for data names (no "-") ? | ||
If "D": | Display: | Enter Database name |
Password ? | ||
Dataset name ? | ||
Prefix for data names (up to 3 characters, no "-") ? |
This program will create a file containing prints of selected VPLUS forms by using the VPRINTFORM intrinsic. The output file can then be printed using the FORMLIST utility which is described elsewhere in this document. This allows forms to be designed using FORMSPEC, then printed for inclusion in any design/specification document.
Data fields will not be left blank but filled as follows:-
Program dialog:
(1) | Display: | Disc file name or space to exit: |
Enter: | name of disc file | |
(2) | Display: | **** File <name> already exists
OK to PURGE Y/N [N] |
Enter: | "Y" or "N" | |
(3) | Display: | Formsfile name or space to exit: |
Enter: | name of formsfile file | |
(4) | Display: | Form name or space to exit: |
Enter: | name of form | |
(5) | Display: | <form> printed to <file> |
This is a FIJI (Friendly Interactive Job Interface) utility that takes the input file (usually created by the VIEWDOC program) and uses QEDIT to add the necessary control characters for printing on the laserjet. These control characters are added to a copy of the input file, therefore the original file is not changed in any way.
The following print modes are available:
If PORTRAIT mode is selected the print file is created with a forms message as a prompt to load the special cartridge.
This will then stream a job to create the print file, which will be directed to device LASER.
It is also possible to create the print file online, instead of using FIJI to stream a job. Please do the following:-
It may be useful to obtain screen prints after an application has been developed so that the data fields contain real values instead of being filled with X's and 9's. The following procedure shows how to create the FORMLIST file from the application instead of the VIEWDOC program. In addition to the screen contents each page will contain the window message and the function key labels.
PURGE FORMLIST
FILE FORMLIST;DEV=DISC;REC=-80;SAVE
This will output to a disc file rather than a spool file.
SETJCW VIEWFORMLISTCLOSE=2
This tells the screen print utility not to close the output file until the program terminates, instead of after each page.
SETJCW VIEWPRINTCONTROL=1
<optional>
This causes the VPRINTFORM intrinsic to underline all data fields.
It is not possible to mix screens from the menu system and the application system in the same output file as they are separate processes and require separate output files. |
RESET FORMLIST
The FORMLIST file is now ready for printing using one of the methods described previously.
This FIJI job uses QUIZ to create reports from a DICTIONARY/3000 database as an alternative to those produced by QSHOW. The reports are printed on A4 paper via the laserjet, and are suitable for inclusion in any system documentation.
The report contents are as follows:-
This will list all manual and detail datasets (not autos) in the sequence in which they have been defined for the selected database. Each page will show the dataset name, title, and the elements which it contains. Against each element name will be shown the size (in COBOL's PICTURE format). Search items will be shown as either UNIQUE or REPEATING KEYS, with the sort item if appropriate.
This will list all elements in name sequence, showing the element title, size, and description text.
This optional report will list the description text for each of the datasets.
Procedure:
Note: The Wide option (132 columns) is more or less redundant
This will then stream the relevant job.
This program allows text (ie: field labels) within a VPLUS `fast' formsfile to be changed. This can be used, for example, to produce a foreign-language version of the file without the need to use FORMSPEC to make the changes manually.
The original formfile is not changed in any way - the file is copied and all changes are made in the copy.
A print file is produced (name = FORMLIST) of the original file, and again after all changes have been made. The report is in two parts:-
Each text change requires two strings to be input - the original text and the replacement text. These two strings MUST be the same length as it is impossible to alter the total length of the screen image within the formfile. The '^' character can be used to indicate the space character. For example, a change from "NAME" to "NOM" would not be allowed, but "NAME" to "NOM^" would.
The change can be limited to a single form (including all forms within the same forms family), or to all forms within the file.
After each text change has been input the program will read through the file and make any changes. It will report the number of changes made on each form, plus the total number for the whole file.
The changes are terminated by entering spaces for the source text.
Program dialog:
Some applications run the FIJI program beneath the Menu system (ie: as a son process) to stream jobs as this has more options regarding the validation of runtime parameters than the default processing provided within the Menu system itself. Some parameters may require values that are already known to the Menu system, and it can be frustrating for the user to have to enter these values a second time.
Whenever the Menu program creates a son process it writes a selection of values to an XDS (Extra Data Segment). FIJI, however, cannot access an XDS, but it can access a data file. The FIJIINFO program is used to create a data file using the contents of the Menu XDS.
The file is called USERINFO, temporary, 46 bytes long, and contains a single record with the following format:
COMPANY PIC X(2) USER-ID PIC X(8) USER-NAME PIC X(20) PASSWORD PIC X(8) PRINTER PIC X(8)
The run command for the FIJIINFO program must therefore be included within the MENU database so that the USERINFO file is created before the FIJI program itself is run. This can either be within the command file for the FIJI transaction itself, or within the entries for the logon company. The values within the USERINFO file are set after the Menu LOGON screen is successfully processed.
This utility is used whenever there has been an update to the menu program, or any of the standard copy libraries, macros or utilities. It will create the correct group structure and transfer the relevant files from the STANDARD account. It is initiated as follows:
FIJI MENUIMP.PUB.STANDARD
This will ask the following questions:
(If both sets of files are required then this utility must be run twice)
If the Development Environment is chosen certain files are required for the initial implementation only. These files are subsequently customised during the development of the project, and therefore should not be overwritten with the skeleton copies.
This is a stand-alone batch program that will ensure that all users of the menu system (MENU) are logged off. This is to cater for those situations where users are in the habit of forgetting to log off before they go home at the end of their working day. This can cause problems with overnight backups as files which are still being accessed cannot be stored.
The existing shutdown procedure is not effective on unattended terminals, especially those without a time-out value being in force, or those which are running external programs via type "MP" transactions. Sessions which are waiting for input from the terminal cannot be interrupted by other processes, only aborted.
The program is initiated with the following commands:-
!FILE MENU.DATA=MENU.DATA.<account> !RUN MENUDOWN.NMPROG.<account>
It should be included in a jobstream with a username having at least "AM" capability, but preferably "SM" capability - otherwise the program may abort when trying to issue the ABORTJOB command.
The program has the following steps:-
"SHOWJOB JOB=@S"
to list all active sessions.If the program cannot complete successfully it will produce the usual diagnostic report (to $STDLIST as well as a print file called ERROR) and set the standard jcw (called "JCW") to a value of 9999, thus preventing the remainder of the jobstream from being executed.
The program will produce a trace of all actions taken by writing to $STDLIST, as in the following example:
:FILE MENU.DATA=MENU.DATA.STANDARD :RUN MENUDOWN.NMPROG.STANDARD MENUDOWN 01.000.000 09/16/92 11:16:24 11:51:31 - SETTING COMPANY TIMEOUTS 11:51:31 - LOGGING OFF DEVICES a) 11:51:31 - MESSAGE SENT TO FILE LDEV0110.PUB.STD FOR USER TONY 11:51:31 - PAUSE FOR THE MESSAGE TO SINK IN 11:56:31 - CHECKING ACTIVE SESSIONS (SHOWJOB JOB=@S) JOBNUM STATE IPRI JIN JLIST INTRODUCED JOB NAME #S819 EXEC QUIET 112 112 WED 9:03A MGR.BWDEV #S828 EXEC QUIET 126 126 WED 9:48A JULIA.BWDEV b) #S846 EXEC 110 110 WED 11:04A TONY,MGR.STD #S848 EXEC 117 117 WED 11:04A SYLVIA.PRQ #S844 EXEC 123 123 WED 11:00A STEVE,MGR.CIPHER #S849 EXEC QUIET 120 120 WED 11:21A MIKE,MGR.PRQ #S823 EXEC QUIET 136 136 WED 9:21A DAVE,MGR.TSL c) 11:56:32 - SESSION ACTIVE ON DEVICE 0110 - ABORTJOB #S00846 11:56:35 - RESETTING COMPANY TIMEOUTS END OF PROGRAM
In this example:
This is a stand-alone program that will make global changes to the contents of the command file on the MENU database, without having to use the existing online function (MGR11) on individual entries.
The program is initiated with the following command:-
(1) | Log into the account of the relevant MENU database. | |
(2) | RUN MENUCF.[NM]PROG.STANDARD | |
(3) | Display: | Enter source string: |
Enter: | <string>, or <RETURN> to exit | |
(4) | Display: | Enter target string: |
Enter: | <replacement string> | |
(5) | Display: | Source=<source string>
Target=<target string> Is this correct? (YES/NO): |
Enter: | <YES or NO>
(program will then list all lines to be changed) |
|
(6) | Display: | Do you wish to implement these changes? (YES/NO): |
Enter: | <YES or NO>
Program will repeat from (3). |
NOTES:
This is a stand-alone program that will enable the contents of any MENU database to be amended without the need to do it manually via the online maintenance transactions. It has more intelligence than a QUERY XEQ file as it will reject entries that already exist without either aborting or adding duplicates. NOTE: This program cannot amend records - it can only delete or add.
This accepts all parameters from the $STDIN device, and is terminated with the `//' characters. It is therefore possible to use pre-defined parameters in a file by appending STDIN=filename to the run command.
:RUN MENULOAD.PROG Enter COMMAND, HELP, or `//' to terminate HELP Valid commands are: 1) RENAME <trancode>,<trancode> 2) DELETE TRAN-CODE <trancode> 3) DELETE TRAN-GROUP <trangroup> 4) DELETE OTHER-OPTIONS <trancode> 5) DELETE COMMAND <command-id> 6) ADD TRAN-GROUP <trangroup> <name> 7) ADD TRAN-CODE <trancode> <tran desc> GROUP=<trangroup>,ENTRY=<entrypoint>,TYPE=<type> END 8) ADD MENU <menucode> LINE=nnnn,TRAN-CODE=<trancode> (repeat as necessary) END 9) ADD COMMAND <command-id> L=nnn;<data...................................> (repeat as necessary) END 10) ADD OTHER-OPTIONS <trancode> LABEL=<label>,TRAN-CODE=<trancode> (repeat as necessary) END 11) ADD USER <userid> <name> FIRST=<tran> PASS=<pword> GROUP=<group> where <userid> includes the company prefix 12) ADD TRAN-USER <userid> GROUP=<trangroup> where <userid> includes the company prefix 13) ADD TRAN-USER <userid> TRAN=<trancode> where <userid> includes the company prefix 14) ADD USER-GROUP <usergroup> <name> where <usergroup> includes the company prefix Enter COMMAND, HELP, or `//' to terminate //
This series of utility programs will allow the structure of an IMAGE database to be changed for those clients who do not have any third- party products (eg: ADAGER, DBGENERAL). These utilities are:-
BASECAP | ensure that the dataset capacities of the new schema are not less than the current capacities |
BASEDUMP | dump a database to a serial disk file |
BASELOAD | load a database from a serial disk file |
The BASEDUMP/BASELOAD programs will cater for the following types of database restructuring:
This cannot convert any items of type R (real). New items will be created with NULL values. |
(1) | Logon as the creator of the desired database. | |
(2) | RUN BASECAP.[NM]PROG.STANDARD | |
(3) | Display: | SCHEMA> |
Enter: | Name of database schema | |
Display: | DATABASE NAME=<basename> (from the schema)
Note: Will be opened in mode 1 with creator password. |
|
(4) | Display: | SET=<setname>, SCHEMA CAPACITY=<capacity>
DATABASE CAPACITY=<capacity> ** UPDATED ** Note: The schema entry will only be updated if its capacity value is less than the current database capacity. |
(5) | This will be repeated for each dataset, followed by: | |
Display: | DATABASE CAPACITY RESET COMPLETED |
(1) | Logon as the creator of the desired database. | |
(2) | RUN BASEDUMP.[NM]PROG.STANDARD | |
(3) | Display: | DUMP FILE> |
Enter: | Name of serial file (8 characters)
Note: This is created with a default size of 10,000 records. If this is not sufficient you must issue a file equate for a higher capacity, eg: FILE DSTOR;DEV=DISC;REC=100000 |
|
(4) | Display: | DUMPFILE ALREADY EXISTS, OK TO PURGE (N/Y)>
(ignored if file does not exist) |
Enter: | "Y" to delete file (this is automatic in jobstreams)
"N" to reprompt |
|
(5) | Display: | DATABASE> |
Enter: | Database name, with group if different from logon group.
Note: Will be opened in mode 8 (other readers, no writers). Will use the creator password. |
|
(6) | Display: | UNLOAD EDIT (N/Y)> |
Enter: | "N" (default) will unload all datasets
"Y" will prompt at each dataset |
|
(7) | Display: | UNLOAD AUTOMATIC MASTERS? (N/Y)> |
Enter: | "N" (default) to ignore automatic masters
"Y" to include automatic masters (if changing to a manual master) |
|
(8) | Display: | <setname> <type>, ENTRIES=<entrycount>/<capacity> |
(9) | Display: | DATASET IS EMPTY (no records, nothing to dump)
or AUTO NOT UNLOADED (if answer at 7 is "N") |
(10) | Display: | TO BE UNLOADED? (Y/N)> (if reply at 6 is "Y") |
Enter: | "Y" (default) to unload this dataset
"N" to ignore this dataset |
|
(11) | Display: | SET NOT UNLOADED (if reply at 10 is "N")
or <count> RECORDS UNLOADED IN sss.mmm SECONDS |
(12) | Repeat from 5 for each dataset, followed by: | |
Display: | DATABASE LOAD COMPLETED |
(1) | Logon as the creator of the desired database. | |
(2) | RUN BASELOAD.[NM]PROG.STANDARD | |
(3) | Display: | DUMP FILE> |
Enter: | Name of serial file (8 characters)
Note: This must have been created by program BASEDUMP. |
|
(4) | Display: | OLD BASE NAME: <old database name>
NEW BASE NAME> |
Enter: | new database name, if different from the old name
<RETURN> will default to the old name Note: Will be opened in mode 3 (exclusive), and will use the creator password. |
|
(5) | Display: | DATASET <setname> DOES NOT EXIST, ENTER NEW NAME>
(if the setname does not exist in the new schema) |
Enter: | new set name (ie: change of name)
<RETURN> will ignore this dataset |
|
(6) | Display: | SET NOT RELOADED
(if new name not supplied at 5, or set is an automatic master) |
(7) | Display: | <setname> <type>, ENTRIES=<entrycount>/<capacity> |
(8) | Display: | <itemname> NOT FOUND, NEW ITEM NAME>
(if the itemname does not exist in this dataset) |
Enter: | new item name (ie: change of name)
<RETURN> will ignore this item |
|
(9) | Display: | NULL ITEM LIST - SET NOT RELOADED
(no items from the dumpfile exist in the dataset) |
(10) | Display: | <count> RECORDS RELOADED IN sss.mmm SECONDS |
(11) | Repeat from 5 for each dataset, followed by: | |
Display: | DATABASE LOAD COMPLETED |
!JOB DBCHANGE,MGR.account,DATA !COMMENT ************************************************************* !COMMENT * Sample jobstream to convert a database, using programs !COMMENT * BASEDUMP, BASECAP and BASELOAD !COMMENT ************************************************************* !RESET MENU !PURGE DSTOR !TELL @.account; DATABASE DUMP STARTING !RUN BASEDUMP.PROG.STANDARD DSTOR MENU N N !TELL @.account; SCHEMA CAPACITY UPDATE STATING !RUN BASECAP.PROG.STANDARD MENUSC !TELL @.account; DATABASE PURGE STARTING !RUN DBUTIL.PUB.SYS,PURGE MENU !TELL @.account; DATABASE REBUILD STARTING !FILE DBSTEXT=MENUSC !RUN DBSCHEMA.PUB.SYS;PARM=1 !RUN DBUTIL.PUB.SYS,CREATE MENU !TELL @.account; DATABASE RELOAD STARTING !RUN BASELOAD.PROG.STANDARD DSTOR MENU !TELL @.account; QUERY UPDATE STARTED !RUN QUERY.PUB.SYS B=MENU ; 1 F ALL D-CONTROL.VERSION-NUMBER REPL VERSION-NUMBER="01.010.004";END EXIT !TELLOP ** JOB COMPLETE ** !EOJ
- END -