MainframeMaster

COBOL Tutorial

COBOL REFERENCE Clause - Quick Reference

Progress0 of 0 lessons

Overview

The REFERENCE clause is used in CALL statements and subprogram parameter definitions to specify that parameters should be passed by reference rather than by value. This enables efficient data sharing between programs and allows called programs to modify the original data directly.

Purpose and Usage

  • Parameter passing by reference - Pass memory address instead of data copy
  • Data modification - Allow called programs to modify original data
  • Memory efficiency - Avoid copying large data structures
  • Performance optimization - Reduce parameter passing overhead
  • Data sharing - Enable efficient data sharing between programs

Reference vs Content Passing

REFERENCE: [Calling Program] → [Memory Address] → [Called Program]
CONTENT: [Calling Program] → [Data Copy] → [Called Program]
REFERENCE allows modification of original data
CONTENT provides data isolation

REFERENCE passes the memory address, while CONTENT passes a copy of the data.

Syntax

The REFERENCE clause follows specific syntax patterns in CALL statements and subprogram parameter definitions.

Basic Syntax

cobol
1
2
3
4
5
6
7
8
9
10
11
12
13
14
15
16
17
18
19
* Basic REFERENCE clause syntax REFERENCE IS data-name * In CALL statement CALL "subprogram-name" USING REFERENCE parameter-name * In subprogram parameter definition PROCEDURE DIVISION USING REFERENCE parameter-name. * Complete example CALL "CALCULATE-TAX" USING REFERENCE CUSTOMER-DATA REFERENCE TAX-AMOUNT CONTENT TAX-RATE. * Subprogram definition PROCEDURE DIVISION USING REFERENCE CUSTOMER-RECORD REFERENCE TAX-AMOUNT CONTENT TAX-RATE.

REFERENCE can be used in both CALL statements and subprogram parameter definitions.

Mixed Parameter Passing

cobol
1
2
3
4
5
6
7
8
9
10
11
12
13
14
15
16
17
18
19
20
21
22
* Mixing REFERENCE and CONTENT CALL "PROCESS-ORDER" USING REFERENCE ORDER-DATA * Can be modified CONTENT ORDER-NUMBER * Read-only copy REFERENCE TOTAL-AMOUNT * Can be modified CONTENT DISCOUNT-RATE. * Read-only copy * Subprogram receiving mixed parameters PROCEDURE DIVISION USING REFERENCE ORDER-RECORD CONTENT ORDER-NUM REFERENCE TOTAL CONTENT DISCOUNT. * Data definitions 01 ORDER-DATA. 05 CUSTOMER-ID PIC 9(5). 05 ORDER-AMOUNT PIC 9(7)V99. 05 ORDER-STATUS PIC X. 01 ORDER-NUMBER PIC 9(8). 01 TOTAL-AMOUNT PIC 9(7)V99. 01 DISCOUNT-RATE PIC 9(3)V99.

You can mix REFERENCE and CONTENT parameters in the same CALL statement.

Parameter Passing Comparison

AspectREFERENCECONTENT
What is passedMemory addressData copy
Data modificationAllowedNot allowed
Memory usageLowHigh
PerformanceFastSlower
Data safetyLowerHigher

Practical Examples

These examples demonstrate how to use the REFERENCE clause effectively in different programming scenarios.

Customer Data Processing

cobol
1
2
3
4
5
6
7
8
9
10
11
12
13
14
15
16
17
18
19
20
21
22
23
24
25
26
27
28
29
30
31
32
33
34
35
36
37
38
39
40
41
42
43
44
45
46
47
48
49
50
51
52
53
54
55
56
57
58
59
60
61
62
63
* Main program calling subprogram IDENTIFICATION DIVISION. PROGRAM-ID. CUSTOMER-MAIN. DATA DIVISION. WORKING-STORAGE SECTION. 01 CUSTOMER-RECORD. 05 CUSTOMER-ID PIC 9(5). 05 CUSTOMER-NAME PIC X(30). 05 CUSTOMER-BALANCE PIC 9(7)V99. 05 CUSTOMER-STATUS PIC X. 01 PROCESSING-RESULT PIC X(50). PROCEDURE DIVISION. MAIN-PROCESS. * Initialize customer data MOVE 12345 TO CUSTOMER-ID MOVE "JOHN DOE" TO CUSTOMER-NAME MOVE 1000.00 TO CUSTOMER-BALANCE MOVE "A" TO CUSTOMER-STATUS * Call subprogram with REFERENCE parameters CALL "PROCESS-CUSTOMER" USING REFERENCE CUSTOMER-RECORD REFERENCE PROCESSING-RESULT * Display results (data may have been modified) DISPLAY "Customer ID: " CUSTOMER-ID DISPLAY "Customer Name: " CUSTOMER-NAME DISPLAY "Customer Balance: " CUSTOMER-BALANCE DISPLAY "Customer Status: " CUSTOMER-STATUS DISPLAY "Processing Result: " PROCESSING-RESULT STOP RUN. * Subprogram that receives REFERENCE parameters IDENTIFICATION DIVISION. PROGRAM-ID. PROCESS-CUSTOMER. DATA DIVISION. LINKAGE SECTION. 01 CUSTOMER-DATA. 05 CUST-ID PIC 9(5). 05 CUST-NAME PIC X(30). 05 CUST-BALANCE PIC 9(7)V99. 05 CUST-STATUS PIC X. 01 RESULT-MESSAGE PIC X(50). PROCEDURE DIVISION USING REFERENCE CUSTOMER-DATA REFERENCE RESULT-MESSAGE. PROCESS-LOGIC. * Modify customer data (affects original) IF CUST-BALANCE > 500.00 MOVE "P" TO CUST-STATUS MOVE "Customer upgraded to Premium" TO RESULT-MESSAGE ELSE MOVE "S" TO CUST-STATUS MOVE "Customer remains Standard" TO RESULT-MESSAGE END-IF EXIT PROGRAM.

