HLI: IFDIAL processing

From m204wiki
Revision as of 23:14, 15 July 2016 by ELowell (talk | contribs) (→‎Overview)
(diff) ← Older revision | Latest revision (diff) | Newer revision → (diff)
Jump to navigation Jump to search

Overview

This chapter describes basic processing using an IFDIAL thread for application programmers who are using the Host Language Interface facility.

See IFDIAL thread calls for descriptions of HLI calls that are available using an IFDIAL thread.

Terminal type interface

IFDIAL thread

An IFDIAL thread provides a line-at-a-time terminal emulation type interface between a host language application and Model 204. With an IFDIAL thread, a host language program functions as a terminal, transmitting a line of input to Model 204 and receiving a line of output from Model 204.

An IFDIAL thread supports the use of the companion calls, IFREAD and IFWRITE, to communicate with Model 204. Use an IFREAD call to transmit data (a line of output) from Model 204 to your application program and an IFWRITE call to transmit data (a line of input) back to Model 204.

Using an IFDIAL thread, you can pass Model 204 commands, ad hoc or stored SOUL procedures, or Application Subsystem Management applications from an HLI application (batch) program to Model 204. You can also extract data from Model 204, use the data in your program, and put the results into your Model 204 database.

Note: If you are using an IFDIAL thread, you must code the calls, specifications, and corresponding program logic that are valid for use with this thread.

See HLI: Threads for more information about IFDIAL threads. See HLI: Function summary for a description of HLI calls.

Communication between Model 204 and an IFDIAL thread

The underlying communications mechanism for a terminal type interface drives IFDIAL thread functioning. A parent-child protocol directs the interchange between the partner programs, that is, between Model 204 (the parent) and the IFDIAL thread (the child).

In all communications between IFDIAL and Model 204, Model 204 is the parent and directs the interchange. The IFDIAL thread is the child. If the Model 204 side wants input, the IFDIAL thread is required to send input.

Also, an IFDIAL thread must process all output from Model 204 that normally goes to a terminal, such as character prompts for logons and passwords or warning and broadcast messages.

Sample call sequences

Establishing an IFDIAL connection

The HLI application initiates the request to establish an IFDIAL connection to Model 204. To start an IFDIAL thread, the HLI application program must specify the IFDIAL call.

For example, a host language application might issue calls in the following order to establish an IFDIAL connection to Model 204:

  1. IFDIAL to start an IFDIAL thread.
  2. IFREAD to receive the Model 204 response.
  3. IFWRITE to log in to Model 204.
  4. IFREAD to receive the Model 204 response.
  5. IFWRITE to supply a password.
  6. IFREAD to receive the Model 204 response:
    .
    . perform IFDIAL processing
    .

To disconnect the IFDIAL thread and finish processing, the HLI application issues an IFHNGUP call. The following sections show sample call sequences once the IFDIAL connection is established.

Submitting a SOUL request

Once the connection is established, you can use an IFDIAL thread to submit an ad hoc SOUL request to Model 204.

For example, to submit a SOUL request after an IFDIAL connection is established (see the previous section), an HLI application might read an input file containing a SOUL request into a program storage area, and then issue HLI calls in the following order:

.
. establish the IFDIAL connection
.

  1. IFWRITE inside a program loop, to issue the SOUL statements until all statements are sent to Model 204 (by referencing the program storage area).
  2. IFREAD to receive the Model 204 response.

    The program code might loop, issuing the IFREAD to read each line of output from Model 204 until there is no more output in the storage buffer.

Note: This sample shows the basic IFWRITE and IFREAD sequence for submitting a SOUL request. Always code your IFDIAL application to check the completion return code for these calls. See Checking IFWRITE and IFREAD return codes for information about checking the return codes for IFREAD and IFWRITE.

Invoking a stored SOUL procedure

Once the connection is established, you can use an IFDIAL thread to invoke a stored SOUL procedure.

For example, to invoke a stored SOUL procedure after an IFDIAL connection is established, an HLI application might issue calls in the following order:

