HLI: IFSTRT processing

From m204wiki
Jump to navigation Jump to search

Overview

This topic describes how to perform basic IFSTRT data processing operations for application programmers who are using the Host Language Interface facility.

If you are using multiple cursor IFSTRT thread functionality in your HLI application for the first time, see Using cursors on a multiple cursor IFSTRT thread.

Using record sets

A set of records is a group of records found in a file or group that meet the conditions of selection criteria specified in an HLI call. For example:

NAME = SMITH AGE = 60

See HLI: Find criteria for Model 204 data for information about specifying find conditions.

Creating a record set

Use the following HLI calls to select records from a file or group and create a record set for processing:

  • IFFAC
  • IFFIND
  • IFFNDX
  • IFFWOL

Current record set

The set of records currently being processed is the current set.

On a multiple cursor IFSTRT thread, you must explicitly specify the record set in the HLI call. On a single cursor IFSTRT thread, the current set is the one last created.

The COBOL coding excerpt below shows an IFFIND call on a multiple cursor IFSTRT thread that creates a found set of records (named WODOCS) and a call to IFRELR, which releases the record set when processing against the records is complete. The IFRELR call specifies the WODOCS record set.

WORKING-STORAGE SECTION. 01 CALL-PARMS. 05 RETCODE PIC 9(5) COMP SYNC. 05 DOCS-SPEC PIC X(61) VALUE 'IN FILE PROFS FD SEX=FEMALE;OCCUPATION=DOCTOR OR DENTIST;END;'. 05 DOCS-NAME PIC X(7) VALUE 'WODOCS;'. . . . PROCEDURE DIVISION. . . . * FIND CREATES RECORD SET * CALL "IFFIND" USING RETCODE,DOCS-SPEC,DOCS-NAME. * * PERFORM USER SUBROUTINE RECORD PROCESSING LOOP * THEN RELEASE RECORD SET * CALL "IFRELR" USING RETCODE,DOCS-NAME. . . .

See Example of cursor processing for an example that illustrates using a cursor to reference a found set. See HLI: Function summary for a description of HLI calls used to process record sets.

Using value sets

A set of values is a group of unique values of a field found in a file that meet the conditions of selection criteria in an HLI call. For example, for a field named AGENT, the following data values may be found stored in the file: SMITH, JONES, and GREEN.

See HLI: Find criteria for Model 204 data for information about specifying find conditions.

Creating a value set

Use the IFFDV call to select field values from a file and create a value set for processing.

You can create value sets using only fields with the FRV (For Each Value) or the ORDERED attribute.

See HLI: Model 204 fields and variables for information about field attributes.

Current value set

The set of values currently being processed is the current set.

On a multiple cursor IFSTRT thread, you must explicitly specify the value set in the HLI call. On a single cursor IFSTRT thread, the current set is the one last created.

See HLI: Function summary for a description of HLI calls used to process value sets.

Using lists

A list is a user-defined entity that holds copies of a found set of records for processing.

List processing is similar to set processing. However, placing records in a found set on a list allows the enqueue locks to be freed so that records can be accessed by other users. Also, you can modify the record set by adding additional records to the list or removing records from the list.

Creating a list

Use the following HLI calls to place records from a found set on a list for processing:

  • IFPROLS, on a multiple cursor IFSTRT thread
  • IFLIST, on a single cursor IFSTRT thread

Use IFPROL to add a record to a list, or IFRRFL to remove a record from a list. On a multiple cursor IFSTRT thread, use IFCLST to clear a list and IFRRFLS to remove records from a list.

See HLI: Locking behavior of HLI calls for information about record locking.

Example of list processing

The following COBOL coding excerpt calls IFPROLS to place records from a found set (named WODOCS) that contains female doctors and dentists on a list (called INCOME).

Subsequent calls to IFOCUR and IFFTCH allow the application to process records on the list. For example, a record processing loop might examine a record for INCOME values and report data in different annual income ranges.

When record processing is finished, IFRRFL removes the records from list INCOME.