This example shows how REFERENCE allows the subprogram to modify the original customer data.

Array Processing

cobol
1
2
3
4
5
6
7
8
9
10
11
12
13
14
15
16
17
18
19
20
21
22
23
24
25
26
27
28
29
30
31
32
33
34
35
36
37
38
39
40
41
42
43
44
45
46
47
48
49
50
51
52
53
54
55
56
57
58
59
60
61
62
* Main program with array IDENTIFICATION DIVISION. PROGRAM-ID. ARRAY-MAIN. DATA DIVISION. WORKING-STORAGE SECTION. 01 NUMBER-ARRAY. 05 ARRAY-SIZE PIC 9(3) VALUE 5. 05 ARRAY-ELEMENTS PIC 9(3) OCCURS 100 TIMES. 01 SORT-RESULT PIC X(20). PROCEDURE DIVISION. MAIN-PROCESS. * Initialize array MOVE 50 TO ARRAY-ELEMENTS(1) MOVE 30 TO ARRAY-ELEMENTS(2) MOVE 80 TO ARRAY-ELEMENTS(3) MOVE 20 TO ARRAY-ELEMENTS(4) MOVE 60 TO ARRAY-ELEMENTS(5) * Call sort subprogram with REFERENCE CALL "SORT-ARRAY" USING REFERENCE NUMBER-ARRAY REFERENCE SORT-RESULT * Display sorted array (modified by subprogram) PERFORM VARYING I FROM 1 BY 1 UNTIL I > ARRAY-SIZE DISPLAY "Element " I ": " ARRAY-ELEMENTS(I) END-PERFORM DISPLAY "Sort Result: " SORT-RESULT STOP RUN. * Sort subprogram IDENTIFICATION DIVISION. PROGRAM-ID. SORT-ARRAY. DATA DIVISION. LINKAGE SECTION. 01 ARRAY-DATA. 05 SIZE PIC 9(3). 05 ELEMENTS PIC 9(3) OCCURS 100 TIMES. 01 RESULT PIC X(20). PROCEDURE DIVISION USING REFERENCE ARRAY-DATA REFERENCE RESULT. SORT-LOGIC. * Simple bubble sort (modifies original array) PERFORM VARYING I FROM 1 BY 1 UNTIL I >= SIZE PERFORM VARYING J FROM 1 BY 1 UNTIL J >= SIZE IF ELEMENTS(J) > ELEMENTS(J + 1) MOVE ELEMENTS(J) TO TEMP MOVE ELEMENTS(J + 1) TO ELEMENTS(J) MOVE TEMP TO ELEMENTS(J + 1) END-IF END-PERFORM END-PERFORM MOVE "Array sorted successfully" TO RESULT EXIT PROGRAM.

REFERENCE is efficient for large arrays as it avoids copying the entire array.

Mixed Parameter Example