.
. establish the IFDIAL connection
.

  1. IFWRITE to open a file.
  2. IFREAD to receive the Model 204 response.
  3. IFWRITE to supply a password, if required.
  4. IFREAD to receive open file messages from Model 204.
  5. IFWRITE to issue the command to include the stored SOUL procedure.

Note: Always code your IFDIAL application to check the completion return codes for IFWRITE and IFREAD. See Checking IFWRITE and IFREAD return codes for information about checking these return codes.

Using the Model 204 Application Subsystem facility

Once the connection is established, you can use an IFDIAL thread to access the Model 204 Application Subsystem facility.

For example, to use the Model 204 Application Subsystem facility after an IFDIAL connection is established (see Establishing an IFDIAL connection) an HLI application might issue calls in the following order:

.
. establish the IFDIAL connection
.

  1. IFWRITE to invoke an Application Subsystem (APSY).
  2. IFREAD to receive the results of the APSY execution.

Notes: Make sure to use an Application Subsystem that is designed to run on a line-at-a-time IFDIAL thread. Also, always code your IFDIAL application to check the completion return codes for IFWRITE and IFREAD, as described in Checking IFWRITE and IFREAD return codes.

See Application Subsystem development for information about the Application Subsystem facility.

Checking IFWRITE and IFREAD return codes

Always code your IFDIAL application to check the Model 204 completion return code from the previous IFWRITE or IFREAD call before issuing the next IFWRITE or IFREAD.

The IFDIAL application must issue IFREAD or IFWRITE depending on which call Model 204 expects next. Model 204 indicates which of these calls is required next by returning a particular completion code from the previous IFREAD or IFWRITE.

If the Model 204 completion return code from the previous IFREAD or IFWRITE equals 1, the IFDIAL application must issue an IFWRITE. Or, if the return code equals 2, the application must issue an IFREAD.

This is necessary to ensure proper communication with Model 204 during IFDIAL processing.

In the sample coding sequence in Submitting a SOUL request (and also in HLI: Threads) the IFDIAL application loops to send lines of input to Model 204 by issuing multiple calls to IFWRITE.

This loop must be controlled by checking the value of the return code each time before the next IFWRITE call is issued. For example, the following COBOL statement is coded:

PERFORM WRITE-LOOP UNTIL RETCODE = 2 OR INRECS = 0.

where INRECS is a counter that is decremented for each record sent from the input file, and when INRECS equals zero, all SOUL statements have been sent to Model 204.

If during processing Model 204 encounters an error in one of the SOUL statements from the input file, the IFDIAL application must receive the error message from Model 204 by issuing IFREAD before issuing another call to IFWRITE.

Any number of other types of messages might be issued by Model 204, for example, messages from the operator, that might interrupt an IFWRITE processing loop and must be received by the IFDIAL application.

Also, the same type of checking must be done for an IFREAD processing loop. For example, a loop that issues IFREAD to read each line of output from Model 204 until there is no more output in the storage buffer must be controlled by checking the return code for a value of 1, which indicates that an IFWRITE call is required next.

See Sample COBOL program using a stored procedure for an example of return code checking in a COBOL program that uses IFDIAL processing.

Using stored procedures

An HLI call in a host language program that invokes another program to perform a specific function, or functions, is called a stored procedure call. The stored procedure can be a SOUL procedure or a set of Model 204 commands.

As briefly outlined in Invoking a stored SOUL procedure, you can use an IFDIAL thread for stored procedure calls.

Operations against the database

You can use a stored procedure with an IFDIAL thread to perform different types of operations against the database, depending on the needs of the HLI application.

Although you can use IFDIAL applications with stored procedures for any type of terminal activity, the following examples are the most common:

  • Sending and receiving Model 204 images, which are defined in the program storage area of the HLI application.
  • Issuing Model 204 commands, for any Model 204 command that can be issued at a terminal such as MONITOR, and receiving output generated by Model 204.
  • Transferring procedures in and out of Model 204 files, which allows you to maintain SOUL procedures in external software configuration management systems.

