HP 3000 Manuals

ANSI85 Features in the PROCEDURE DIVISION [ HP COBOL II/XL Programmer's Guide ] MPE/iX 5.0 Documentation


HP COBOL II/XL Programmer's Guide

ANSI85 Features in the PROCEDURE DIVISION 

This section explains the following ANSI85 features of the PROCEDURE
DIVISION:

   *   ADD statement enhancement.
   *   ALPHABETIC-LOWER.
   *   ALPHABETIC-UPPER.
   *   CALL BY CONTENT.
   *   De-editing.
   *   INITIALIZE statement.
   *   INSPECT CONVERTING statement.
   *   Reference modification.
   *   Relational operators.
   *   REPLACE statement.
   *   Setting switches.
   *   Setting condition names.
   *   Table initialization.

The other ANSI85 features of the PROCEDURE DIVISION support structured
programming, and are explained in Chapter 3 .  These are:

   *   CONTINUE statement.
   *   EVALUATE statemnet.
   *   Explicit scope terminators.
   *   NOT phrases.
   *   PERFORM statement enhancements.
   *   USE GLOBAL AFTER ERROR PROCEDURE ON statement.

ADD Statement Enhancement 

An ADD statement in ANSI85 can have both a TO phrase and a GIVING phrase.
All literals and values of the identifiers to the left of the GIVING
keyword are added and the result is stored into each identifier named to
the right of the GIVING keyword.  See Format 2 of the ADD statement in
the HP COBOL II/XL Reference Manual.

Example.   

The following two statements are equivalent:

     ADD A TO B GIVING C
     ADD A B GIVING C

ALPHABETIC-LOWER and ALPHABETIC-UPPER Class Tests 

The class test ALPHABETIC-LOWER returns TRUE if every character of the
specified data item is a lowercase letter or a space.  The class test
ALPHABETIC-UPPER returns the value TRUE if every character of a specified
data item is an uppercase letter or a space.

Example.   

The following show two IF statements that use the ALPHABETIC-LOWER and
ALPHABETIC-UPPER class conditions:

     IF STRING1 IS ALPHABETIC-LOWER PERFORM UPSHIFT.
     IF STRING2 IS ALPHABETIC-UPPER THEN PERFORM CAPITAL.

CALL BY CONTENT 

When your program passes an actual parameter BY CONTENT, it copies the
actual parameter and passes the address of the copy to the subprogram.
If the subprogram changes the value of its formal parameter, it changes
the value of the copy, but it does not change the value of your program's
actual parameter.  For more information on parameter passing, see Chapter
4 .

CALL BY CONTENT has a performance penalty, because each parameter passed
BY CONTENT must be copied.

De-Editing 

De-editing converts an edited numeric field to its numeric value,
allowing you to move it to either a numeric field or a numeric edited
field.

Example.   

The following shows an example of a de-edited move:

     WORKING-STORAGE SECTION.
       01   PRINT-A       PIC $ZZZ,ZZZ.99CR.
       01   HOLD-A        PIC S9(6)V99.
     PROCEDURE DIVISION.
     PARA-001.
         MOVE -76543.21 TO PRINT-A.
         MOVE PRINT-A TO HOLD-A.         A de-edited MOVE statement. 

The first move statement above sends the following data to PRINT-A:

     -076543.21
[REV BEG]

The following value is stored in PRINT-A:[REV END]

     $ 76,543.21CR

The second move statement is the de-edited move.  It sends the following
data to HOLD-A:

     $ 76,543.21CR
[REV BEG]

The following value is stored in HOLD-A. (There is an implied decimal
point[REV END] between 2 and 3):
[REV BEG]

0765432J[REV END]

All edit symbols are removed and blanks are converted to zeros when the
edited value is moved.

INITIALIZE Statement 

The INITIALIZE statement sets the values of specified types of elementary
items in a record to specified values.

Example.   

The following example shows the INTIALIZE statement:

     WORKING-STORAGE SECTION.
     01  RECORD-1.
         05  EMP-NO    PIC 9(6).
         05  EMP-NAME  PIC X(20).
         05  EMP-PAY   PIC 9(5)V99.
         05  JOB-TITLE PIC X(20).
                     :
     PROCEDURE DIVISION.
     MAIN-100.
        INITIALIZE RECORD-1 REPLACING NUMERIC BY ZERO
                            REPLACING ALPHANUMERIC BY SPACES.

The above INITIALIZE statement has the same effect and efficiency as the
following MOVE statements:

        MOVE ZERO TO EMP-NO EMP-PAY.
        MOVE SPACES TO EMP-NAME JOB-TITLE.
[REV BEG]

Note that if the record to be initialized contains only elementary items
with fillers or items of the wrong category, the INITIALIZE statement has
no effect.  An error message is output.[REV END]

INSPECT CONVERTING Statement 

The INSPECT CONVERTING statement is similar to the INSPECT REPLACING
statement, but it is more efficient.  It allows you to specify several
replacements in one string, rather than requiring an entire line for each
replacement.

Example 1.   

The following two INSPECT statements are equivalent:

     INSPECT WORD CONVERTING "ABCD" TO "XYZX" AFTER QUOTE BEFORE "#".

     INSPECT WORD REPLACING
           ALL "A" BY "X" AFTER QUOTE BEFORE "#"
           ALL "B" BY "Y" AFTER QUOTE BEFORE "#"
           ALL "C" BY "Z" AFTER QUOTE BEFORE "#"
           ALL "D" BY "X" AFTER QUOTE BEFORE "#".

If in the above example the initial value of WORD is:

        AC"AEBDFBCD#AB"D

Then the final value of WORD is:

        AC"XEYXFYZX#AB"D

Converting uppercase letters to their lowercase forms is much easier with
the INSPECT CONVERTING statement than it would be with the INSPECT
REPLACING statement.

Example 2.   

The following two INSPECT statements are equivalent:

        INSPECT NAME CONVERTING
              "ABCDEFGHIJKLMNOPQRSTUVWXYZ" TO "abcdefghijklmnopqrstuvwxyz".

        INSPECT NAME REPLACING
              ALL "A" TO "a"
              ALL "B" TO "b"
                    :
              ALL "Z" TO "z".

Example 3.   

The following INSPECT CONVERTING statement translates blanks and
asterisks to zeros:

     INSPECT AMT-DUE CONVERTING " *" TO "00"

Reference Modification 
[REV BEG]

Reference modification allows you to reference part of an item whose
usage is DISPLAY.[REV END] To access a substring within a data item,
specify the position of the leftmost character and length of the
substring, in characters.[REV BEG] You can specify the position and
length with any integer expression.[REV END]

Example 1.   

If the value of the data item A is "ABCDEFGHI", then the following
statement moves the value "CDEFG" to the data item B:

     MOVE A (3:5) TO B

Example 2.   

The data item in a reference modification can also be the target of a
move.  If the value of the data item A is "ABCDEFGHI", then the following
statement gives A the value "AB*****HI".

     MOVE ALL '*' TO A(3:5)
[REV BEG]

Example 3.   

This example shows reference modification on the result of a COBOL
function call.  The example calls the COBOL function CURRENT-DATE and
displays only the characters in positions 1 through 4.  These characters
represent the current year.

     DISPLAY FUNCTION CURRENT-DATE (1:4).

The above DISPLAY statement displays the following:

     1991

See "Reference Modification" in the HP COBOL II/XL Reference Manual for
more examples.[REV END]

Relational Operators 

In ANSI85 you can use the relational operators LESS THAN OR EQUAL TO (<=)
and GREATER THAN OR EQUAL TO (>=).  An HP extension allows the symbol <>
as shorthand for NOT EQUAL.

Example.   

The following IF statements use these relational operators:

     IF TR-CODE <= 1 PERFORM 310-GET-NEXT-RECORD.
     IF STATE CODE >= 50 THEN PERFORM FOREIGN-RTN.
     IF CITY-CODE <> 25 PERFORM 420-VALIDATE-CITY.

REPLACE Statement 

The REPLACE statement affects source program text the way the COPY
REPLACING statement affects library text.  The scope of the REPLACE
statement is from its start to the start[REV BEG] of another REPLACE
statement or the end of the current concatenated program,[REV END]
whichever comes first.

The program in the following example replaces ANSI85 reserved words that
were not reserved in the 1974 ANSI standard.  Remember that the REPLACE
statement is executed each time the program is compiled.  It may be more
efficient to use an editor to change the file permanently than to consume
CPU time to change the file each time it is compiled.

Example.   

The following shows a COBOL program before REPLACE execution:

     IDENTIFICATION DIVISION.                    
     PROGRAM-ID.    PROG1.                       
     DATA DIVISION.
     REPLACE   ==TEST==  BY  ==TESTT==          Begin REPLACE statement 1. 

               ==TRUE==  BY  ==TRUE-FLAG==.     End REPLACE statement 1. 

        01  NAME   PIC   X(30).
        01  TEST   PIC   X.                     TEST will be replaced. 

             88   TRUE    VALUE  "T".           TRUE will be replaced. 

     PROCEDURE DIVISION.                         
     P1.
          ACCEPT TEST.                          TEST will be replaced. 

          IF TRUE   PERFORM P2.                 TRUE will be replaced. 

          REPLACE ==ALPHABETIC==                Begin REPLACE statement 2. 

             BY  ==ALPHABETIC-UPPER==.          End REPLACE statement 2. 

          IF NAME IS ALPHABETIC THEN         ALPHABETIC will be replaced. 

             SET TRUE-FLAG TO TRUE.
          REPLACE OFF.                       REPLACE statement 3. 
          PERFORM P3 WITH TEST AFTER
             UNTIL NAME IS NOT ALPHABETIC.
                    :

The actual code sent to the compiler becomes the following:

     IDENTIFICATION DIVISION.
     PROGRAM-ID.   PROG1.
     DATA DIVISION.
        01  NAME   PIC  X(30).
        01  TESTT  PIC  X.
            88  TRUE-FLAG  VALUE "T".
     PROCEDURE DIVISION.
     P1.
          ACCEPT TESTT.
          IF TRUE-FLAG PERFORM P2.
          IF NAME IS ALPHABETIC-UPPER THEN
             SET TRUE-FLAG TO TRUE.
          PERFORM P3 WITH TEST AFTER
             UNTIL NAME IS NOT ALPHABETIC.
                    :

Statement 2 overrides statement 1 and the second occurrence of "TEST"
remains unchanged.  Statement 3 ends all replacing and the second
occurrence of "ALPHABETIC" remains unchanged.

Setting Switches 

The SET statement in COBOL can set external switches to the values ON and
OFF. An ANSI74 program can test the values of switches, but it cannot
change their values.

Example.   

The following declares a switch:

     ENVIRONMENT DIVISION.
     SPECIAL-NAMES.
        SWO IS SWITCH-1

The following SET statement uses the switch:

     PROCEDURE DIVISION.
     PRINT-ROUTINE.
        SET SWITCH-1 TO ON.

Setting Condition Names 

The SET statement in COBOL can set condition names to the value TRUE.

Example.   

The following declares a condition name, EOF-FLAG:

        01  READ-FLAG      PIC 9.
            88  EOF-FLAG   VALUE 1.

The following SET statement uses the condition name EOF-FLAG:

        SET EOF-FLAG TO TRUE.

The SET statement above is equivalent to the following MOVE statement:

        MOVE 1 TO READ-FLAG.

Example.   

You cannot set a condition name to FALSE, but you can define two
condition names, one for the true case and one for the false case.  The
following example illustrates this:

     01   FIRST-TIME-FLAG   PIC X  VALUE "Y".
          88  FIRST-TIME     VALUE "Y".
          88  FIRST-TIME-OFF VALUE "N".

The following example uses the SET statement on both condition names:

     IF FIRST-TIME
        PERFORM INIT-SECTION
        SET FIRST-TIME-OFF TO TRUE
     END-IF

Table Initialization 

You can initialize a table (a data item that contains an OCCURS clause)
by specifying a VALUE clause for it.  Each table element (or
"occurrence") receives the value that you specify.

Example.   

In the following example, the ten elements of table B receive the value
zero:

     01 A.
        05 B PIC S999 OCCURS 10 TIMES VALUE 0.
[REV BEG]

For dynamic subprograms,[REV END] this initialization is as efficient as
the same initialization accomplished by a PERFORM loop for every VALUE
clause.



MPE/iX 5.0 Documentation