cobol
1
2
3
4
5
6
7
8
9
10
11
12
13
14
15
16
17
18
19
20
21
22
23
24
25
26
27
28
29
30
31
32
33
34
35
36
37
38
39
40
41
42
43
44
45
46
47
48
49
50
51
52
53
54
55
56
57
58
59
60
61
62
* Main program with mixed parameters IDENTIFICATION DIVISION. PROGRAM-ID. MIXED-MAIN. DATA DIVISION. WORKING-STORAGE SECTION. 01 ACCOUNT-DATA. 05 ACCOUNT-NUMBER PIC 9(10). 05 ACCOUNT-BALANCE PIC 9(7)V99. 05 ACCOUNT-TYPE PIC X. 01 INTEREST-RATE PIC 9(3)V99 VALUE 5.50. 01 CALCULATED-INTEREST PIC 9(7)V99. PROCEDURE DIVISION. MAIN-PROCESS. * Initialize account data MOVE 1234567890 TO ACCOUNT-NUMBER MOVE 10000.00 TO ACCOUNT-BALANCE MOVE "S" TO ACCOUNT-TYPE * Call with mixed REFERENCE and CONTENT CALL "CALCULATE-INTEREST" USING REFERENCE ACCOUNT-DATA * Can modify CONTENT INTEREST-RATE * Read-only REFERENCE CALCULATED-INTEREST * Output parameter * Display results DISPLAY "Account: " ACCOUNT-NUMBER DISPLAY "Balance: " ACCOUNT-BALANCE DISPLAY "Interest: " CALCULATED-INTEREST STOP RUN. * Subprogram with mixed parameters IDENTIFICATION DIVISION. PROGRAM-ID. CALCULATE-INTEREST. DATA DIVISION. LINKAGE SECTION. 01 ACCOUNT. 05 ACC-NUMBER PIC 9(10). 05 ACC-BALANCE PIC 9(7)V99. 05 ACC-TYPE PIC X. 01 RATE PIC 9(3)V99. 01 INTEREST PIC 9(7)V99. PROCEDURE DIVISION USING REFERENCE ACCOUNT CONTENT RATE REFERENCE INTEREST. CALCULATE. * Calculate interest (can modify account data) COMPUTE INTEREST = ACC-BALANCE * RATE / 100 * Update account balance ADD INTEREST TO ACC-BALANCE * Rate is CONTENT, so we cannot modify it * ACC-BALANCE and INTEREST are REFERENCE, so changes affect original EXIT PROGRAM.

This example shows how to use REFERENCE for output parameters and CONTENT for input parameters.

Best Practices and Tips

Following these best practices ensures effective and safe use of the REFERENCE clause in COBOL applications.

REFERENCE Usage Guidelines

  • Use for output parameters - When called program needs to return data
  • Use for large data structures - Avoid copying large arrays or records
  • Use CONTENT for input-only - Protect data that shouldn\'t be modified
  • Document parameter intent - Clearly indicate which parameters can be modified
  • Test thoroughly - Verify that data modifications work as expected
  • Consider data safety - Use REFERENCE only when necessary

Common Pitfalls to Avoid

PitfallProblemSolution
Unintended modificationsCalled program modifies data unexpectedlyUse CONTENT for input-only parameters
Data corruptionMultiple programs modify same dataCarefully manage data access
Debugging complexityHard to trace data changesDocument all REFERENCE parameters
Performance overuseUsing REFERENCE for small parametersUse CONTENT for small, simple data
Interface confusionUnclear which parameters are modifiedUse consistent naming conventions

Performance Considerations

  • Memory efficiency - REFERENCE uses less memory than CONTENT
  • Processing speed - REFERENCE is faster for large parameters
  • Copy overhead - CONTENT requires data copying
  • Parameter size impact - Benefits increase with parameter size
  • System resources - Consider overall system impact
  • Network considerations - REFERENCE may not work across systems

When to Use REFERENCE vs CONTENT

ScenarioUse REFERENCEUse CONTENT
Output parametersYesNo
Large data structuresYesNo
Input-only parametersNoYes
Small, simple dataNoYes
Data protection neededNoYes

REFERENCE Clause Quick Reference

UsageSyntaxExample
CALL statementCALL "program" USING REFERENCE paramCALL "SORT" USING REFERENCE ARRAY
Subprogram parameterPROCEDURE DIVISION USING REFERENCE paramUSING REFERENCE DATA-RECORD
Mixed parametersUSING REFERENCE param1 CONTENT param2REFERENCE ARRAY CONTENT RATE
Multiple REFERENCEUSING REFERENCE param1 REFERENCE param2REFERENCE INPUT REFERENCE OUTPUT
Default behaviorUSING param (defaults to CONTENT)USING DATA-ITEM

Test Your Knowledge

1. What is the primary purpose of the REFERENCE clause in COBOL?

  • To define data types
  • To specify parameter passing by reference
  • To control file operations
  • To perform calculations

2. In which context is the REFERENCE clause most commonly used?

  • FILE SECTION
  • CALL statements and subprograms
  • WORKING-STORAGE SECTION
  • ENVIRONMENT DIVISION

3. What happens when a parameter is passed by REFERENCE?

  • A copy of the data is made
  • The address of the data is passed
  • The data is converted to a different type
  • The data is encrypted

4. What is the difference between REFERENCE and CONTENT parameter passing?

  • They are the same thing
  • REFERENCE passes address, CONTENT passes value
  • REFERENCE is faster, CONTENT is slower
  • REFERENCE is for files, CONTENT is for data

5. Which of the following is a valid REFERENCE clause usage?

  • REFERENCE IS data-name
  • REFERENCE CONTAINS value
  • REFERENCE BY ADDRESS
  • REFERENCE MODE

Frequently Asked Questions