The following sections describe IFDIAL processing using stored SOUL procedures with images.

Using stored procedures for image processing

Sending and receiving Model 204 images

Because SOUL allows Model 204 images to be read or written to a terminal, an HLI application using an IFDIAL thread that operates in terminal emulation mode can send and receive Model 204 images.

A Model 204 image is a SOUL feature that allows a request to read and process terminal input or input from sequential files. An image describes the format of an external record.

SOUL statements can refer to each item described in the image definition. Using the images facility, you can open a file, read records to the image, write records to a terminal or to a file, and close the file. This capability allows an application to write multiple output files and reports based on a single pass of the database.

The syntax for reading and writing images with SOUL is as follows:

OPEN {TERMINAL | %VAR} FOR {INPUT [OUTPUT] | OUTPUT [INPUT] | INOUT} READ [IMAGE] imagename FROM {TERMINAL | %VAR} [PROMPT {'string' | %VAR}] WRITE [IMAGE] imagename ON {TERMINAL | %VAR} CLOSE {TERMINAL | %VAR}

See Images for more information about images.

Example of a stored procedure used to process images

The following SOUL (User Language) example is a stored procedure, named IFDIAL-WRITE, which finds records and writes images to the IFDIAL application in the Sample COBOL program using a stored procedure.

User Language stored procedure example

* * OPEN MODEL 204 DATA FILE * OPEN VEHICLES * BEGIN * USER LANGUAGE PROGRAM TO SHOW USE * OF IFDIAL AND IMAGES * IMAGE VEHICLES.LIST VL.BODY IS STRING LEN 4 VL.COLOR IS STRING LEN 8 VL.MAKE IS STRING LEN 10 VL.MODEL IS STRING LEN 20 VL.YEAR IS PACKED DIGITS 2 END IMAGE * * OPEN PATH TO IFDIAL PROGRAM * OPEN TERMINAL FOR OUTPUT PREPARE IMAGE VEHICLES.LIST * * FIND AND WRITE IMAGES TO IFDIAL PROGRAM * FOUND_SET: FIND ALL RECORDS FOR WHICH MAKE=FORD AND COLOR=BLUE END FIND LOOP: FOR EACH RECORD IN FOUND_SET * %VEHICLES.LIST:VL.BODY = BODY %VEHICLES.LIST:VL.COLOR = COLOR %VEHICLES.LIST:VL.MAKE = MAKE %VEHICLES.LIST:VL.MODEL = MODEL %VEHICLES.LIST:VL.YEAR = YEAR * WRITE IMAGE VEHICLES.LIST ON TERMINAL * END FOR * END

Example of IFDIAL application that processes images

The following COBOL example performs IFDIAL communication to Model 204 using the stored procedure, IFDIAL-WRITE, shown in the User Language stored procedure example. See Using a special purpose subroutine for the CVTFLAG subroutine.

Sample COBOL program using a stored procedure

