MainframeMaster

COBOL Tutorial

COBOL OBJECT-REFERENCE - Object-Oriented Programming

Progress0 of 0 lessons

What is OBJECT-REFERENCE?

OBJECT-REFERENCE is a data type in object-oriented COBOL that holds a reference to an object (an instance of a class). Think of it as a "remote control" that lets you work with objects - you don't directly manipulate the object, but you use the reference to tell the object what to do.

🏗️ Real-World Analogy

Imagine you're building a house:

  • Class: The blueprint for a house (defines what a house should have)
  • Object: An actual house built from that blueprint
  • OBJECT-REFERENCE: The address of that house (lets you find and work with it)
  • Methods: Things you can do with the house (turn on lights, open doors)

Just like you need an address to find a house, you need an OBJECT-REFERENCE to work with an object.

Key Concepts

  • Object-Oriented Programming - A programming paradigm that uses objects to organize code
  • Class - A template that defines what an object should look like and what it can do
  • Instance - A specific object created from a class (like a specific house built from a blueprint)
  • Reference - A way to access and work with an object without directly manipulating its memory
  • Method Invocation - Telling an object to perform an action using its methods
  • Polymorphism - Using different types of objects through the same interface

How to Use OBJECT-REFERENCE

Using OBJECT-REFERENCE involves declaring variables, creating objects, and invoking methods. Let's look at the basic steps.

Basic OBJECT-REFERENCE Usage

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
* Basic OBJECT-REFERENCE example IDENTIFICATION DIVISION. PROGRAM-ID. OBJECT-EXAMPLE. DATA DIVISION. WORKING-STORAGE SECTION. * Declare an object reference variable 01 CUSTOMER-OBJECT OBJECT-REFERENCE. 01 ACCOUNT-OBJECT OBJECT-REFERENCE. 01 RESULT-VALUE PIC X(50). PROCEDURE DIVISION. * Create a new customer object INVOKE Customer "NEW" RETURNING CUSTOMER-OBJECT * Set customer properties INVOKE CUSTOMER-OBJECT "setName" USING BY CONTENT "John Doe" INVOKE CUSTOMER-OBJECT "setAccountNumber" USING BY CONTENT "12345" * Get customer information INVOKE CUSTOMER-OBJECT "getName" RETURNING RESULT-VALUE DISPLAY "Customer Name: " RESULT-VALUE * Create an account object INVOKE Account "NEW" RETURNING ACCOUNT-OBJECT * Link customer to account INVOKE CUSTOMER-OBJECT "setAccount" USING BY REFERENCE ACCOUNT-OBJECT STOP RUN.

This example shows the basic pattern: declare, create, use, and invoke methods.

Object Reference Declaration

DeclarationPurposeExample
01 var-name OBJECT-REFERENCESingle object reference01 CUSTOMER-OBJ OBJECT-REFERENCE
01 var-name OBJECT-REFERENCE OCCURS n TIMESArray of object references01 CUSTOMER-LIST OBJECT-REFERENCE OCCURS 10 TIMES
01 var-name OBJECT-REFERENCE CLASS class-nameTyped object reference01 CUSTOMER-OBJ OBJECT-REFERENCE CLASS Customer
01 var-name OBJECT-REFERENCE INITIAL NULLSInitialized to null01 CUSTOMER-OBJ OBJECT-REFERENCE INITIAL NULLS

Practical Examples

Let's look at some real-world examples of how OBJECT-REFERENCE is used in COBOL applications.

