HP 3000 Manuals

ENTRY Statement [ HP COBOL II/XL Reference Manual ] MPE/iX 5.0 Documentation


HP COBOL II/XL Reference Manual

ENTRY Statement 

The ENTRY statement is an HP extension to the ANSI COBOL standard.

The ENTRY statement establishes a secondary entry point in an HP COBOL II
subprogram.  In nested programs, this statement must begin in Area A.[REV
BEG] However, like all other COBOL statements in the PROCEDURE DIVISION,
the ENTRY statement must be in a paragraph.[REV END]

Syntax 
[REV BEG]

     ENTRY literal-1 [USING {data-name-1}...][REV END]

Parameters 

literal-1           nonnumeric literal.  It must be formed according to
                    the rules for program names, but must not be the name
                    of the called program in which it appears.
                    Furthermore, it must not be the name of any other
                    entry point or program name in the run unit.[REV BEG]

data-name-1         as described and used in the USING phrase of the
                    PROCEDURE[REV END] DIVISION header.  Refer to Chapter
                    8  for details.

Description 

The link between the calling program and a secondary entry point of a
called program is supplied by literal-1.  That is, literal-1 must be used
in a CALL statement of the calling program and must appear in an ENTRY
statement in the called program.

When the called program is invoked using such CALL and ENTRY statements,
the called program is entered at the ENTRY statement that specifies
literal-1.

When using secondary entry points the PROCEDURE DIVISION statements for
each such entry point may only reference passed parameters that are
declared in the USING clause for the respective entry point.  Attempts to
reference passed parameters declared in other entry point USING clauses
will produce a run-time bounds violation.

The USING option has the same format and meaning as in the USING phrase
of the PROCEDURE DIVISION header.  Refer to Chapter 8  for details.

The entry name must be unique with respect to all program units (HP COBOL
II main program or subroutines) compiled in a particular instance[REV
BEG] unless contained in different programs.[REV END] Refer to "System
Dependencies" in Appendix H  for information on the resulting external
name.

Example 

The following example shows a main program and a subprogram.  The
subprogram has a secondary entry point named by the ENTRY statement.

The CALL statement in MAINPROG specifies that SUBPRO1 is to be executed,
starting at the ENTRY statement rather than at the first line following
the PROCEDURE DIVISION header.  Also, the data areas of INV-FILE and
SALES-FILE are to be used in both programs.

Following is the main program:

     IDENTIFICATION DIVISION.
     PROGRAM ID.  MAINPROG.
           :
     DATA DIVISION.
     FILE SECTION.
     FD INV-FILE.
     01 INV-REC.
        02 PT-NUM          PIC X(10).
        02 PT-NAME         PIC X(30).
        02 BEGIN-QTY       PIC 9(6).
        02 PRICE-WHSL      PIC 9(3)V99.
        02 PRICE-RETAIL    PIC 9(4)V99.
     FD SALES-FILE.
     01 SALES-REC.
        02 SOLD-PT-NO      PIC X(10).
        02 SOLD-PART       PIC X(30).
        02 SOLD-QTY        PIC 9(6).
             :
     PROCEDURE DIVISION.
     MAIN-PARA-001.
               :
          IF SOLD-QTY IS NOT EQUAL TO ZERO
             CALL "SUBPRO1-ENTRY" USING INV-REC, SALES-REC.
               :
          STOP RUN.

Following is the subprogram:

     IDENTIFICATION DIVISION.
     PROGRAM-ID.   SUBPRO1.
           :
     DATA DIVISION.
     FILE SECTION.
     FD PRINT-FILE.
     01 P-REC              PIC X(132).
           :
     WORKING-STORAGE SECTION.
     01 HEADER.
         :
     01 WRITE-SALES.
        02 FILLER        PIC X(15)     VALUE SPACES.
        02 NAME          PIC X(30)     VALUE SPACES.
        02 FILLER        PIC X(5)      VALUE SPACES.
        02 NUM-1         PIC X(10)     VALUE SPACES.
        02 FILLER        PIC X(5)      VALUE SPACES.
        02 QUANTITY      PIC Z(3)9(3)  VALUE ZERO.
        02 FILLER        PIC X(5)      VALUE SPACES.
        02 GROSS-SALES   PIC $Z(10).99 VALUE ZEROS.
        02 FILLER        PIC X(5)      VALUE SPACES.
        02 GROSS-PROFIT  PIC $9(10).99.
             :
     LINKAGE SECTION.
     01 ORIGINAL.
        02 PT-NUM        PIC X(10).
        02 PT-NAME       PIC X(30).
        02 START-QTY     PIC 9(6).
        02 OUR-PRICE     PIC 9(3)V99.
        02 THEIR-PRICE   PIC 9(4)V99.
     01 SALES.
        02 SOLD-NUM      PIC X(10).
        02 SOLD-NAME     PIC X(30).
        02 QTY-SOLD      PIC 9(6).
     PROCEDURE DIVISION.
     SUB-PARA-001.
           :
     CALC-PARA-100.
     ENTRY "SUBPRO1-ENTRY" USING ORIGINAL, SALES.
          MULTIPLY QTY-SOLD BY THEIR-PRICE GIVING GROSS-SALES.
          SUBTRACT START-QTY FROM QTY-SOLD GIVING QUANTITY.
          COMPUTE GROSS-PROFIT =
             (THEIR-PRICE - OUR-PRICE) * QTY-SOLD.
          MOVE PT-NUM TO NUM-1.
          MOVE PT-NAME TO NAME.
          WRITE P-REC FROM HEADER AFTER ADVANCING 1 LINES.
          WRITE P-REC FROM WRITE-SALES AFTER ADVANCING 3 LINES.
          GOBACK.
            :



MPE/iX 5.0 Documentation