*************************************************************** * THIS IS A SAMPLE COBOL PROGRAM WHICH DOES * IFDIAL COMMUNICATION TO M204. *************************************************************** IDENTIFICATION DIVISION. PROGRAM-ID. IFDIALUL. * ENVIRONMENT DIVISION. INPUT-OUTPUT SECTION. FILE-CONTROL. SELECT REPORT-FILE ASSIGN TO UT-S-REPORT. SELECT INPUT-FILE ASSIGN TO UT-S-INPUT. * DATA DIVISION. FILE SECTION. FD REPORT-FILE LABEL RECORDS ARE OMITTED BLOCK CONTAINS 0 RECORDS DATA RECORD IS OUT-BUFFER. 01 OUT-BUFFER PIC X(133). * WORKING-STORAGE SECTION. 01 ERROR-FUNCTION PIC X(8) VALUE SPACES. 01 DISPLAY-STATUS-IND PIC 9(5) VALUE ZERO. 01 WS-OUTPUT-REPORT-LINE. 05 WS-CCTL-CHAR PIC X VALUE SPACES. 05 MAKE PIC X(10). 05 FILLER PIC X(5) VALUE SPACES. 05 MODEL PIC X(20). 05 FILLER PIC X(5) VALUE SPACES. 05 BODY PIC X(4). 05 FILLER PIC X(5) VALUE SPACES. 05 YEAR PIC X(2). 05 FILLER PIC X(5) VALUE SPACES. 05 COLOR PIC X(8). * 01 OUTPUT-AREA PIC X(256) VALUE SPACES. * 01 INPUT-AREA PIC X(256). 01 FORMATED-INPUT-AREA REDEFI NES INPUT-AREA. 05 BODY PIC X(4). 05 COLOR PIC X(8). 05 MAKE PIC X(10). 05 MODEL PIC X(20). 05 YEAR PIC X(2). * 01 INTEGER-CALL-ARGS COMP SYNC. 05 STATUS-IND PIC 9(5) VALUE 99. 05 WRITE-STAT PIC 9(5). 05 READ-STAT PIC 9(5). 05 LANGUAGE-IND PIC 9(5) VALUE 2. * 01 IFREAD-FLAGS. 05 IFREAD-MSG-LENGTH PIC 9999 COMP SYNC. 05 IFDIAL-ERROR-MSG PIC X VALUE "N". 88 ERROR-MSG VALUE "Y". 05 IFDIAL-NEW-PAGE PIC X VALUE "N". 88 NEW-PAGE VALUE "Y". 05 IFDIAL-USER-RESTARTED PIC X VALUE "N". 88 USER-RESTARTED VALUE "Y". 05 IFDIAL-PASSWORD-REQUEST PIC X VALUE "N". 88 PASSWORD-REQUEST VALUE "Y". 05 IFDIAL-READ-REQUEST PIC X VALUE "N". 88 READ-REQUEST VALUE "Y". 05 IFDIAL-INFO-MSG PIC X VALUE "N". 88 INFO-MSG VALUE "Y". * 01 STRING-CALL-ARGS. 05 INPUT-FLAGS PIC X. 05 M204-ERR-MESSAGE PIC X(80) VALUE SPACES. 05 VMCF-CHANNEL PIC X(8) VALUE "M204VMIO". 05 LOGON-MSG PIC X(16) VALUE "LOGON SUPERKLUGE". 05 LOGON-PASSWORD PIC X(8) VALUE "PIGFLOUR". 05 REQUEST-NAME PIC X(14) VALUE "I IFDIAL-WRITE". PROCEDURE DIVISION. * MAIN-ROUTINE. * INITIALIZATION. OPEN OUTPUT REPORT-FILE CALL "IFDIALN" USING STATUS-IND, LANGUAGE-IND, VMCF-CHANNEL. DISPLAY "IFDIALN STATUS ", STATUS-IND. IF STATUS-IND IS NOT EQUAL ZERO MOVE "IFDIALN " TO ERROR-FUNCTION PERFORM ERROR-ROUTINE. * * LOGON-PROCESS * MOVE LOGON-MSG TO OUTPUT-AREA. CALL "IFWRITE" USING WRITE-STAT, OUTPUT-AREA. DISPLAY "IFWRITE STATUS ", WRITE-STAT. IF WRITE-STAT = 2 PERFORM READ-LINE THRU READ-LINE-EXIT UNTIL READ-STAT = 1 OR READ-STAT = 12. IF PASSWORD-REQUEST DISPLAY "PASSWORD REQUEST ", IFDIAL-PASSWORD-REQUEST. MOVE SPACES TO OUTPUT-AREA MOVE LOGON-PASSWORD TO OUTPUT-AREA CALL "IFWRITE" USING WRITE-STAT, OUTPUT-AREA PERFORM READ-LINE THRU READ-LINE-EXIT UNTIL READ-STAT = 1 OR READ-STAT = 12. * * MAIN-LOOP * START USER LANGUAGE TRANSACTION TO RETRIEVE * RECORDS. * IFWRITE USES REQUEST-NAME TO EXECUTE * STORED USER LANGUAGE PROCEDURE IFDIAL-WRITE * AT NEXT INPUT REQUEST, TERMINATE. * MOVE SPACES TO OUTPUT-AREA. MOVE REQUEST-NAME TO OUTPUT-AREA. CALL "IFWRITE" USING WRITE-STAT, OUTPUT-AREA. PERFORM MAIN-LOOP UNTIL READ-STAT NOT = 2 GO TO TERMINATION. * MAIN-LOOP. PERFORM READ-LINE THRU READ-LINE-EXIT. MOVE CORRESPONDING FORMATED-INPUT-AREA TO WS-OUTPUT-REPORT-LINE. WRITE OUT-BUFFER FROM WS-OUTPUT-REPORT-LINE. * * READ-LINE CALLS CVTFLAG (CONVERT FLAGS) * TO PROCESS MODEL 204 OUTPUT FROM IFREAD * READ-LINE. MOVE SPACES TO INPUT-AREA. CALL "IFREAD" USING READ-STAT, INPUT-AREA, INPUT-FLAGS. IF READ-STAT = 100 GO TO TERMINATION. DISPLAY "IFREAD STATUS ", READ-STAT, " DATA ", INPUT-AREA. CALL "CVTFLAG" USING INPUT-FLAGS, IFREAD-FLAGS. MOVE ZERO TO INPUT-FLAGS. IF USER-RESTARTED GO TO TERMINATION. IF ERROR-MSG OR INFO-MSG GO TO READ-LINE. READ-LINE-EXIT. EXIT. * ERROR-ROUTINE. MOVE STATUS-IND TO DISPLAY-STATUS-IND. DISPLAY "CRITICAL ERROR ENCOUNTERED WITH FUNCTION: " ERROR-FUNCTION ", WITH A RETURN CODE OF: " DISPLAY-STATUS-IND. MOVE SPACES TO ERROR-FUNCTION. MOVE SPACES TO M204-ERR-MESSAGE. IF ERROR-FUNCTION NOT EQUAL "IFHNGUP" THEN PERFORM TERMINATION. * TERMINATION. CLOSE REPORT-FILE. CALL "IFHNGUP" USING STATUS-IND. IF STATUS-IND NOT EQUAL 0 THEN MOVE "IFHNGUP" TO ERROR-FUNCTION PERFORM ERROR-ROUTINE. STOP RUN.

