MainframeMaster

COBOL Class Design

Class design in COBOL represents the foundation of object-oriented programming, allowing developers to create reusable, maintainable, and well-structured code. Modern COBOL supports full object-oriented capabilities including classes, inheritance, encapsulation, and polymorphism.

Understanding Class Design Concepts

A class in COBOL is a blueprint that defines the structure and behavior of objects. It encapsulates data (properties) and functions (methods) into a single unit, providing a template for creating multiple instances of similar objects. This approach promotes code reusability and makes programs easier to maintain.

Basic Class Structure

1. Class Definition

Every class in COBOL begins with a CLASS-ID statement in the IDENTIFICATION DIVISION. This statement defines the class name and can include inheritance specifications. The class definition serves as the foundation for all object-oriented functionality.

cobol
1
2
3
4
5
6
7
8
9
10
11
12
13
14
15
IDENTIFICATION DIVISION. CLASS-ID. CUSTOMER-CLASS. *> This defines a class named CUSTOMER-CLASS *> The class will contain customer-related data and operations ENVIRONMENT DIVISION. CONFIGURATION SECTION. *> Environment settings for the class DATA DIVISION. WORKING-STORAGE SECTION. *> Class-level data definitions go here PROCEDURE DIVISION. *> Class methods will be defined here

The CLASS-ID statement creates a new class definition. The name CUSTOMER-CLASS becomes the identifier for this class throughout the program. This is similar to defining a data type, but with the added capability of containing both data and methods that operate on that data.

2. Property Definitions

Properties in COBOL classes define the data attributes that each object instance will contain. These properties can have different access levels (PUBLIC, PRIVATE, PROTECTED) to control how they can be accessed from outside the class.

cobol
1
2
3
4
5
6
7
8
9
10
11
12
13
14
15
16
17
DATA DIVISION. WORKING-STORAGE SECTION. *> Public properties - accessible from outside the class 01 CUSTOMER-ID PIC 9(8) VALUE ZERO. 01 CUSTOMER-NAME PIC X(50) VALUE SPACES. 01 CUSTOMER-EMAIL PIC X(100) VALUE SPACES. *> Private properties - only accessible within the class 01 PRIVATE-CUSTOMER-BALANCE PIC 9(10)V99 VALUE ZERO. 01 PRIVATE-CREDIT-LIMIT PIC 9(8)V99 VALUE ZERO. *> Protected properties - accessible by subclasses 01 PROTECTED-ACCOUNT-STATUS PIC X(1) VALUE 'A'. 88 ACTIVE-ACCOUNT VALUE 'A'. 88 INACTIVE-ACCOUNT VALUE 'I'. 88 SUSPENDED-ACCOUNT VALUE 'S'.

Properties are defined in the WORKING-STORAGE SECTION of the class. Public properties can be accessed directly from outside the class, while private properties are hidden and can only be accessed through class methods. Protected properties are accessible to the class itself and any subclasses that inherit from it.

Method Definitions

1. Basic Method Structure

Methods in COBOL classes are defined using METHOD-ID statements. Each method represents a specific behavior or operation that objects of this class can perform. Methods can accept parameters and return values, making them flexible tools for object interaction.

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
PROCEDURE DIVISION. METHOD-ID. SET-CUSTOMER-DATA. *> This method sets customer information *> Parameters: customer-id, customer-name, customer-email DATA DIVISION. LINKAGE SECTION. 01 CUSTOMER-ID-PARAM PIC 9(8). 01 CUSTOMER-NAME-PARAM PIC X(50). 01 CUSTOMER-EMAIL-PARAM PIC X(100). PROCEDURE DIVISION USING CUSTOMER-ID-PARAM CUSTOMER-NAME-PARAM CUSTOMER-EMAIL-PARAM. *> Store the passed parameters into class properties MOVE CUSTOMER-ID-PARAM TO CUSTOMER-ID MOVE CUSTOMER-NAME-PARAM TO CUSTOMER-NAME MOVE CUSTOMER-EMAIL-PARAM TO CUSTOMER-EMAIL *> Validate the data before storing IF CUSTOMER-ID-PARAM > 0 DISPLAY 'Customer data set successfully' ELSE DISPLAY 'Invalid customer ID provided' END-IF END METHOD SET-CUSTOMER-DATA.

