-----------------------------------------------------------------------
PERFORM Statement  -- is used to execute a module repeatedly from multiple locations in the program.

The PERFORM paragraph-name statement jumps "out-of-line" by transferring control to the first executable statement in the paragraph referenced.

When the last statement of the PERFORMed procedure is complete, or an EXIT statement is executed, control jumps back to the statement immediately following the calling PERFORM.
-----------------------------------------------------------------------
The EXIT statement.   When reached, the EXIT becomes the end point in a paragraph and the remaining statements in the paragraph are bypassed.

A-A-CALCULATIONS.
    IF REGION-A-CALLS-IN = ZERO
       EXIT.
    COMPUTE REGION-A-CHARGE-OUT WS-AREA-A-CHARGE
          =  REGION-A-CALLS-IN   * .05
          +  REGION-A-MINUTES-IN * .03.
-------------------------------------------------------
Format for a simple PERFORM.

PERFORM paragraph-name.
 

 
PERFORM PARA-A.
- - - - - - - - - - - - - - - - - - - - - - - - - - - -
PERFORM paragraph-name  THRU paragraph-name-2
 

PERFORM PARA-A THRU PARA-C
- - - - - - -- - - - - - - - - - - - - - - - - - - - -
PERFORM paragraph-name  THRU paragraph-name-2 [ {identifier } TIMES ]
                                              [{numeric  }]

    PERFORM PARA-A 5 TIMES
    or
    MOVE 5 TO LOOP-CONTROL  (define LOOP-CONTROL in working-storage)
    PERFORM PARA-A LOOP-CONTROL TIMES
--------------------------------------------------------------------
PERFORM paragraph-name UNTIL some-condition-is-met

This format is a method of performing the paragraph-name a variable number of times until some condition is true.
 

        UNTIL SWITCH = 'YES'
        UNTIL REC-COUNT > 20
        UNTIL END-OF-FILE OR TOTAL-INPUT > 100
 

         MOVE 'NO' TO SWITCH.
         PERFORM PARA-A UNTIL SWITCH = 'YES'
 

        MOVE ZERO TO REC-COUNT
        PERFORM PARA-A UNTIL REC-COUNT > 9
 

        MOVE 10 TO REC-COUNT
        PERFORM PARA-A UNTIL REC-COUNT > 9
 

        MOVE 10 TO REC-COUNT
        PERFORM PARA-A  WITH TEST AFTER
        UNTIL REC-COUNT > 9
 

    If the condition is a count, then there should be a count increment.

        UNTIL REC-COUNT > 10  should have an ADD 1 TO REC-COUNT

    If the condition is a switch, then the switch should be set in the loop.

        UNTIL SWITCH = 'YES'   should have a   MOVE 'YES' TO SWITCH
-----------------------------------------------------------------------
        PERFORM paragraph-name
            VARYING  a-variable-value FROM start-value BY increment-value
            UNTIL some-condition-is-met

    The advantage of this statement is that it offers a good
    "locality of reference." The variable and its increment are
    close together.  The other PERFORM statements might have the
    initializing statement, the increment statement and the PERFORM
    far from each other and therefore difficult to trace..

    With variables of

         01 TEST-1  PIC S999.
         01 FILE-SWITCH PIC XXX VALUE SPACES.
 

        PERFORM PARA-A
            VARYING  TEST-1 FROM 1 BY 1
            UNTIL TEST-1 > 10
 

        PERFORM PARA-A
            VARYING  TEST-1 FROM 100 BY -1
            UNTIL TEST-1 = ZEROS.
 

        PERFORM PARA-A
            VARYING  TEST-1 FROM 1 BY 1
            UNTIL TEST-1 > 1000
             OR  FILE-SWITCH = 'EOF'

    In addition to the counter countrolled by the VARYING, this code depends on a statement somewhere in PARA-A that moves 'EOF' to FILE-switch.

-----------------------------------------------------------------------------
With nested PERFORMS, every single execution of the outer PERFORM causes a complete looping of the inner PERFORM.

     01 INNER-1  PIC 9.
     01 OUTER-1  PIC 9.

     PERFORM    WITH TEST AFTER
         VARYING OUTER-1 FROM 0 BY 1
         UNTIL OUTER-1 = 9
 
         PERFORM  WITH TEST AFTER
             VARYING INNER-1 FROM 0 BY 1
             UNTIL INNER-1 = 9

             DISPLAY OUTER-1 INNER-1

         END-PERFORM

     END-PERFORM

    The above displays what starting value ____
    through what ending value____?
------------------------------------------------------------------
The above example utilizes "in-line" PERFORMS which do not require a named paragraph to refer to.

The range of statements for "in-line" PERFORMS

Every PERFORM format discussed for the "out-of-line" PERFORM
is also applicable to the "in-line" PERFORM.
----------------------------------------------------------------
    The CLASS tests are

        NUMERIC              ALPHABETIC
        ALPHABETIC-LOWER     ALPHABETIC-UPPER
        ALPHANUMERIC         ALPHANUMERIC-EDITED