Using a special purpose subroutine

Sample subroutine to convert IFREAD flags

IFREAD returns a message descriptor flag as a series of bits. Each bit indicates the type of data received, the password prompt, error messages, and so on. The CVTFLAG (convert flags) subroutine example in Sample assembly language subroutine to convert IFREAD flags translates the IFREAD flags to COBOL character strings and refers to them with Level 88 statements.

The following sample COBOL program calls this subroutine after issuing the IFREAD call.

Sample assembly language subroutine to convert IFREAD flags

CVTFLAG CSECT 0 ENTRY CVTFLAG * * SAMPLE ASSEMBLY LANGUAGE PROGRAM FOR TRANSLATING THE * MESSAGE DESCRIPTOR FIELD RETURNED AS THE THIRD ARGUMENT * OF THE IFREAD CALL. * * THIS MODULE EXPECTS TWO PARAMETERS. THE FIRST IS THE * THIRD PARAMETER RETURNED BY THE IFREAD CALL, THE MESSAGE * DESCRIPTOR FIELD. THIS FIELD SHOULD BE DEFINED AS: * 01 MSG-DESC-FIELD PICTURE 9(8) COMP SYNC. * * THE SECOND PARAMETER IS AN 01 LEVEL WORKING STORAGE AREA * DEFINED AS FOLLOWS: * * 01 IFREAD-FLAGS. * 05 IFREAD-MSG-LENGTH PICTURE 9999 COMP SYNC. * 05 IFDIAL-ERROR-MSG PICTURE X VALUE 'N'. * 88 ERROR-MSG VALUE 'Y' * 05 IFDIAL-NEW-PAGE PICTURE X VALUE 'N'. * 88 NEW-PAGE VALUE 'Y' * 05 IFDIAL-USER-RESTARTED PICTURE X VALUE 'N'. * 88 USER-RESTARTED VALUE 'Y' * 05 IFDIAL-PASSWORD-REQUEST PICTURE X VALUE 'N'. * 88 PASSWORD-REQUEST VALUE 'Y' * 05 IFDIAL-READ-REQUEST PICTURE X VALUE 'N'. * 88 READ-REQUEST VALUE 'Y' * 05 IFDIAL-INFO-MSG PICTURE X VALUE 'N'. * 88 INFO-MSG VALUE 'Y' * THE CVTFLAGS SUBROUTINE MOVES THE FIRST HALF WORD OF THE * MESSAGE DESCRIPTOR FIELD MINUS 4 TO THE FIELD DESCRIBED * ABOVE AS 'IFREAD-MSG-LENGTH'. THIS IS THE TRUE LENGTH * OF THE DATA RECEIVED. THE SUBROUTINE THEN EXAMINES THE * FLAGS IN THE THIRD BYTE OF THE MESSAGE DESCRIPTOR FIELD * AND SET THE CORRESPONDING FLAGS IN THE COBOL WORKING * STORAGE AREA TO 'Y'. EACH TIME THE SUBROUTINE IS CALLED * ALL THE FLAGS ARE SET TO 'N' THEN THE APPROPRIATE FLAGS * ARE SET TO 'Y'. THE WORKING STORAGE FIELDS MUST BE ARRANGED * AS DESCRIBED ABOVE. THE LEVEL 88 FIELDS ARE OPTIONAL. * * NOTE: THIS SUBROUTINE IS AN EXAMPLE ONLY AND IS NOT SUPPORTED * BY ROCKET SOFTWARE. * ********** REGEQU SET REGISTER SYMBOLS STM R14,R12,12(R13) SAVE REGISTER LR 12,15 SET BASE REGISTER USING CVTFLAG,R12 ESTABLISH ADDRESSING LR R11,R13 SET UP SAVE AREA LINKAGE LA R13,SAVEAREA ST R11,4(R13) ST R13,8(R11) * * PROGRAM LOGIC STARTS HERE * * ADDRESS PARAMETERS L R2,0(R1) R2, INPUT PARAMETER ADDRESS L R3,4(R1) R3, OUTPUT PARAMETER LIST USING WSPARM,R3 ADDRESSING TO WS PARM AREA * RETURN LENGTH TO CALLER L R4,0(R2) R4, PARAMETER WORD SRL R4,16 SHIFT 16 BITS LEFT, LEAVING LENGTH SH R4,=Y(4) DECREMENT LENGTH BY 4 ACTUAL LEN. STH R4,LENGTH MOVE ACTUAL LENGTH TO USER * RETURN FLAGS TO CALLER MVI EMSG,C'N' CLEAR ALL ERROR MESSAGES MVC EMSG+1(FLAGLEN-1),EMSG PROPAGATE 'N' TO ALL FLAGS TM 2(R2),X'80' CLASS E MSG ? BZ *+4+4 NO, NEXT TEST MVI EMSG,C'Y' YES, TURN ON FLAG TM 2(R2),X'40' NEW PAGE ? BZ *+4+4 NO, NEXT TEST MVI NPAGE,C'Y' YES, TURN ON FLAG TM 2(R2),X'20' RESTARTED ? BZ *+4+4 NO, NEXT TEST MVI RESTART,C'Y' YES, TURN ON FLAG TM 2(R2),X'10' PASSWORD ? BZ *+4+4 NO, NEXT TEST MVI PASSWORD,C'Y' YES, TURN ON FLAG TM 2(R2),X'08' READ PROMPT ? BZ *+4+4 NO, NEXT TEST MVI READ,C'Y' YES, TURN ON FLAG TM 2(R2),X'04' CLASS I MESSAGE BZ *+4+4 NO, ALL DONE MVI INFO,C'Y' YES, TURN ON FLAG * * RETURN TO CALLER * L R13,SAVEAREA+4 RESTORE CALLERS REGISTERS LM R14,R12,12(R13) SR R15,R15 CLEAR R15 JUST FOR GOOD FORM BR 14 RETURN TO CALLER DROP R12,R3 END ADDRESSING TO BASE, WSPARM LTORG SAVEAREA DS 18F'0' WSPARM DSECT MAP OF COBOL WORKING STORAGE RET ARGS. LENGTH DS H'0' LENGTH OF MESSAGE EMSG DS X ERROR CLASS OF MSG NPAGE DS X NEW PAGE INDICATOR RESTART DS X USER RESTARTED PASSWORD DS X PASSWORD PROMPT READ DS X READ PROMPT INFO DS X I CLASS MESSAGE FLAGLEN EQU *-EMSG NUMBER OF 1 BYTE FLAGS END

