Your Browser is not longer supported

Please use Google Chrome, Mozilla Firefox or Microsoft Edge to view the page correctly
Loading...

{{viewport.spaceProperty.prod}}

Example with a COBOL main program

t

&pagelevel(3)&pagelevel

PERCON is to be called as a subprogram by a COBOL main program. The PERCON statements are supplied by the program.

Source listing

       IDENTIFICATION DIVISION.
        PROGRAM-ID. PERCONCO.
        ENVIRONMENT DIVISION.
        CONFIGURATION SECTION.
        SPECIAL-NAMES.
            TERMINAL IS SYSOUT.
        DATA DIVISION.
        WORKING-STORAGE SECTION.
        01 PARAM.                                                        (1)
          02 STMT-INDICATOR             PIC S9(5) COMP SYNC VALUE 132.   (2)
          02 STATEMENT-1 SYNC.
            03 STMT-LENGTH              PIC S99 COMP VALUE 45.           (3)
            03 FILLER                   PIC S99 COMP VALUE 0.
            03 STMT                     PIC X(41) VALUE                  (4)
                 "MODIFY-PERCON-OPTIONS SYSOUT-LOGGING=*ALL".
          02 STATEMENT-2 SYNC.
            03 STMT-LENGTH              PIC S99 COMP VALUE 38.
            03 FILLER                   PIC S99 COMP VALUE 0.
            03 STMT                     PIC X(34) VALUE
                 "ASSIGN-INPUT-FILE  LINK-NAME=PCIN".
          02 STATEMENT-3 SYNC.
            03 STMT-LENGTH              PIC S99 COMP VALUE 38.
            03 FILLER                   PIC S99 COMP VALUE 0.
            03 STMT                     PIC X(34) VALUE
                 "ASSIGN-OUTPUT-FILE LINK-NAME=PCOUT".
          02 STATEMENT-4 SYNC.
            03 STMT-LENGTH              PIC S99 COMP VALUE 7.
            03 FILLER                   PIC S99 COMP VALUE 0.
            03 STMT                     PIC X(3) VALUE
                 "END".

(1)

Symbolic address of the parameter area.

(2)

Byte 4 contains the identifier indicating the way in which the statements are transferred. X’84’: the PERCON statements are transferred by the main program in the form of variable-length records.

(3)

The record length field of the statement is defined by means of STMT-LENGTH and FILLER.

(4)

The field for the record contents of the statement is defined by means of STMT.

        01 RETCODE.                                                      (5)
          02 DMS-CODE                   PIC S9(5) COMP SYNC.             (6)
          02 MESSAGE-ID.                                                 (7)
             03 BYTE-1-2                PIC 9(4) COMP.
             03 BYTEAN-1-2              REDEFINES BYTE-1-2.
                04 BYTEAN-1             PIC X.
                04 FILLER               PIC X.
             03 BYTES-REST              PIC X(10).
        01 RESERVED.
          02 FILLER                     PIC S9(5) COMP.
          02 FILLER                     PIC S9(5) COMP.
        77 BIT-2                        PIC 9.
       PROCEDURE DIVISION.
        AUFRUF-PERCON SECTION.
        AR-1.
            CALL "PERCONU" USING PARAM RETCODE RESERVED.                 (8)
            SUBTRACT 32768 FROM BYTE-1-2.
            IF BYTEAN-1 NOT < SPACE
            MOVE 1 TO BIT-2
            ELSE MOVE ZERO TO BIT-2.
            IF BIT-2 = 0
               DISPLAY "PERCON RUN SUCCESSFUL" UPON SYSOUT
            ELSE
               DISPLAY "PERCON RUN ERRONEOUS" UPON SYSOUT.
        STOP RUN.

(5)

Symbolic address of the area for return information.

(6)

PERCON supplies the DMS-CODE field with the last DMS message.

(7)

This area is reserved for the PERCON messages.

(8)

PERCON is called. PERCONU is the entry point. The following data is transferred:

  • the data group PARAM, consisting of a field containing the statement indicator, followed by the PERCON statements;

  • the data group RETCODE, consisting of 4 fields which can accommodate the return code;

  • the data group RESERVED, consisting of 2 fields for subsequent extensions.