Customer Management System

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
64
65
66
67
68
* Customer management with object references IDENTIFICATION DIVISION. PROGRAM-ID. CUSTOMER-MANAGER. DATA DIVISION. WORKING-STORAGE SECTION. 01 CUSTOMER-OBJECT OBJECT-REFERENCE. 01 ACCOUNT-OBJECT OBJECT-REFERENCE. 01 CUSTOMER-NAME PIC X(50). 01 ACCOUNT-NUMBER PIC 9(10). 01 BALANCE PIC 9(10)V99. 01 ACTION-CODE PIC X(1). PROCEDURE DIVISION. * Create customer object INVOKE Customer "NEW" RETURNING CUSTOMER-OBJECT * Set up customer information MOVE "John Smith" TO CUSTOMER-NAME MOVE "1234567890" TO ACCOUNT-NUMBER MOVE 1000.00 TO BALANCE INVOKE CUSTOMER-OBJECT "setName" USING BY CONTENT CUSTOMER-NAME INVOKE CUSTOMER-OBJECT "setAccountNumber" USING BY CONTENT ACCOUNT-NUMBER * Create account object INVOKE Account "NEW" RETURNING ACCOUNT-OBJECT INVOKE ACCOUNT-OBJECT "setBalance" USING BY CONTENT BALANCE * Link customer to account INVOKE CUSTOMER-OBJECT "setAccount" USING BY REFERENCE ACCOUNT-OBJECT * Perform customer operations PERFORM UNTIL ACTION-CODE = "Q" DISPLAY "Customer Operations:" DISPLAY "1 - View Customer Info" DISPLAY "2 - Deposit Money" DISPLAY "3 - Withdraw Money" DISPLAY "Q - Quit" ACCEPT ACTION-CODE EVALUATE ACTION-CODE WHEN "1" PERFORM DISPLAY-CUSTOMER-INFO WHEN "2" PERFORM DEPOSIT-MONEY WHEN "3" PERFORM WITHDRAW-MONEY END-EVALUATE END-PERFORM STOP RUN. DISPLAY-CUSTOMER-INFO. INVOKE CUSTOMER-OBJECT "displayInfo". DEPOSIT-MONEY. DISPLAY "Enter amount to deposit: " ACCEPT BALANCE INVOKE ACCOUNT-OBJECT "deposit" USING BY CONTENT BALANCE. WITHDRAW-MONEY. DISPLAY "Enter amount to withdraw: " ACCEPT BALANCE INVOKE ACCOUNT-OBJECT "withdraw" USING BY CONTENT BALANCE.

This example shows a complete customer management system using object references.

Polymorphic Shape Calculator

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
* Polymorphic shape calculator using object references IDENTIFICATION DIVISION. PROGRAM-ID. SHAPE-CALCULATOR. DATA DIVISION. WORKING-STORAGE SECTION. 01 SHAPE-OBJECT OBJECT-REFERENCE. 01 SHAPE-TYPE PIC X(10). 01 LENGTH PIC 9(3)V99. 01 WIDTH PIC 9(3)V99. 01 RADIUS PIC 9(3)V99. 01 AREA PIC 9(6)V99. PROCEDURE DIVISION. DISPLAY "Shape Calculator" DISPLAY "Enter shape type (RECTANGLE/CIRCLE): " ACCEPT SHAPE-TYPE * Create appropriate shape object based on type EVALUATE SHAPE-TYPE WHEN "RECTANGLE" DISPLAY "Enter length: " ACCEPT LENGTH DISPLAY "Enter width: " ACCEPT WIDTH INVOKE Rectangle "NEW" USING BY CONTENT LENGTH WIDTH RETURNING SHAPE-OBJECT WHEN "CIRCLE" DISPLAY "Enter radius: " ACCEPT RADIUS INVOKE Circle "NEW" USING BY CONTENT RADIUS RETURNING SHAPE-OBJECT WHEN OTHER DISPLAY "Unknown shape type" STOP RUN END-EVALUATE * Calculate area using polymorphic method call INVOKE SHAPE-OBJECT "calculateArea" RETURNING AREA DISPLAY "Area: " AREA * Display shape information INVOKE SHAPE-OBJECT "displayInfo" STOP RUN.

This example demonstrates polymorphism - the same method call works for different object types.

Advanced OBJECT-REFERENCE Features

OBJECT-REFERENCE supports advanced features for complex object-oriented programming scenarios.

Object Collections and Arrays

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
* Working with collections of objects IDENTIFICATION DIVISION. PROGRAM-ID. OBJECT-COLLECTION. DATA DIVISION. WORKING-STORAGE SECTION. 01 CUSTOMER-LIST OBJECT-REFERENCE OCCURS 10 TIMES. 01 CUSTOMER-COUNT PIC 9(2) VALUE 0. 01 I PIC 9(2). 01 CUSTOMER-NAME PIC X(50). 01 CUSTOMER-OBJECT OBJECT-REFERENCE. PROCEDURE DIVISION. * Add customers to the collection PERFORM ADD-CUSTOMER UNTIL CUSTOMER-COUNT >= 10 * Display all customers PERFORM VARYING I FROM 1 BY 1 UNTIL I > CUSTOMER-COUNT INVOKE CUSTOMER-LIST(I) "getName" RETURNING CUSTOMER-NAME DISPLAY "Customer " I ": " CUSTOMER-NAME END-PERFORM STOP RUN. ADD-CUSTOMER. ADD 1 TO CUSTOMER-COUNT MOVE CUSTOMER-COUNT TO I DISPLAY "Enter customer name: " ACCEPT CUSTOMER-NAME * Create new customer object INVOKE Customer "NEW" RETURNING CUSTOMER-OBJECT INVOKE CUSTOMER-OBJECT "setName" USING BY CONTENT CUSTOMER-NAME * Store in collection MOVE CUSTOMER-OBJECT TO CUSTOMER-LIST(I).