Coding guidelines for IFDIAL applications

Designing your IFDIAL application

Design your HLI application program and SOUL procedure to work together.

For example, your HLI application reads a list of accounting numbers to generate a report. The HLI application sends an account number to the SOUL procedure. After the SOUL procedure receives the account record and performs data manipulation, Model 204 returns the data to the HLI program for final reporting.

When the HLI program sends an account number, the SOUL procedure must be expecting it. Conversely, when the SOUL procedure sends a completed record, the HLI program must be expecting it. The two programs must be synchronous so that the data is usable.

To minimize programming time and effort and to maximize processing efficiency, write a general purpose IFDIAL application that uses basic IFREAD and IFWRITE logic but does not perform data operations.

Design your generic IFDIAL application so that it can be used with a variety of SOUL procedures. Allow the SOUL procedure to do the work of manipulating data and formatting reports.

Note that Model 204 provides a BATCH2 utility that allows you to run a SOUL procedure without having to code an IFDIAL application.

Checking the Model 204 completion return code

Always check the Model 204 completion return code from the IFREAD or IFWRITE call previously issued to ensure that the next call issued by the HLI application is the one that is expected by Model 204.

A return code of 1 from IFREAD or IFWRITE requires an IFWRITE next; or, a return code of 2 requires an IFREAD next.

