Previous Topic: Advanced CA IDMS Programming TopicsNext Topic: Basic Mode


Calling a DC Program from a CA ADS Dialog

CA ADS dialogs can call COBOL, PL/I, or Assembler programs by using the LINK function. For example, a commonly used date conversion routine could be coded in COBOL for use by all CA ADS dialogs running under a DC system.

Because CA ADS calls your program using the LINK command, linkage conventions are the same as if the call were from another DC program.

The calling dialog can pass the following records to the linked program:

Within the linked program, you can issue DC RETURN statements with the NEXT TASK CODE parameter to perform pseudoconversational processing as required.

Extended Run Unit

The linked program may not need to issue any BIND statements or reestablish currencies if the CA ADS dialog establishes an extended run unit.

For more information on CA ADS and extended run units, see CA ADS Reference Guide.

Steps to Call a Program from CA ADS

To code a program to be called by CA ADS dialogs, perform the following steps:

  1. Define any passed records in the LINKAGE SECTION and code a PROCEDURE DIVISION USING statement.
  2. If an extended run unit has been established, do not issue a BIND RUN-UNIT statement. You can issue BIND RECORD statements for any records which have not already been bound for the run unit, and you can issue other appropriate BIND statements.
  3. Perform processing, as required.

    If an extended run unit has been established, do not issue FINISH or ROLLBACK statements within the called program. To issue either of these statements, return to the calling dialog with an indicator in a passed status field and let the dialog end the run unit. If you do not follow this procedure, the CA ADS program may receive an error (DC174019) when it tries to save currencies for a run unit that no longer exists.

  4. Return control to the CA ADS dialog by issuing one of the following DC RETURN statements:

Example of a Subroutine Called by CA ADS

The program excerpt below is a subroutine called by a CA ADS dialog to perform data conversion functions.

Depending on the conversion code, it converts a Julian date to Gregorian or a Gregorian date to Julian.

 WORKING-STORAGE SECTION.
 01  CONVERT-CODES.
     05 JULGREG                  PIC X    VALUE 'J'.
     05 GREGJUL                  PIC X    VALUE 'G'.
 01  GREGORIAN.
     10  MM                      PIC 99   VALUE ZEROS.
     10  DD                      PIC 99   VALUE ZEROS.
     10  YY                      PIC 99   VALUE ZEROS.
 01  JULIAN.
     10  JULIAN-YY               PIC 99   VALUE ZEROS.
     10  JULIAN-DDD              PIC 999  VALUE ZEROS.
 LINKAGE SECTION.
*** DEFINE RECORDS THAT ARE PASSED FROM CA ADS ***
 01  COPY IDMS SUBSCHEMA-CTRL.
 01  COPY IDMS RECORD DATE-RECORD.
 01  COPY IDMS RECORD DIALOG-REFERENCE-RECORD.
 PROCEDURE DIVISION USING SUBSCHEMA-CTRL
                          DATE-RECORD
                          DIALOG-REFERENCE-RECORD.
     IF CONV-DIRECTION = JULGREG
        PERFORM A100-JULGREG
     ELSE
        IF CONV-DIRECTION = GREGJUL
           PERFORM A100-GREGJUL
     ELSE
        PERFORM A100-ERROR.
*** RETURN CONTROL TO CA ADS PROGRAM ***
     DC RETURN.
*** DATE CONVERSION AND ERROR PROCESSING ***
       .
       .
       .