The METHOD-ID statement defines a new method within the class. The USING clause specifies the parameters that the method accepts. Inside the method, we can access both the parameters and the class properties. This method demonstrates data validation and assignment, which are common patterns in class design.

2. Method with Return Value

Methods can return values to the calling code. This is useful for retrieving calculated results or accessing private data through controlled interfaces. The RETURNING clause specifies what value the method will return.

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
METHOD-ID. GET-CUSTOMER-BALANCE. *> This method returns the customer's current balance *> Returns: customer balance as a numeric value DATA DIVISION. LINKAGE SECTION. 01 RETURN-BALANCE PIC 9(10)V99. PROCEDURE DIVISION RETURNING RETURN-BALANCE. *> Return the private balance property MOVE PRIVATE-CUSTOMER-BALANCE TO RETURN-BALANCE *> Log the balance access for audit purposes DISPLAY 'Balance accessed for customer: ' CUSTOMER-ID END METHOD GET-CUSTOMER-BALANCE. METHOD-ID. CALCULATE-TOTAL-CHARGES. *> This method calculates total charges based on transactions DATA DIVISION. LINKAGE SECTION. 01 TRANSACTION-COUNT PIC 9(4). 01 AVERAGE-TRANSACTION PIC 9(6)V99. 01 RETURN-TOTAL PIC 9(10)V99. PROCEDURE DIVISION USING TRANSACTION-COUNT AVERAGE-TRANSACTION RETURNING RETURN-TOTAL. *> Calculate total charges COMPUTE RETURN-TOTAL = TRANSACTION-COUNT * AVERAGE-TRANSACTION *> Apply any discounts or fees IF TRANSACTION-COUNT > 100 COMPUTE RETURN-TOTAL = RETURN-TOTAL * 0.95 DISPLAY 'Volume discount applied' END-IF END METHOD CALCULATE-TOTAL-CHARGES.

The RETURNING clause allows methods to return calculated values. The first method demonstrates accessing private data through a controlled interface, while the second method shows how to perform calculations and return results. This pattern maintains encapsulation while providing necessary functionality.

Inheritance in Class Design

1. Creating a Subclass

Inheritance allows new classes to be created based on existing classes, inheriting their properties and methods. This promotes code reuse and creates hierarchical relationships between classes. The INHERITS clause establishes the inheritance relationship.

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
IDENTIFICATION DIVISION. CLASS-ID. PREMIUM-CUSTOMER-CLASS INHERITS FROM CUSTOMER-CLASS. *> This class inherits all properties and methods from CUSTOMER-CLASS *> It adds premium-specific functionality DATA DIVISION. WORKING-STORAGE SECTION. *> Additional properties specific to premium customers 01 PREMIUM-MEMBERSHIP-TYPE PIC X(10) VALUE SPACES. 01 PREMIUM-DISCOUNT-RATE PIC 9(3)V99 VALUE ZERO. 01 CONCIERGE-SERVICE-FLAG PIC X(1) VALUE 'N'. 88 CONCIERGE-AVAILABLE VALUE 'Y'. 88 CONCIERGE-NOT-AVAILABLE VALUE 'N'. PROCEDURE DIVISION. METHOD-ID. SET-PREMIUM-MEMBERSHIP. *> This method sets premium membership details DATA DIVISION. LINKAGE SECTION. 01 MEMBERSHIP-TYPE-PARAM PIC X(10). 01 DISCOUNT-RATE-PARAM PIC 9(3)V99. PROCEDURE DIVISION USING MEMBERSHIP-TYPE-PARAM DISCOUNT-RATE-PARAM. *> Set premium-specific properties MOVE MEMBERSHIP-TYPE-PARAM TO PREMIUM-MEMBERSHIP-TYPE MOVE DISCOUNT-RATE-PARAM TO PREMIUM-DISCOUNT-RATE *> Enable concierge service for certain membership types IF MEMBERSHIP-TYPE-PARAM = 'PLATINUM' SET CONCIERGE-AVAILABLE TO TRUE DISPLAY 'Concierge service enabled' ELSE SET CONCIERGE-NOT-AVAILABLE TO TRUE END-IF END METHOD SET-PREMIUM-MEMBERSHIP.

