ASAM ARB
Application programs and AR/CTL use the ARB to exchange information such as call functions and results. Code the ARB in the working storage area of an application program. The program can use a single ARB for all calls, or it can use a separate ARB for checkpoint support and for each sequential file that uses ASAM support. If the program uses a single ARB for multiple call types, it must reinitialize the ARB for each call.
The following example shows the ARB in COBOL:
...
DATA DIVISION.
WORKING-STORAGE SECTION.
01 ARCARB.
02 ARCARB-TYPE PIC X(8) VALUE '$ARCARB '.
02 FUNC-CODE PIC X(8) VALUE 'READ'.
02 DDNAME PIC X(8) VALUE 'ddname '.
02 STATUS-CODE PIC X(2) VALUE SPACES.
02 FILLER PIC X(2) VALUE SPACES.
02 ULRECL PIC S9(8) COMP.
ARB Type | This field identifies the ARB. |
---|---|
Function Code | This field (at offset 8 from the beginning byte 0) indicates the type of access you want for the next call. |
DDname | This field identifies the ddname specified in the associated data set option member (also known as the FCB). |
Status Code | This field contains the status code that the application program can check to determine the results of a call to AR/CTL. The status codes that AR/CTL can return are recorded with the calls. |
ULRECL | If the data set has an undefined record format and you are writing a record, set this field to the length of the record being written. If AR/CTL is reading a record, it sets this field to the length of the record being read. |
OPEN | Open the ASAM data set identified in the call. The ASAM I/O area can contain operands to indicate data set usage. For more information see ASAM-I-O-areas. |
CLSE | Close the ASAM data set identified in the call. |
READ | Read records from the ASAM data set identified in the call. |
WRITE | Write records to the ASAM data set identified in the call. |
ROLD | Restore the staged-output ASAM data set identified in the call to the last application program checkpoint by purging all uncommitted data from the staging area. The ROLD function does not result in checkpoint processing, and AR/CTL deletes only the staged output for the ASAM data set referenced by the ARB you specify in the ASAM call. AR/CTL does not delete any staged output for other ASAM data sets and does not signal any DBMS to back out uncommitted updates. The ROLD function can help simplify application program logic. For example, if the application program holds output records in a buffer until a commit point, it can now issue the WRITE function to write the output records to a staged-output ASAM data set immediately. If an error occurs, the program can issue the ASAM call with the ROLD function to back out the changes. This function repositions an ASAM data set only if it uses output staging. |