WORKING-STORAGE SECTION. 01 CALL-PARMS. 05 RETCODE PIC 9(5) COMP SYNC. 01 FIND-PARMS. 05 FIND-NAME PIC X(7) VALUE 'WODOCS;'. 05 DOCS-SPEC PIC X(44) VALUE 'SEX=FEMALE;OCCUPATION=DOCTOR OR DENTIST;END;'. 01 LIST-PARMS. 05 LIST-SPEC PIC X(24) VALUE 'IN WODOCS ON LIST INCOME;'. 05 LIST-NAME PIC X(7) VALUE 'INCOME;'. 01 CURSOR-PARMS. 05 CURSOR-SPEC PIC X(38) VALUE 'ON LIST INCOME IN ORDER BY INCOME AMT;'. 05 CURSOR-NAME PIC X(7) VALUE 'DOCINC;'. 01 FETCH-PARMS. 05 DIRECTION PIC 9 COMP SYNC VALUE '1'. 05 EDIT-SPEC PIC X(44) VALUE 'EDIT (SSN,NAME,INCOME AMT)(A(9),A(30),J(8));'. 01 WORK-REC. 05 WORK-SSN PIC 9(9). 05 WORK-NAME PIC X(30). 05 WORK-INCOME-AMT PIC 9(8). . . . PROCEDURE DIVISION. . . . * FIND CREATES RECORD SET * CALL "IFFIND" USING RETCODE,FIND-SPEC,FIND-NAME. CALL "IFPROLS" USING RETCODE,LIST-SPEC. CALL "IFOCUR" USING RETCODE,CURSOR-SPEC,CURSOR-NAME. * * PERFORM USER SUBROUTINE LOOP TO PROCESS RECORDS IN LIST * INCLUDES CALLS SHOWN BELOW TO IFFTCH AND IFRRFL * TO REMOVE RECORD FROM LIST WHEN FINISHED PROCESSING * CALL "IFFTCH" USING RETCODE,WORK-REC,DIRECTION, CURSOR-NAME,EDIT-SPEC. . . . CALL "IFRRFL" USING RETCODE,LIST-NAME,CURSOR-NAME. . . .

Using cursors on a multiple cursor IFSTRT thread

A cursor is a user-defined entity that identifies an existing record or value set that has been named on a multiple cursor IFSTRT thread.

Opening and closing a cursor

Two basic functions are required to manipulate each cursor on a multiple cursor IFSTRT thread:

  • IFOCUR specifies a cursor name and opens the cursor to a set that has been previously established by the successful execution of one of the following calls using the Compiled IFAM feature:
    • IFFAC
    • IFFDV
    • IFFIND
    • IFFNDX
    • IFFWOL
    • IFSORT
    • IFSRTV

    You can open more than one cursor against the same named set to maintain different positions within the set; and you can open several cursors against several different record sets. You can also open a cursor on a list.

    You can also establish a cursor by using IFFRN or IFSTOR and then reference that cursor by using the name of the saved compilation.

  • IFCCUR closes the named cursor and indicates that processing against the cursor is complete.

Naming a cursor

The following guidelines apply for naming cursors:

  • Name must be unique.
  • Specify the cursor name as a short character string; the maximum length is 32 characters.
  • Cursor name must begin with a letter (A-Z or a-z), which can be followed by one or more occurrences of:
    • Letter (A-Z or a-z)
    • Digit (0-9)
    • Period (.)
    • Underscore (_)
  • Avoid using a SOUL keyword for a cursor name. If in another specification you refer to a cursor name that is a keyword, Model 204 might incorrectly interpret the name.

Cursor processing

Positioning a cursor

In order to process records from a found set or a list on a multiple cursor IFSTRT thread, you must first open a cursor by issuing a call to IFOCUR that specifies the found set or list. Then use IFFTCH to advance to the next record.

Once you use IFFTCH to position the cursor, issue any of the following single record function calls:

If you need to obtain the internal database number of the record in the current cursor, use IFRNUM.

The IFFRN and IFSTOR functions implicitly allocate and open a cursor. The current record is the record whose number is specified in IFFRN, or the record just stored by IFSTOR. You can then manipulate the record using one of the single record function calls listed above.

See Individual record level IFSTRT calls for information on single record level IFSTRT thread calls. See also Multiple cursor IFSTRT thread example.

Example of cursor processing

The following COBOL coding excerpt opens a cursor to a found set (named FDFORD), which contains FORD records from a CARS file.