This example shows how to work with collections of objects using arrays of OBJECT-REFERENCE.

Null Reference Handling

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
* Safe object reference handling IDENTIFICATION DIVISION. PROGRAM-ID. SAFE-OBJECT-HANDLING. DATA DIVISION. WORKING-STORAGE SECTION. 01 CUSTOMER-OBJECT OBJECT-REFERENCE INITIAL NULLS. 01 CUSTOMER-NAME PIC X(50). 01 OBJECT-EXISTS PIC X VALUE "N". PROCEDURE DIVISION. * Check if object exists before using it IF CUSTOMER-OBJECT = NULLS DISPLAY "No customer object exists" PERFORM CREATE-CUSTOMER END-IF * Safe method invocation IF CUSTOMER-OBJECT NOT = NULLS INVOKE CUSTOMER-OBJECT "getName" RETURNING CUSTOMER-NAME DISPLAY "Customer: " CUSTOMER-NAME ELSE DISPLAY "Error: Customer object is null" END-IF STOP RUN. CREATE-CUSTOMER. INVOKE Customer "NEW" RETURNING CUSTOMER-OBJECT INVOKE CUSTOMER-OBJECT "setName" USING BY CONTENT "Default Customer".

This example shows how to safely handle null object references to prevent runtime errors.

Best Practices and Tips

Following these best practices will help you use OBJECT-REFERENCE effectively in your COBOL applications.

OBJECT-REFERENCE Best Practices

  • Always check for null references - Check if OBJECT-REFERENCE is NULLS before using it
  • Use meaningful variable names - Name your object references clearly (e.g., CUSTOMER-OBJECT, ACCOUNT-OBJECT)
  • Initialize object references - Use INITIAL NULLS to ensure proper initialization
  • Handle exceptions - Use ON EXCEPTION clauses in INVOKE statements
  • Document object relationships - Document how objects relate to each other
  • Use polymorphism appropriately - Leverage polymorphism for flexible, maintainable code
  • Clean up resources - Set object references to NULLS when done with them

Common Mistakes to Avoid

MistakeProblemSolution
Not checking for null referencesRuntime errors when invoking methodsAlways check IF OBJECT-REF = NULLS before use
Using wrong parameter typesMethod invocation failuresMatch parameter types exactly with method signature
Forgetting to create objectsNull reference errorsAlways use INVOKE class "NEW" to create objects
Not handling exceptionsProgram crashes on errorsUse ON EXCEPTION clauses in INVOKE statements
Memory leaksExcessive memory usageSet object references to NULLS when done

OBJECT-REFERENCE Quick Reference

ActionSyntaxExample
Declare object reference01 var-name OBJECT-REFERENCE01 CUSTOMER-OBJ OBJECT-REFERENCE
Create object instanceINVOKE class "NEW" RETURNING obj-refINVOKE Customer "NEW" RETURNING CUSTOMER-OBJ
Invoke methodINVOKE obj-ref "method" USING paramsINVOKE CUSTOMER-OBJ "setName" USING "John"
Check for nullIF obj-ref = NULLSIF CUSTOMER-OBJ = NULLS
Set to nullMOVE NULLS TO obj-refMOVE NULLS TO CUSTOMER-OBJ
Array of objects01 array OBJECT-REFERENCE OCCURS n01 CUSTOMER-LIST OBJECT-REFERENCE OCCURS 10

Test Your Knowledge

1. What is an OBJECT-REFERENCE in COBOL?

  • A pointer to a data file
  • A reference to a class instance in object-oriented COBOL
  • A reference to a subroutine
  • A memory address

2. How do you declare an OBJECT-REFERENCE variable?

  • 01 MY-OBJECT PIC X(10)
  • 01 MY-OBJECT OBJECT-REFERENCE
  • 01 MY-OBJECT POINTER
  • 01 MY-OBJECT REFERENCE

3. How do you create an object instance using OBJECT-REFERENCE?

  • MOVE "CLASS-NAME" TO OBJECT-REF
  • INVOKE CLASS-NAME "NEW" RETURNING OBJECT-REF
  • CALL CLASS-NAME USING OBJECT-REF
  • SET OBJECT-REF TO CLASS-NAME

4. What is polymorphism in the context of OBJECT-REFERENCE?

  • Multiple objects with the same name
  • The ability to use different object types through the same interface
  • Objects that can change their type
  • Objects that can reference themselves

5. How do you check if an OBJECT-REFERENCE is null?

  • IF OBJECT-REF = NULL
  • IF OBJECT-REF = SPACES
  • IF OBJECT-REF = ZERO
  • IF OBJECT-REF = NULLS

Frequently Asked Questions