Writing special purpose subroutines

Write special purpose subroutines to simplify IFDIAL logic, such as for login or user restart.

Formatting data

The format of the data to be exchanged in your HLI application and SOUL programs must agree.

Sending and receiving Model 204 images

When sending and receiving Model 204 images, be sure that the working storage definition and the image correspond.

To send images from your SOUL procedure to your IFDIAL host language program, use the following statement:

WRITE IMAGE imagename TO TERMINAL

To transmit data from your IFDIAL host language program to your SOUL procedure, use the following statement:

READ IMAGE imagename FROM TERMINAL

See Sending and receiving Model 204 images for more information about images.

Handling terminal messages and prompt strings

Because IFDIAL uses a terminal-type interface, you are responsible for messages and prompt strings.

Encapsulate IFREAD and IFWRITE calls in your subroutines or paragraphs to filter out messages and error codes and return only the expected data to the application.

Note: IFREAD returns message descriptor flags as a series of bits. Each bit indicates the type of data received, the password prompt, error messages, and so on.

The CVTFLAG (convert flags) subroutine example translates the IFREAD flags to COBOL character strings and refers to them with Level 88 statements.

Use IFATTN to activate ON attention

As with terminal applications, you can use the ON attention SOUL function. The IFATTN call activates ON attention. This attention interrupt is useful to escape out of any processing loop that two programs may engage in.

Using stored procedure calls

When using stored procedure calls, if your HLI application has many distinct functions, construct a separate SOUL procedure to handle each function.

For example, if your HLI program adds, deletes, and modifies records based on a transaction file, invoke a separate SOUL procedure for each function.

Using an application subsystem

When using stored procedure calls, if your HIL program invokes many SOUL procedures, install the procedures as Application Subsystem (APSY) to minimize overload.

See Application Subsystem development for information about the Application Subsystem facility.

See also