The INHERITS FROM clause creates a subclass that automatically includes all properties and methods from the parent class. The subclass can add new properties and methods, and can also override inherited methods to provide specialized behavior. This demonstrates the "is-a" relationship in object-oriented design.

2. Method Overriding

Method overriding allows subclasses to provide their own implementation of inherited methods. This enables polymorphic behavior where the same method call can produce different results depending on the actual object type.

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
METHOD-ID. CALCULATE-TOTAL-CHARGES. *> This method overrides the inherited method to apply premium discounts DATA DIVISION. LINKAGE SECTION. 01 TRANSACTION-COUNT PIC 9(4). 01 AVERAGE-TRANSACTION PIC 9(6)V99. 01 RETURN-TOTAL PIC 9(10)V99. PROCEDURE DIVISION USING TRANSACTION-COUNT AVERAGE-TRANSACTION RETURNING RETURN-TOTAL. *> First calculate the base total using parent class logic INVOKE SUPER "CALCULATE-TOTAL-CHARGES" USING TRANSACTION-COUNT AVERAGE-TRANSACTION RETURNING RETURN-TOTAL *> Apply premium customer discount COMPUTE RETURN-TOTAL = RETURN-TOTAL * (1 - PREMIUM-DISCOUNT-RATE / 100) *> Additional premium benefits IF CONCIERGE-AVAILABLE DISPLAY 'Premium concierge service included' END-IF END METHOD CALCULATE-TOTAL-CHARGES.

Method overriding allows the subclass to provide specialized behavior while still leveraging the parent class functionality. The INVOKE SUPER statement calls the parent class version of the method, then the subclass adds its own logic. This pattern maintains the inheritance hierarchy while providing customized behavior.

Encapsulation Techniques

1. Access Control

Encapsulation in COBOL classes is achieved through careful control of property and method access. Private properties are hidden from external access, while public methods provide controlled interfaces for data manipulation. This protects data integrity and provides a clean API for class 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
37
38
39
40
41
42
43
44
METHOD-ID. UPDATE-BALANCE. *> This method provides controlled access to the private balance property DATA DIVISION. LINKAGE SECTION. 01 TRANSACTION-AMOUNT PIC S9(8)V99. 01 TRANSACTION-TYPE PIC X(1). 88 DEPOSIT VALUE 'D'. 88 WITHDRAWAL VALUE 'W'. 01 RETURN-SUCCESS PIC X(1). 88 SUCCESS VALUE 'Y'. 88 FAILURE VALUE 'N'. PROCEDURE DIVISION USING TRANSACTION-AMOUNT TRANSACTION-TYPE RETURNING RETURN-SUCCESS. *> Validate the transaction before processing IF TRANSACTION-AMOUNT <= 0 SET FAILURE TO TRUE DISPLAY 'Invalid transaction amount' EXIT METHOD END-IF *> Process deposit IF DEPOSIT ADD TRANSACTION-AMOUNT TO PRIVATE-CUSTOMER-BALANCE SET SUCCESS TO TRUE DISPLAY 'Deposit processed successfully' *> Process withdrawal with balance check ELSE IF WITHDRAWAL IF TRANSACTION-AMOUNT <= PRIVATE-CUSTOMER-BALANCE SUBTRACT TRANSACTION-AMOUNT FROM PRIVATE-CUSTOMER-BALANCE SET SUCCESS TO TRUE DISPLAY 'Withdrawal processed successfully' ELSE SET FAILURE TO TRUE DISPLAY 'Insufficient funds for withdrawal' END-IF ELSE SET FAILURE TO TRUE DISPLAY 'Invalid transaction type' END-IF END METHOD UPDATE-BALANCE.

This method demonstrates proper encapsulation by providing controlled access to the private balance property. The method validates all inputs, performs business logic checks (like sufficient funds), and only modifies the private data if all conditions are met. This protects the data from invalid operations and provides clear feedback about the operation's success or failure.

