Expanded COBOL

This appendix describes how to convert expanded COBOL.

1. Expanded COBOL Elements

Expanded COBOL is internally converted to COBOL and then processed only when the --expanded option is used.

The following are elements used in expanded COBOL and how they are converted to COBOL.

  • EVALUATE statement

    The following is sample expanded COBOL source code for Evaluate.

    EVALUATE WK
       WHEN 28
       WHEN OTHER
         DISPLAY 'WNE OTHER'
    END-EVALUATE.

    The following is the converted source code.

    EVALUATE WK
       WHEN 28
         DISPLAY 'WHEN OTHER'
       WHEN OTHER
         DISPLAY 'WHEN OTHER'
    END-EVALUATE.
  • VALUE CLAUSE truncation

    If there is a value that exceeds PICTURE SIZE in VALUE CLAUSE, it is truncated.

    The following is sample expanded COBOL source code for the truncation.

    01 WK PIC X(10) VALUE '1234567890*'.

    The following is the converted source code.

    01 WK PIC X(10) VALUE '1234567890'.
  • INSPECT statement TRAILING phrase

    The number of times that a specified character is used can be counted from the right by using the TRAILING phrase in an INSPECT statement.

    The following is sample expanded COBOL source code for the TRAILING phrase in an INSPECT statement.

    WORKING-STORAGE SECTION.
    01 TARGET-FIELD PIC X(10) VALUE '123   '.
    01 WS-TALLY-LEN PIC 9999.
    
    PROCEDURE DIVISION.
        INSPECT TARGET-FIELD TALLYING
            WS-TALLY-LEN FOR TRAILING SPACE.
        DISPLAY WS-TALLY-LEN.

    The following is the result.

    3
  • SEARCH statement

    In a SEARCH statement, a WHEN clause can be used right after AT END.

    SEARCH WS-ARH-TBL
    AT END
    WHEN WK = ZEROES
    DISPLAY 'WK :' WK
    END-SEARCH.
  • COMMIT statement

    A COMMIT statement that calls the text_commit function can be used.

    COMMIT.
  • DIVIDE ZERO exception

    If a divisor is 0 when performing a divide operation, 0 is set in the quotient, not the runtime assertion.

           WORKING-STORAGE SECTION.
           01 RESULT1 PIC 9999.
           01 RESULT2 PIC 9999.
           01 DIVISOR PIC 9999 VALUE 0.
           PROCEDURE      DIVISION.
    
           DIVIDE DIVISOR INTO RESULT1.
           DISPLAY "RESULT1 : " RESULT1.
    
           COMPUTE RESULT2 = 10 / 0.
           DISPLAY "RESULT2 : " RESULT2.

    The following is the result.

    RESULT1 : 0
    RESULT2 : 0
  • Zoned Decimal sign zone portion

    When moving a string value to a zoned decimal, the string value is not replaced with a 4-bit unsigned value and moved as it is.

    The following is sample expanded COBOL source code for Zoned Decimal Sign zone portion.

           WORKING-STORAGE SECTION.
           01 ZONED PIC S9(4).
           01 STR   PIC X(4) VALUE 'AAAA'.
           PROCEDURE DIVISION.
               MOVE STR TO ZONED.
               CALL 'ofcob_hexdump' USING ZONED VALUE LENGTH OF ZONED.

    The following is the result.

    >>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>
    HEXA VALUE : 41414141
    >>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>
  • LINKAGE SECTION variable life cycle

    A variable in LINKAGE SECTION can be used as a local variable.

    The following is sample expanded COBOL source code for LINKAGE SECTION variable life cycle.

           IDENTIFICATION DIVISION.
           PROGRAM-ID.    TESTCOB.
           DATA           DIVISION.
           WORKING-STORAGE SECTION.
           PROCEDURE       DIVISION.
               CALL 'SUBCOB'.
    IDENTIFICATION DIVISION.
           PROGRAM-ID.    SUBCOB.
           DATA           DIVISION.
           WORKING-STORAGE SECTION.
           01 F PIC 9(1) COMP.
           01 WK-VAR PIC X(8).
           LINKAGE          SECTION.
           01 LK-VAR PIC X(8).
           PROCEDURE       DIVISION.
    
               DISPLAY "ADDRESS OF LK-VAR : " ADDRESS OF LK-VAR.
    
               ADD 1 TO F.
               IF F = 1 THEN
                 SET ADDRESS OF LK-VAR TO ADDRESS OF WK-VAR
                 CALL 'SUBCOB'.

    The following is the result.

    ADDRESS OF LK-VAR : 0000000000
    ADDRESS OF LK-VAR : 0000000000
  • Expansion of target types for reference modification

    A reference modifier can be used regardless of specified USAGE.

    The following is sample expanded COBOL source code for expansion of target types for reference modification.

           IDENTIFICATION      DIVISION.
           PROGRAM-ID.         TESTCOB.
           ENVIRONMENT            DIVISION.
           CONFIGURATION          SECTION.
           DATA                   DIVISION.
           WORKING-STORAGE        SECTION.
           01 Z PIC 9(8).
           01 S PIC X(8) VALUE 'ZZZZZZZZ'.
           01 C PIC 9(15) COMP-3.
           01 B PIC 9(16) COMP.
           PROCEDURE       DIVISION.
               MOVE S(1:4) TO Z(1:4).
               CALL 'ofcob_hexdump' USING Z VALUE LENGTH OF Z.
               MOVE S(1:4) TO C(1:4).
               CALL 'ofcob_hexdump' USING C VALUE LENGTH OF C.
               MOVE S(1:4) TO B(1:4).
               CALL 'ofcob_hexdump' USING B VALUE LENGTH OF B.

    The following is the result.

    >>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>
    HEXA VALUE : 5a5a5a5a00000000
    >>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>
    >>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>
    HEXA VALUE : 5a5a5a5a00000000
    >>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>
    >>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>
    HEXA VALUE : 5a5a5a5a00000000
    >>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>