----------------------------------------------------------------
    The SIGN tests are

        POSITIVE  NEGATIVE  ZERO
---------------------------------------------------------------
Reference modification --

    can be used to manipulate part of a field.

    FORMAT
 
     field-name (location-of-starting-position : length)
 
 

    01 GROUP-OF-FIELDS.
        05 NUMERIC-1 PIC 9(10) VALUE ZEROS.
        05 FIELD-A PIC X(11) VALUE 'START VALUE'
        05 FIELD-B PIC X(11) VALUE 'START VALUE'
 

        MOVE '-' TO FIELD-A (6:1)
 

        MOVE FIELD-B (7:5) TO FIELD-A (1:5)
        MOVE FIELD-B (1:5) TO FIELD-B (7:5)
        MOVE '-' TO FIELD-A (6:1)
 

        MOVE ALL '*' TO FIELD-A
        MOVE 'TRY IT' TO FIELD-A (3:6)
 

        MOVE 1 TO NUMERIC-VALUE1(9:1)
        MOVE 5 TO NUMERIC-VALUE1 (2:1)
 

    INSPECT GROUP-OF-FIELDS REPLACING ALL "0" BY SPACES.

    INSPECT can count parts of field that match a comparison string.

--------------------------------------------------------------------
INSPECT field TALLYING add-to-field  FOR CHARACTERS
                                         ALL 'comparison'
                                         LEADING 'comparison'

                 Or a figurative constant treated as a 1 character match.             Starts at the left of a string and stops when the stop-string
            or end of field is encountered.
              Starts to the right of the start-string and stops at the end of
            the field.

---------------------------------------------------------------------------

        01 COUNT-1 PIC 99  VALUE ZEROS.
        01 FIELD-1 PIC X(11) VALUE 'ACHIEVEMENT'.
        01 COUNT-2 PIC 99  VALUE ZEROS.
 

        MOVE ZEROS TO COUNT-1
        INSPECT FIELD-1 TALLYING COUNT-1 FOR ALL 'E'.
 

        INSPECT FIELD-1 TALLYING COUNT-1 FOR LEADING 'ACH'.
 

        MOVE ZEROS TO FIELD-1
        INSPECT FIELD-1 TALLYING COUNT-1 FOR ALL 'M' ALL 'T'
 

        INSPECT FIELD-1 TALLYING COUNT-1 FOR ALL 'C'
                                 COUNT-2 FOR ALL 'T'
 

        INSPECT FIELD-1 TALLYING COUNT-1 FOR ALL 'C'
                AFTER INITIAL 'I'

---------------------------------------------------------------

        01 FIELD-1 PIC X(11) VALUE 'ACHIUVUMUNT'.
        01 FIELD-2 PIC X(11) VALUE 'PPPORTUNITY'.
        01 FIELD-3 PIC X(11) VALUE 'PERSISTLNCE'.
 

         INSPECT FIELD-1 REPLACING ALL 'U' BY 'E'
         INSPECT FIELD-2 REPLACING FIRST 'P' BY 'O'
         INSPECT FIELD-3 REPLACING 'L' BY 'E' AFTER INITIAL 'T'
------------------------------------------------------------------

        INSPECT field  REPLACING CHARACTERS
                                 ALL 'comparison'
                                 LEADING 'comparison'
                                 FIRST 'comparison'
                       BY new-string

This INSPECT replaces parts of field that match the comparison.  The comparison and new string should have the same number of characters.
 

        Starts at the left of a string and stops when the stop-string or
        end of field is encountered.
          Starts to the right of the start-string and stops at the end of
        the field.
-----------------------------------------------------------------------------------------------------------

REDEFINES CLAUSE -- a STORAGE space can have multiple definitions.

        01 GROUP-1.
            05 NUMBER-1                  PIC 9(5).
            05 AN-1 REDEFINES NUMBER-1   PIC X(5).
            05 SUB-GROUP-1 REDEFINES NUMBER-1.
                10 SUB-1-NUMBER          PIC 99.
                10 SUB-1-CODE            PIC XXX.
        01 ERROR-FIELD                   PIC X(5).
        01 ANSWER-FIELD                  PIC 9(5)V99.

The multiple definitions of a single storage space are useful because the data in that storage can be manipulated according to its data type.

The picture of NUMBER-1 leads the system to expect a 5 digit number.

If the actual contents of NUMBER-1 is not NUMERIC, then any calculation using NUMBER-1 or any move of NUMBER-1 to a number would crash the program.

The programmer has options to treat the storage location as an alpha field or as a alphanumeric field or as a group item segmented into a number and a alphanumeric code.

 IF  NUMBER-1 NOT NUMERIC
     MOVE AN-1 TO ERROR-FIELD.
 ELSE
     COMPUTE ANSWER-FIELD = NUMBER-1 * 1.6

-----------------------------------------------------------------------------------------------------------