2. Data Validation Methods

Validation methods ensure data integrity by checking input values before they are stored in class properties. These methods encapsulate business rules and validation logic, making the class more robust and easier to maintain.

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
METHOD-ID. VALIDATE-CUSTOMER-DATA. *> This method validates all customer data before storage DATA DIVISION. LINKAGE SECTION. 01 VALIDATION-RESULT PIC X(1). 88 DATA-VALID VALUE 'Y'. 88 DATA-INVALID VALUE 'N'. 01 ERROR-MESSAGE PIC X(100). PROCEDURE DIVISION RETURNING VALIDATION-RESULT ERROR-MESSAGE. *> Initialize validation result SET DATA-VALID TO TRUE MOVE SPACES TO ERROR-MESSAGE *> Validate customer ID IF CUSTOMER-ID <= 0 SET DATA-INVALID TO TRUE MOVE 'Customer ID must be greater than zero' TO ERROR-MESSAGE EXIT METHOD END-IF *> Validate customer name IF CUSTOMER-NAME = SPACES SET DATA-INVALID TO TRUE MOVE 'Customer name cannot be empty' TO ERROR-MESSAGE EXIT METHOD END-IF *> Validate email format (basic check) IF CUSTOMER-EMAIL NOT CONTAINS '@' SET DATA-INVALID TO TRUE MOVE 'Email must contain @ symbol' TO ERROR-MESSAGE EXIT METHOD END-IF *> Validate account status IF NOT ACTIVE-ACCOUNT AND NOT INACTIVE-ACCOUNT AND NOT SUSPENDED-ACCOUNT SET DATA-INVALID TO TRUE MOVE 'Invalid account status' TO ERROR-MESSAGE EXIT METHOD END-IF END METHOD VALIDATE-CUSTOMER-DATA.

This validation method demonstrates comprehensive data checking. It examines each property for validity according to business rules, provides specific error messages for different types of validation failures, and returns both a success indicator and descriptive error information. This approach makes debugging easier and provides clear feedback to calling code.

Polymorphism Implementation

1. Interface-Based Polymorphism

Polymorphism in COBOL allows objects of different classes to be treated uniformly through common interfaces. This is achieved by defining methods with the same signature across different classes, enabling flexible and extensible code design.

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
METHOD-ID. PROCESS-PAYMENT. *> This method processes payments differently based on customer type DATA DIVISION. LINKAGE SECTION. 01 PAYMENT-AMOUNT PIC 9(8)V99. 01 PAYMENT-METHOD PIC X(10). 01 PROCESSING-RESULT PIC X(1). 88 PAYMENT-SUCCESS VALUE 'Y'. 88 PAYMENT-FAILED VALUE 'N'. PROCEDURE DIVISION USING PAYMENT-AMOUNT PAYMENT-METHOD RETURNING PROCESSING-RESULT. *> Different processing based on customer type EVALUATE PAYMENT-METHOD WHEN 'CREDIT-CARD' PERFORM PROCESS-CREDIT-CARD-PAYMENT WHEN 'BANK-TRANSFER' PERFORM PROCESS-BANK-TRANSFER WHEN 'CASH' PERFORM PROCESS-CASH-PAYMENT WHEN OTHER SET PAYMENT-FAILED TO TRUE DISPLAY 'Unsupported payment method' END-EVALUATE END METHOD PROCESS-PAYMENT. METHOD-ID. PROCESS-CREDIT-CARD-PAYMENT. *> Process credit card payments with validation PROCEDURE DIVISION. *> Check credit limit IF PAYMENT-AMOUNT <= PRIVATE-CREDIT-LIMIT SET PAYMENT-SUCCESS TO TRUE DISPLAY 'Credit card payment processed' ELSE SET PAYMENT-FAILED TO TRUE DISPLAY 'Payment exceeds credit limit' END-IF END METHOD PROCESS-CREDIT-CARD-PAYMENT.

This method demonstrates polymorphic behavior by handling different payment methods through a unified interface. The same method call can process various payment types, with each type having its own specific implementation. This makes the code flexible and easy to extend with new payment methods.

Best Practices for Class Design

Common Class Design Patterns