The application processes records inside a record processing loop (UPDATE-LOOP) using IFFTCH and performs different actions depending on the year. If the record is 1980 or later, the application updates the record by deleting the color blue. The application also deletes any CARS record that is older than (that is, year is earlier than) 1980.

Note: All calls in the records processing loop reference the found set using the cursor name (CRFORD).

WORKING-STORAGE SECTION. 01 CALL-PARMS. 05 RETCODE PIC 9(5) COMP SYNC. 01 FIND-PARMS. 05 FIND-NAME PIC X(7) VALUE 'FDFORD;'. 05 DOCS-SPEC PIC X(30) VALUE 'IN FILE CARS FD MAKE=FORD;END;'. 05 COUNT PIC 9(5) COMP SYNC. 01 CURSOR-PARMS. 05 CURSOR-SPEC PIC X(10) VALUE 'IN FDFORD;'. 05 CURSOR-NAME PIC X(7) VALUE 'CRFORD;'. 01 FETCH-UPDATE-PARMS. 05 DIRECTION PIC 9 COMP SYNC VALUE '1'. 05 EDIT-SPEC PIC X(53) VALUE 'EDIT(MAKE,MODEL,YEAR,COLOR)(A(15),A(15),J(4),A(10));'. 05 COMP-NAME PIC X(7) VALUE 'EDFORD;'. 01 WORK-REC. 05 WORK-MAKE PIC X(15). 05 WORK-MODEL PIC X(15). 05 WORK-YEAR PIC 9(4). 05 WORK-COLOR PIC X(10). . . . 01 FIELDS-PARMS. 05 FIELD-LIST PIC X(6) VALUE 'COLOR;'. 05 DFIELD-VALUE PIC X(5) VALUE 'BLUE;'. 05 DFIELD-NAME PIC X(6) VALUE 'COLOR;'. 05 FIELD-COUNT PIC X(8). PROCEDURE DIVISION. . . . * FIND CREATES RECORD SET * CALL "IFFAC" USING RETCODE,DOCS-SPEC,COUNT,FIND-NAME. MOVE COUNT TO TOT-RECS. PRINT 'TOTAL NUMBER OF FORD CARS IS ' TOT-RECS. * * OPEN CURSOR TO FOUND SET AND DO PROCESSING LOOP * CALL "IFOCUR" USING RETCODE,CURSOR-SPEC,CURSOR-NAME. PERFORM UPDATE-LOOP UNTIL TOT-RECS IS EQUAL TO ZERO. . . . * * UPDATE-LOOP SUBROUTINE TO PROCESS RECORDS IN CURSOR * FETCH A RECORD, * IF 1980 OR LATER, COUNT OCCURRENCES OF COLOR * IF ONE OR MORE, THEN DELETE VALUE OF BLUE AND UPDATE REC * ELSE, IF EARLIER THAN 1980, DELETE THE RECORD * UPDATE-LOOP. CALL "IFFTCH" USING RETCODE,WORK-REC,DIRECTION, CURSOR-NAME,EDIT-SPEC. IF WORK-YEAR IS GT 1980 THEN CALL "IFOCC" USING RETCODE,FIELD-COUNT,CURSOR-NAME, FIELD-LIST. MOVE FIELD-COUNT TO TOT-FIELDS. IF TOT-FIELDS IS GT ZERO THEN CALL "IFDVAL" USING RETCODE,DFIELD-NAME,DFIELD-VALUE, CURSOR-NAME. ELSE CALL "IFDREC" USING RETCODE,CURSOR-NAME. SUBTRACT 1 FROM TOT-RECS. . . .

Using the compiled IFAM facility

The Compiled Inverted File Access Method (IFAM) facility allows certain functions executed on IFSTRT threads to be compiled and stored. You can execute a compilation at a later time by specifying the name under which it was stored. You do not need to recompile the stored call.

Advantage of using Compiled IFAM calls

In the standard HLI implementation (without Compiled IFAM), Model 204 handles each call separately, looking up field names in the data dictionary, and parsing character parameter strings for each execution of a call.

Using the Compiled IFAM facility, you can request that Model 204 perform the initial parsing and dictionary reference once and then refer to the stored information in later calls.

