The PERFORM statement is one of the most essential and versatile statements in COBOL. It enables you to execute paragraphs or sections and provides structures for iteration, making it the primary means of implementing subroutines and loops in COBOL programs.
1234567891011* Format 1: Basic PERFORM PERFORM paragraph-name. * Format 2: PERFORM with THRU option PERFORM paragraph-1 THRU paragraph-2. * Format 3: In-line PERFORM PERFORM statement-1 statement-2 END-PERFORM.
These are the fundamental formats of the PERFORM statement without iteration options.
12345678910111213141516171819202122232425262728293031323334353637383940414243444546474849IDENTIFICATION DIVISION. PROGRAM-ID. PERFBASIC. DATA DIVISION. WORKING-STORAGE SECTION. 01 TOTAL-VALUE PIC 9(5) VALUE ZERO. 01 INPUT-VALUE PIC 9(5) VALUE 100. PROCEDURE DIVISION. MAIN-LOGIC. DISPLAY "Starting program execution" PERFORM CALCULATE-ROUTINE DISPLAY "After first PERFORM, TOTAL-VALUE = " TOTAL-VALUE MOVE 200 TO INPUT-VALUE PERFORM CALCULATE-ROUTINE DISPLAY "After second PERFORM, TOTAL-VALUE = " TOTAL-VALUE PERFORM DISPLAY-ROUTINE THRU END-DISPLAY-ROUTINE PERFORM IN-LINE-DEMO STOP RUN. CALCULATE-ROUTINE. ADD INPUT-VALUE TO TOTAL-VALUE. DISPLAY "Added " INPUT-VALUE " to TOTAL-VALUE". DISPLAY-ROUTINE. DISPLAY "This is the start of DISPLAY-ROUTINE". DISPLAY "TOTAL-VALUE is now: " TOTAL-VALUE. MIDDLE-ROUTINE. DISPLAY "This is MIDDLE-ROUTINE which is included". DISPLAY "because it falls between DISPLAY-ROUTINE". DISPLAY "and END-DISPLAY-ROUTINE in the code". END-DISPLAY-ROUTINE. DISPLAY "This is the end of the display routine block". IN-LINE-DEMO. DISPLAY "Using in-line PERFORM:" PERFORM DISPLAY "This code is part of an in-line PERFORM" DISPLAY "It executes directly where it appears" DISPLAY "Rather than jumping to a paragraph" END-PERFORM. DISPLAY "After in-line PERFORM completion".
This example demonstrates the basic PERFORM statement in its various forms.
The basic PERFORM statement has several key characteristics:
Note: When using PERFORM with the THRU option, all paragraphs physically located between the first and last named paragraphs will be executed, even if not explicitly named in the PERFORM statement. This sequential execution is based on the source code order, not the logical relationship between paragraphs.
The PERFORM TIMES format allows you to execute a paragraph or section a fixed, predetermined number of times. This is useful when you know exactly how many iterations you need, such as printing headers or processing a fixed set of items.
123456789101112131415161718* Format 1: Out-of-line PERFORM TIMES PERFORM paragraph-name identifier TIMES. PERFORM paragraph-name numeric-literal TIMES. * Format 2: Out-of-line PERFORM TIMES with THRU PERFORM paragraph-1 THRU paragraph-2 identifier TIMES. PERFORM paragraph-1 THRU paragraph-2 numeric-literal TIMES. * Format 3: In-line PERFORM TIMES PERFORM identifier TIMES statement-1 statement-2 END-PERFORM. PERFORM numeric-literal TIMES statement-1 statement-2 END-PERFORM.
These formats show how to use the TIMES option with different PERFORM variations.
123456789101112131415* Example 1: Fixed number of iterations PERFORM PRINT-HEADER 3 TIMES. * Example 2: Variable number of iterations MOVE 5 TO ITERATION-COUNT. PERFORM PROCESS-DATA ITERATION-COUNT TIMES. * Example 3: In-line PERFORM with fixed iterations PERFORM 10 TIMES ADD 1 TO COUNTER DISPLAY "Counter value: " COUNTER END-PERFORM. * Example 4: PERFORM TIMES with THRU option PERFORM INIT-ROUTINE THRU END-INIT-ROUTINE 2 TIMES.
These examples show different ways to use the PERFORM TIMES statement.
12345678910111213141516171819202122232425262728293031323334353637383940414243444546474849505152IDENTIFICATION DIVISION. PROGRAM-ID. PERFTIMES. DATA DIVISION. WORKING-STORAGE SECTION. 01 ITERATION-COUNT PIC 9(2) VALUE 5. 01 COUNTER PIC 9(3) VALUE 0. 01 SUB-TOTAL PIC 9(5) VALUE 0. 01 LINE-COUNT PIC 9(2) VALUE 0. PROCEDURE DIVISION. MAIN-LOGIC. DISPLAY "PERFORM TIMES Demonstration" DISPLAY "--------------------------" * Fixed number of times DISPLAY "Fixed PERFORM TIMES (3):" PERFORM PRINT-DASH-LINE 3 TIMES * Variable number of times DISPLAY "Variable PERFORM TIMES (" ITERATION-COUNT "):" PERFORM INCREMENT-COUNTER ITERATION-COUNT TIMES DISPLAY "Counter after " ITERATION-COUNT " iterations: " COUNTER * In-line PERFORM TIMES DISPLAY "In-line PERFORM TIMES (4):" PERFORM 4 TIMES ADD 25 TO SUB-TOTAL DISPLAY "Added 25, subtotal now: " SUB-TOTAL END-PERFORM * PERFORM TIMES with THRU DISPLAY "PERFORM TIMES with THRU (2):" PERFORM HEADER-ROUTINE THRU FOOTER-ROUTINE 2 TIMES STOP RUN. PRINT-DASH-LINE. DISPLAY "------------------------------------". INCREMENT-COUNTER. ADD 1 TO COUNTER. HEADER-ROUTINE. ADD 1 TO LINE-COUNT. DISPLAY "Report line " LINE-COUNT " header". DETAIL-ROUTINE. DISPLAY " Detail information for line " LINE-COUNT. FOOTER-ROUTINE. DISPLAY "Report line " LINE-COUNT " footer".
This program demonstrates various uses of the PERFORM TIMES statement.
Key points about PERFORM TIMES:
Important: When using a variable for the iteration count, ensure it contains a valid numeric value before the PERFORM. If the field contains non-numeric data, you'll get a runtime error. Consider validating the data or using a default value to prevent issues.
The PERFORM UNTIL format executes a paragraph, section, or block of code repeatedly until a specified condition becomes true. This is particularly useful when processing data of unknown quantity, such as reading records from a file until reaching the end.
1234567891011121314151617181920* Format 1: Out-of-line PERFORM UNTIL PERFORM paragraph-name UNTIL condition. * Format 2: Out-of-line PERFORM UNTIL with THRU PERFORM paragraph-1 THRU paragraph-2 UNTIL condition. * Format 3: In-line PERFORM UNTIL PERFORM UNTIL condition statement-1 statement-2 END-PERFORM. * Format 4: PERFORM TEST BEFORE/AFTER PERFORM paragraph-name WITH TEST BEFORE UNTIL condition. PERFORM paragraph-name WITH TEST AFTER UNTIL condition.
These formats show how to use the UNTIL option with different PERFORM variations.
1234567891011121314151617* Example 1: Basic PERFORM UNTIL with simple condition PERFORM PROCESS-RECORD UNTIL END-OF-FILE = 'Y'. * Example 2: PERFORM UNTIL with compound condition PERFORM CALCULATE-TOTAL UNTIL TOTAL > 1000 OR RECORD-COUNT > 100. * Example 3: In-line PERFORM UNTIL PERFORM UNTIL COUNTER > 5 ADD 1 TO COUNTER DISPLAY "Counter: " COUNTER END-PERFORM. * Example 4: TEST AFTER to ensure at least one execution PERFORM PROCESS-INPUT WITH TEST AFTER UNTIL NO-MORE-INPUT.
These examples show different ways to use the PERFORM UNTIL statement.
1234567891011121314151617181920212223242526272829303132333435363738394041424344454647484950515253545556575859606162636465666768697071727374IDENTIFICATION DIVISION. PROGRAM-ID. PERFUNTIL. DATA DIVISION. WORKING-STORAGE SECTION. 01 COUNTER PIC 9(3) VALUE 0. 01 TOTAL-VALUE PIC 9(5) VALUE 0. 01 USER-INPUT PIC 9(3). 01 CONTINUE-FLAG PIC X VALUE 'Y'. 88 CONTINUE-PROCESS VALUE 'Y' 'y'. 88 END-PROCESS VALUE 'N' 'n'. 01 END-OF-DATA-FLAG PIC X VALUE 'N'. 88 END-OF-DATA VALUE 'Y'. PROCEDURE DIVISION. MAIN-LOGIC. DISPLAY "PERFORM UNTIL Demonstration" DISPLAY "--------------------------" * Basic PERFORM UNTIL DISPLAY "Basic PERFORM UNTIL (runs until COUNTER = 5):" PERFORM COUNT-UP UNTIL COUNTER = 5 DISPLAY "Counter after loop: " COUNTER * With compound condition DISPLAY "PERFORM UNTIL with compound condition:" PERFORM ADD-VALUES UNTIL TOTAL-VALUE > 100 OR COUNTER = 10 DISPLAY "Counter: " COUNTER ", Total: " TOTAL-VALUE * In-line PERFORM UNTIL DISPLAY "In-line PERFORM UNTIL:" MOVE 0 TO COUNTER PERFORM UNTIL COUNTER >= 3 ADD 1 TO COUNTER DISPLAY "In-line iteration: " COUNTER END-PERFORM * Interactive example DISPLAY "Interactive example (enter 999 to stop):" PERFORM PROCESS-USER-INPUT UNTIL END-OF-DATA * TEST AFTER example DISPLAY "TEST AFTER example (guaranteed to run once):" MOVE 'N' TO CONTINUE-FLAG PERFORM DISPLAY-MESSAGE WITH TEST AFTER UNTIL NOT CONTINUE-PROCESS STOP RUN. COUNT-UP. ADD 1 TO COUNTER. DISPLAY "Counting up: " COUNTER. ADD-VALUES. ADD 20 TO TOTAL-VALUE. ADD 1 TO COUNTER. DISPLAY "Added 20, Total now: " TOTAL-VALUE. PROCESS-USER-INPUT. DISPLAY "Enter a number (999 to end): " WITH NO ADVANCING ACCEPT USER-INPUT IF USER-INPUT = 999 SET END-OF-DATA TO TRUE ELSE ADD USER-INPUT TO TOTAL-VALUE DISPLAY "Total so far: " TOTAL-VALUE END-IF. DISPLAY-MESSAGE. DISPLAY "This will display at least once even though" DISPLAY "CONTINUE-PROCESS is already set to 'N'".
This program demonstrates various uses of the PERFORM UNTIL statement.
Key points about PERFORM UNTIL:
Note: PERFORM UNTIL is particularly useful for processing files or user input where the number of iterations isn't known in advance. For example: PERFORM PROCESS-RECORD UNTIL END-OF-FILE
. Just be sure to update the condition variable within the performed code to avoid infinite loops.
The PERFORM VARYING format is the most sophisticated PERFORM option, providing a built-in loop counter that is automatically initialized, incremented, and tested. It's equivalent to a "for" loop in many other programming languages.
1234567891011121314151617181920212223* Format 1: Basic PERFORM VARYING PERFORM paragraph-name VARYING identifier-1 FROM identifier-2 BY identifier-3 UNTIL condition-1. * Format 2: With literal values PERFORM paragraph-name VARYING identifier-1 FROM literal-1 BY literal-2 UNTIL condition-1. * Format 3: In-line PERFORM VARYING PERFORM VARYING identifier-1 FROM identifier-2 BY identifier-3 UNTIL condition-1 statement-1 statement-2 END-PERFORM. * Format 4: Nested VARYING with AFTER PERFORM paragraph-name VARYING identifier-1 FROM identifier-2 BY identifier-3 UNTIL condition-1 AFTER identifier-4 FROM identifier-5 BY identifier-6 UNTIL condition-2.
These formats show how to use the VARYING option with different PERFORM variations.
12345678910111213141516171819202122* Example 1: Simple counter loop PERFORM VARYING COUNTER FROM 1 BY 1 UNTIL COUNTER > 5 DISPLAY "Counter value: " COUNTER END-PERFORM. * Example 2: Decrementing loop PERFORM COUNTDOWN VARYING COUNTER FROM 10 BY -1 UNTIL COUNTER < 1. * Example 3: Using a variable for the increment MOVE 2 TO INCREMENT-VALUE. PERFORM VARYING COUNTER FROM 1 BY INCREMENT-VALUE UNTIL COUNTER > 10 DISPLAY "Even number: " COUNTER END-PERFORM. * Example 4: Nested VARYING for a two-dimensional table PERFORM VARYING ROW-IDX FROM 1 BY 1 UNTIL ROW-IDX > 3 AFTER COL-IDX FROM 1 BY 1 UNTIL COL-IDX > 4 DISPLAY "Position [" ROW-IDX "," COL-IDX "]" END-PERFORM.
These examples show different ways to use the PERFORM VARYING statement.
12345678910111213141516171819202122232425262728293031323334353637383940414243444546474849505152535455565758596061626364656667686970717273747576IDENTIFICATION DIVISION. PROGRAM-ID. PERFVARYING. DATA DIVISION. WORKING-STORAGE SECTION. 01 COUNTER PIC 9(3) VALUE 0. 01 INCREMENT-VALUE PIC 9(2) VALUE 1. 01 TOTAL PIC 9(5) VALUE 0. 01 ROW-IDX PIC 9(2). 01 COL-IDX PIC 9(2). 01 MATRIX-VALUE PIC 9(4). * Table for demonstration 01 MONTHLY-SALES-TABLE. 05 QUARTER-DATA OCCURS 4 TIMES. 10 MONTH-DATA OCCURS 3 TIMES. 15 SALES-AMOUNT PIC 9(6) VALUE 0. PROCEDURE DIVISION. MAIN-LOGIC. DISPLAY "PERFORM VARYING Demonstration" DISPLAY "----------------------------" * Initialize the table with some sample data PERFORM INITIALIZE-TABLE * Simple VARYING example DISPLAY "Simple PERFORM VARYING (1 to 5):" PERFORM VARYING COUNTER FROM 1 BY 1 UNTIL COUNTER > 5 DISPLAY " Iteration: " COUNTER ADD COUNTER TO TOTAL END-PERFORM DISPLAY "Total of numbers 1 to 5: " TOTAL * Decreasing counter DISPLAY "PERFORM VARYING with decreasing counter:" PERFORM VARYING COUNTER FROM 5 BY -1 UNTIL COUNTER < 1 DISPLAY " Countdown: " COUNTER END-PERFORM * Variable increment DISPLAY "PERFORM VARYING with variable increment:" MOVE 2 TO INCREMENT-VALUE PERFORM VARYING COUNTER FROM 1 BY INCREMENT-VALUE UNTIL COUNTER > 10 DISPLAY " Even number: " COUNTER END-PERFORM * Nested VARYING for processing a table DISPLAY "Nested PERFORM VARYING for table processing:" PERFORM VARYING ROW-IDX FROM 1 BY 1 UNTIL ROW-IDX > 4 DISPLAY "Quarter " ROW-IDX ":" PERFORM VARYING COL-IDX FROM 1 BY 1 UNTIL COL-IDX > 3 COMPUTE MATRIX-VALUE = SALES-AMOUNT(ROW-IDX, COL-IDX) / 1000 DISPLAY " Month " COL-IDX ": " MATRIX-VALUE "K" END-PERFORM END-PERFORM STOP RUN. INITIALIZE-TABLE. * Just populate with some sample values * In a real application, this would come from input PERFORM VARYING ROW-IDX FROM 1 BY 1 UNTIL ROW-IDX > 4 PERFORM VARYING COL-IDX FROM 1 BY 1 UNTIL COL-IDX > 3 COMPUTE SALES-AMOUNT(ROW-IDX, COL-IDX) = ((ROW-IDX * 10) + COL-IDX) * 1000 END-PERFORM END-PERFORM.
This program demonstrates the various uses of the PERFORM VARYING statement, including table processing.
Key points about PERFORM VARYING:
Important: The counter variable is modified automatically after each iteration. Manually changing the counter variable within the loop can lead to unexpected behavior and should generally be avoided. If you need to exit the loop early, use the EXIT PERFORM statement (discussed in the next tutorial) rather than manipulating the counter.
COBOL supports nested PERFORM statements, where one PERFORM statement invokes code that contains another PERFORM statement. Understanding how nested PERFORMs behave is crucial for complex program logic.
12345678910111213141516171819202122232425262728* Type 1: Sequential nesting (PERFORM statements in a sequence) MAIN-PARA. PERFORM PARA-A. PERFORM PARA-B. STOP RUN. * Type 2: Hierarchical nesting (PERFORM within a performed paragraph) MAIN-PARA. PERFORM PARA-A. STOP RUN. PARA-A. DISPLAY "In PARA-A". PERFORM PARA-B. DISPLAY "Back in PARA-A". PARA-B. DISPLAY "In PARA-B". * Type 3: Nested in-line PERFORM (explicit nested loops) MAIN-PARA. PERFORM VARYING I FROM 1 BY 1 UNTIL I > 3 DISPLAY "Outer loop: " I PERFORM VARYING J FROM 1 BY 1 UNTIL J > 2 DISPLAY " Inner loop: " J END-PERFORM END-PERFORM. STOP RUN.
These examples show different types of nesting with PERFORM statements.
1234567891011121314151617181920212223242526272829303132333435363738394041424344454647484950515253545556575859606162636465666768IDENTIFICATION DIVISION. PROGRAM-ID. PERFNESTED. DATA DIVISION. WORKING-STORAGE SECTION. 01 OUTER-COUNTER PIC 9(2) VALUE 0. 01 INNER-COUNTER PIC 9(2) VALUE 0. 01 TOTAL-VALUE PIC 9(5) VALUE 0. PROCEDURE DIVISION. MAIN-LOGIC. DISPLAY "Nested PERFORM Demonstration" DISPLAY "--------------------------" * Example of hierarchical nesting DISPLAY "Hierarchical Nesting Example:" PERFORM OUTER-ROUTINE DISPLAY "Back in MAIN-LOGIC" * Example of nested iteration DISPLAY "Nested Iteration Example:" PERFORM VARYING OUTER-COUNTER FROM 1 BY 1 UNTIL OUTER-COUNTER > 3 DISPLAY "Outer Loop: " OUTER-COUNTER PERFORM INNER-LOOP-DEMO END-PERFORM * Example of repetition with nesting DISPLAY "Repetition with Nesting Example:" MOVE 0 TO TOTAL-VALUE PERFORM OUTER-CALCULATION 2 TIMES DISPLAY "Final Total: " TOTAL-VALUE STOP RUN. OUTER-ROUTINE. DISPLAY " Starting OUTER-ROUTINE" PERFORM MIDDLE-ROUTINE DISPLAY " Ending OUTER-ROUTINE" . MIDDLE-ROUTINE. DISPLAY " Starting MIDDLE-ROUTINE" PERFORM INNER-ROUTINE DISPLAY " Ending MIDDLE-ROUTINE" . INNER-ROUTINE. DISPLAY " This is INNER-ROUTINE" . INNER-LOOP-DEMO. PERFORM VARYING INNER-COUNTER FROM 1 BY 1 UNTIL INNER-COUNTER > 3 DISPLAY " Inner Loop: " INNER-COUNTER DISPLAY " [" OUTER-COUNTER "," INNER-COUNTER "]" END-PERFORM . OUTER-CALCULATION. DISPLAY "OUTER-CALCULATION executed" PERFORM INNER-CALCULATION 3 TIMES . INNER-CALCULATION. ADD 10 TO TOTAL-VALUE DISPLAY " Added 10 to TOTAL-VALUE, now: " TOTAL-VALUE .
This program demonstrates various types of nested PERFORM statements.
When a paragraph with a PERFORM statement is itself performed, COBOL preserves the return points for each level. Each PERFORM creates a new return point that is pushed onto a stack. When the performed code completes, control returns to the most recent return point, and that point is popped from the stack.
With nested in-line PERFORM statements, you create explicit nested loops similar to those in other languages. The outer loop executes once, then the inner loop executes completely for each iteration of the outer loop. This differs from hierarchical nesting, where the inner performed paragraph is executed completely before returning to the outer performed paragraph.
Key points about nested PERFORM statements:
Important: Avoid creating recursive PERFORMs (where a paragraph directly or indirectly performs itself), as COBOL doesn't support true recursion. This will cause a stack overflow or runtime error. If you need recursive behavior, you'll need to use explicit stacks and alternative design approaches.
Basic PERFORM Practice
Write a COBOL program that uses the basic PERFORM statement to execute three different paragraphs in sequence, with each paragraph displaying a different message.
PERFORM TIMES Iteration
Create a program that prints a simple multiplication table for a number entered by the user. Use the PERFORM TIMES statement to iterate through multipliers 1 through 10.
PERFORM UNTIL with Input Validation
Write a program that prompts the user for a number between 1 and 100, using PERFORM UNTIL to validate that the input is within the acceptable range before proceeding.
PERFORM VARYING for Table Processing
Create a program with a one-dimensional table of 10 numeric values. Use PERFORM VARYING to populate the table with values, then use another PERFORM VARYING to calculate and display the sum, average, minimum, and maximum values.
Nested PERFORM Demonstration
Write a program that demonstrates both hierarchical nesting and nested in-line PERFORM statements. Use DISPLAY statements to clearly show the flow of execution. Create a pattern using asterisks (*) that requires nested loops to generate.
1. Which format of the PERFORM statement allows you to execute a paragraph a fixed number of times?
2. What is the correct syntax for a PERFORM UNTIL statement?
3. In a PERFORM VARYING statement, when is the condition tested?
4. Which of the following is an in-line PERFORM?
5. What happens if the condition in a PERFORM UNTIL is true before the first execution?
Fundamental programming constructs for controlling program flow
Common patterns for iterating through data and operations
Breaking programs into manageable, reusable components
How programs maintain return addresses for nested operations
Techniques for making loops more efficient