Compiling, linking and calling the program (tracer listing)

/DELETE-SYSTEM-FILE FILE-NAME=*OMF
/START-COBOL2000-COMPILER SOURCE=PERCONCO.SRC - &*————————————————————  (9)
/  ,MONJV=#MONJV
%  BLS0500 PROGRAM 'COBOL2000', VERSION '01.6A11' OF '2020-04-02' LOADED
%  CBL9000 COPYRIGHT (C) 2020 Fujitsu Technology Solutions GmbH.
                         ALL RIGHTS RESERVED
%  CBL9017 COMPILATION INITIATED, VERSION IS  V01.6A11
%  CBL9095 SAVLST FILE :2OS6:$WKST.OPTLST.COBOL.PERCONCO CREATED AND CLOSED
%  CBL9095 SAVLST FILE :2OS6:$WKST.SRCLST.COBOL.PERCONCO CREATED AND CLOSED
%  CBL9095 SAVLST FILE :2OS6:$WKST.ERRFIL.COBOL.PERCONCO CREATED AND CLOSED
%  CBL9097 COMPILATION COMPLETED WITHOUT ERRORS
%  CBL9004 COMPILATION OF PERCONCO USED  0.0631 CPU SECONDS
/START-BINDER &* —————————————————————————————————————————————————————— (10)
//START-LLM-CREATION INTERNAL-NAME=COBPROG1 &* ———————————————————————— (11)
//INCLUDE-MODULES LIBRARY=*OMF,ELEMENT=*ALL
//RESOLVE-BY-AUTOLINK LIBRARY=$.SYSLNK.PERCON.030 &* —————————————————— (12)
//RESOLVE-BY-AUTOLINK LIBRARY=$.SYSLNK.CRTE
//SAVE-LLM LIBRARY=COB.PROG.LIB
%  BND3101 SOME EXTERNAL REFERENCES UNRESOLVED
%  BND3102 SOME WEAK EXTERNS UNRESOLVED
%  BND1501 LLM FORMAT: '1'
//END
% BND1101 BINDER NORMALLY TERMINATED. SEVERITY CLASS: 'UNRESOLVED EXTERNAL'

(9)

The COBOL compiler is called. The SOURCE parameter assigns the file PERCONCO.SRC as the input file.

(10)

The BINDER is called.

(11)

The name of the program is defined.

(12)

The object module library SYSLNK.PERCON.030 and the runtime system SYSLNK.CRTE are assigned.

/ADD-FILE-LINK - &*—————————————————————————————————————————————————————— (13)
/   FILE-NAME=PERS.TAB,-
/   LINK-NAME=PCIN
/CREATE-FILE FILE-NAME=PERS.SEL
/ADD-FILE-LINK - &*—————————————————————————————————————————————————————— (14)
/   FILE-NAME=PERS.SEL,-
/   ACCESS-METHOD=*SAM,-
/   LINK-NAME=PCOUT
/START-EXECUTABLE-PROGRAM - &*——————————————————————————————————————————— (15)
/  FROM-FILE=*LIBRARY-ELEMENT(LIBRARY=COB.PROG.LIB,ELEMENT-OR-SYMBOL=COBPROG1)
%ASSIGN-INPUT-FILE  LINK-NAME=PCIN —————————————————————————————————————— (16)
%ASSIGN-OUTPUT-FILE LINK-NAME=PCOUT        
%END
%  PER0030 NUMBER OF PROCESSED RECORDS FOR LINK='PCIN' 
           (FILE=:2OS6:$WKST.PERS.TAB):                  12   ——————————— (17)
%  PER0030 NUMBER OF PROCESSED RECORDS FOR LINK='PCOUT'
           (FILE=:2OS6:$WKST.PERS.SEL):                  12
%  PER0031 PERCON TERMINATED NORMALLY
PERCON RUN SUCCESSFUL ——————————————————————————————————————————————————— (18)
(13)The input file PERS.TAB is assigned with the link name PCIN.

(13)

The output file PERS.SEL is assigned with the link name PCOUT and its file attributes.

(14)

The program which has just been linked is loaded and started.

(15)

The following statements are provided by the COBOL program and logged here.

(16)

Messages from PERCON as a subprogram.

(17)

Output from the main program.