Using the Compiled IFAM facility reduces the amount of CPU time and disk I/O that Model 204 uses to satisfy program calls.

Stored compilations and server tables

Model 204 stores compilations of HLI calls in the server tables: NTBL, QTBL, VTBL, and STBL. Refer to HLI: Model 204 tables for information about the Model 204 server tables and HLI calls.

You can use the IFFLUSH call to delete compilations that are no longer needed from these tables to make room for new compilations. IFFLUSH functions differently on standard and multiple cursor IFSTRT threads.

Certain calls, when issued on a multiple cursor IFSTRT thread, require that you use Compiled IFAM. You must specify a compilation name for the following HLI calls on a multiple cursor IFSTRT thread:

  • Find functions: IFFAC, IFFDV, IFFIND, IFFNDX, IFFWOL
  • Sort functions: IFSKEY, IFSORT, IFSRTV

Each of these calls establishes a found set and IFOCUR uses the compilation name of the previously compiled call to reference the named set. For example, IFOCUR might open a cursor to a found set (named FDFORD) that was established by a previously compiled IFFIND call.

You must also specify a compilation name for IFFRN, but this name is not referenced by IFOCUR. It is referenced by subsequent single record functions.

Compilation name parameter

A name parameter is required in all Compiled IFAM calls.

The name parameter specifies a character string that is used to identify the compilation. For example, you might specify a compilation name of ORDER1 for an IFFIND call as shown in the following example:

CALL "IFFIND" USING STATUS-IND, ORDER-SPEC, ORDER1.

where:

  • STATUS-IND is an integer variable for the Model 204 return code.
  • ORDER-SPEC is a find specification that creates a found set of records using the ORDERS file.
  • ORDER1 is the name that uniquely identifies the IFFIND compilation.

The Compiled IFAM form of IFFIND differs from the standard form of the call, which does not include the compilation name parameter. For example, on a single cursor IFSTRT thread you can specify the IFFIND call without using the Compiled IFAM facility, as shown in the following example:

CALL "IFFIND" USING STATUS-IND, ORDER-SPEC.

See Compiled IFAM calls for a list of HLI calls that can be used with the Compiled IFAM facility.

Naming a compilation

The following guidelines apply for compilation names on any type of IFSTRT thread:

  • The compilation name is a required input parameter for all Compiled IFAM calls. A null name string is the same as an omitted parameter.
  • The name must be unique.
  • Specify the compilation name as a short character string; the maximum length is 32 characters.

In addition, on a multiple cursor IFSTRT thread, the following guidelines apply for compilation names:

  • Compilation name must begin with a letter (A-Z or a-z), which can be followed by one or more occurrences of:
    • Letter (A-Z or a-z)
    • Digit (0-9)
    • Period (.)
    • Underscore (_)
  • Avoid using a SOUL keyword for a compilation name. If in another specification you refer to a compilation name that is a keyword, Model 204 might incorrectly interpret the name.

In addition, on a single cursor IFSTRT thread, any characters except the following are valid in the compilation name:

  • Blank space
  • Comma (,)
  • Left parenthesis (()
  • Right parenthesis ())
  • Equal sign (=)
  • Semicolon (;)

Three forms of Compiled IFAM calls

Three forms of IFSTRT thread calls are available using the Compiled IFAM facility. These calls function in different ways. The following options are available to accommodate different programming styles:

  • You can use a single call that compiles and executes with the name parameter that identifies the compilation. When the call executes, Model 204 saves the compiled version of the call.

    For example, when the following IFFIND call is executed, Model 204 stores the compilation as ORDER1:

    CALL "IFFIND" USING STATUS-IND,ORDER-SPEC,ORDER1.

    When the same IFFIND call is executed again or when another IFFIND call containing the same name parameter (ORDER1) is executed, Model 204 ignores the find specification (ORDER-SPEC) and uses the stored compilation without requiring recompilation.

  • You can use two calls, one is compile-only (HLI call with C suffix) and one is execute-only (HLI call with E suffix), with the name parameter that identifies the compilation for the two phases of Compiled IFAM processing: compilation and execution.

    This option involves a two-call procedure, useful in loop processing. Use the compilation form of the call outside the loop to compile (but not execute) the call specification. For example, you might issue the compilation-only form of IFFIND as shown in the following example:

    CALL "IFFINDC" USING STATUS-IND,ORDER-SPEC,ORDER1.

    Within the loop, issue the execution form of the call, thereby executing the previously compiled call. For example, you might issue the execute-only form of IFFIND as shown in the following example:

    CALL "IFFINDE" USING STATUS-IND,ORDER1.

The following table lists the HLI calls that are used with the Compiled IFAM facility.

An asterisk (*) indicates that you must use the compiled form of the call with a multiple cursor IFSTRT thread.

Compiled IFAM calls
Compute and execute Compile-only Execute-only
IFCTO IFCTOC IFCTOE
IFFAC* IFFACC IFFACE
IFFDV* IFFDVC IFFDVE
IFFIND* IFFINDC IFFINDE
IFFNDX* IFFNDXC IFFNDXE
IFFRN* IFFRNC IFFRNE
IFFTCH IFFTCHC IFFTCHE
IFFWOL* IFFWOLC IFFWOLE
IFGET IFGETC IFGETE
IFGETV IFGTVC IFGTVE
IFGETX IFGETC IFGETXE
IFMORE IFMOREC IFMOREE
IFMOREX IFMOREC IFMORXE
IFOCC IFOCCC IFOCCE
IFFOCUR* IFOCURC IFOCURE
IFPUT IFPUTC IFPUTE
IFSKEY* IFSKYC IFSKYE
IFSORT* IFSRTC IFSRTE
IFSRTV* IFSTVC IFSTVE
IFSTOR IFSTRC IFSTRE
IFUPDT IFUPDTC IFUPDTE

Sharing a compilation

Some calls that use the Compiled IFAM facility can share the specifications that Model 204 compiles for other functions.

The following calls can share precompiled specifications:

  • IFGET, IFMORE, and IFPUT

    When an IFGET, IFMORE, or IFPUT call is compiled, Model 204 does not save the data area address of the HLI application program. The application program can manipulate its buffers and data freely without losing any of the benefits of Compiled IFAM.

  • IFFAC and IFFIND
  • IFUPDT with a precompiled IFFTCH

Example of a shared compilation

An example of a shared compilation on a multiple cursor IFSTRT thread is an IFUPDTE (execute-only) call that updates the current record using data previously returned by IFFTCH.

In this example, using Compiled IFAM and specifying certain of the same parameter values as the previously compiled IFFTCH, IFUPDTE does the following:

  • Points to the same buffer area. (Both calls use WORK-REC, which contains the data fields defined in working storage.)
  • References the same cursor. (In this example, the cursor name is NAMERECS.)
  • Uses an identical edit specification, which describes the format of the data in the buffer.

IFUPDTE executes using the name of the previously compiled IFFTCH call. In this example, the IFFTCH compilation name is CUSTNAME.

The following COBOL coding excerpt shows the IFUPDTE and IFFTCH shared compilation.

WORKING-STORAGE SECTION. 01 WORK-REC. 05 WORK-SSN PIC 9(9). 05 WORK-NAME PIC X(30). . . . 01 CALL-PARMS. 05 RETCODE PIC 9(5) COMP SYNC. 05 CURSOR-NAME PIC X(9) VALUE 'CUSTNAME;'. 05 EDIT-SPEC PIC X(28) VALUE 'EDIT (SSN,NAME)(A(9),A(30));'. 05 COMP-NAME PIC X(9) VALUE 'NAMERECS;'. 05 DIRECTION PIC 9 COMP SYNC VALUE '1'. . . . PROCEDURE DIVISION. . . . CALL "IFFTCH" USING RETCODE,WORK-REC,DIRECTION,CURSOR-NAME, EDIT-SPEC,COMP-NAME. * * PERFORM UPDATE OPERATION MOVE SPACES TO WORK-NAME * CALL "IFUPDTE" USING RETCODE,WORK-REC,COMP-NAME. . . .

Using variables with precompiled specifications

Use %variables and field name variables (that is, %%variables) to make small but regular changes to precompiled specifications. You can assign values for %variables by including the variable buffer and variable specification parameters in HLI calls.

See HLI: Model 204 fields and variables for more information about %variables.

See also