MainframeMaster

COBOL Tutorial

COBOL END-CLASS Clause - Quick Reference

Progress0 of 0 lessons

Overview

The END-CLASS clause is used to terminate a class definition in object-oriented COBOL. This clause marks the end of a class scope and completes the class structure, working in conjunction with the CLASS-ID clause to define complete class definitions.

Purpose and Usage

  • Class termination - Mark the end of a class definition
  • Scope management - Close class scope properly
  • Structure completion - Complete class structure
  • OOP support - Support object-oriented programming
  • Compilation aid - Help compiler understand class boundaries

Class Structure Concept

Class Definition: [CLASS-ID] → [Class Content] → [END-CLASS]
Class Scope: [Start of Class] → [Methods/Properties] → [End of Class]
Structure: [CLASS-ID class-name] → [Class Body] → [END-CLASS]
END-CLASS properly terminates the class definition

END-CLASS provides proper class termination and scope management.

Syntax

The END-CLASS clause follows specific syntax patterns and is used to terminate class definitions in object-oriented COBOL.

Basic Syntax

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
* Basic END-CLASS clause syntax CLASS-ID class-name. * Class content goes here * Methods, properties, etc. END-CLASS. * Examples CLASS-ID CustomerClass. * Customer class methods and properties END-CLASS. CLASS-ID BankAccount. * Bank account class methods and properties END-CLASS. * Complete example CLASS-ID EmployeeClass. ENVIRONMENT DIVISION. CONFIGURATION SECTION. DATA DIVISION. WORKING-STORAGE SECTION. 01 EMPLOYEE-NAME PIC X(50). 01 EMPLOYEE-ID PIC 9(5). METHOD-ID CONSTRUCTOR. DATA DIVISION. LINKAGE SECTION. 01 EMP-NAME PIC X(50). 01 EMP-ID PIC 9(5). PROCEDURE DIVISION USING EMP-NAME EMP-ID. MOVE EMP-NAME TO EMPLOYEE-NAME MOVE EMP-ID TO EMPLOYEE-ID END METHOD. METHOD-ID GET-NAME. DATA DIVISION. LINKAGE SECTION. 01 RETURN-NAME PIC X(50). PROCEDURE DIVISION RETURNING RETURN-NAME. MOVE EMPLOYEE-NAME TO RETURN-NAME END METHOD. END-CLASS.

END-CLASS terminates a class definition that was started with CLASS-ID.

Class Structure Requirements

ComponentRequiredPurpose
CLASS-IDYesStart class definition
Class contentOptionalMethods, properties, data
END-CLASSYesTerminate class definition
MethodsOptionalClass behavior implementation

Multiple Classes 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
* Multiple classes in a single program CLASS-ID CustomerClass. DATA DIVISION. WORKING-STORAGE SECTION. 01 CUSTOMER-NAME PIC X(50). 01 CUSTOMER-ID PIC 9(5). METHOD-ID CONSTRUCTOR. DATA DIVISION. LINKAGE SECTION. 01 CUST-NAME PIC X(50). 01 CUST-ID PIC 9(5). PROCEDURE DIVISION USING CUST-NAME CUST-ID. MOVE CUST-NAME TO CUSTOMER-NAME MOVE CUST-ID TO CUSTOMER-ID END METHOD. END-CLASS. CLASS-ID OrderClass. DATA DIVISION. WORKING-STORAGE SECTION. 01 ORDER-NUMBER PIC 9(10). 01 ORDER-AMOUNT PIC 9(8)V99. METHOD-ID CREATE-ORDER. DATA DIVISION. LINKAGE SECTION. 01 ORD-NUM PIC 9(10). 01 ORD-AMT PIC 9(8)V99. PROCEDURE DIVISION USING ORD-NUM ORD-AMT. MOVE ORD-NUM TO ORDER-NUMBER MOVE ORD-AMT TO ORDER-AMOUNT END METHOD. END-CLASS. * Main program PROGRAM-ID MainProgram. * Main program logic here END PROGRAM.

Each class must be properly terminated with its own END-CLASS clause.

Common Use Cases

END-CLASS is commonly used in specific scenarios where object-oriented programming with classes is needed.

Business Object Classes

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
* Business object class definition CLASS-ID CustomerClass. DATA DIVISION. WORKING-STORAGE SECTION. 01 CUSTOMER-NAME PIC X(50). 01 CUSTOMER-ID PIC 9(5). 01 CUSTOMER-ADDRESS PIC X(100). 01 CUSTOMER-PHONE PIC X(15). METHOD-ID CONSTRUCTOR. DATA DIVISION. LINKAGE SECTION. 01 CUST-NAME PIC X(50). 01 CUST-ID PIC 9(5). 01 CUST-ADDR PIC X(100). 01 CUST-PHONE PIC X(15). PROCEDURE DIVISION USING CUST-NAME CUST-ID CUST-ADDR CUST-PHONE. MOVE CUST-NAME TO CUSTOMER-NAME MOVE CUST-ID TO CUSTOMER-ID MOVE CUST-ADDR TO CUSTOMER-ADDRESS MOVE CUST-PHONE TO CUSTOMER-PHONE END METHOD. METHOD-ID GET-CUSTOMER-INFO. DATA DIVISION. LINKAGE SECTION. 01 RETURN-NAME PIC X(50). 01 RETURN-ID PIC 9(5). PROCEDURE DIVISION RETURNING RETURN-NAME RETURN-ID. MOVE CUSTOMER-NAME TO RETURN-NAME MOVE CUSTOMER-ID TO RETURN-ID END METHOD. END-CLASS.

Define business objects with proper class termination.

Utility Classes

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
* Utility class for common operations CLASS-ID StringUtilityClass. METHOD-ID CONCATENATE-STRINGS. DATA DIVISION. LINKAGE SECTION. 01 STRING1 PIC X(50). 01 STRING2 PIC X(50). 01 RESULT-STRING PIC X(100). PROCEDURE DIVISION USING STRING1 STRING2 RETURNING RESULT-STRING. STRING STRING1 DELIMITED BY SPACE STRING2 DELIMITED BY SPACE INTO RESULT-STRING END METHOD. METHOD-ID CONVERT-TO-UPPERCASE. DATA DIVISION. LINKAGE SECTION. 01 INPUT-STRING PIC X(50). 01 OUTPUT-STRING PIC X(50). PROCEDURE DIVISION USING INPUT-STRING RETURNING OUTPUT-STRING. MOVE FUNCTION UPPER-CASE(INPUT-STRING) TO OUTPUT-STRING END METHOD. METHOD-ID VALIDATE-EMAIL. DATA DIVISION. LINKAGE SECTION. 01 EMAIL-ADDRESS PIC X(100). 01 IS-VALID PIC X. PROCEDURE DIVISION USING EMAIL-ADDRESS RETURNING IS-VALID. IF EMAIL-ADDRESS CONTAINS "@" MOVE "Y" TO IS-VALID ELSE MOVE "N" TO IS-VALID END-IF END METHOD. END-CLASS.

Create utility classes with multiple methods.

Data Access Classes

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
* Data access class for database operations CLASS-ID DatabaseAccessClass. DATA DIVISION. WORKING-STORAGE SECTION. 01 CONNECTION-STRING PIC X(200). 01 SQL-STATEMENT PIC X(500). METHOD-ID CONNECT-DATABASE. DATA DIVISION. LINKAGE SECTION. 01 CONN-STRING PIC X(200). 01 SUCCESS-FLAG PIC X. PROCEDURE DIVISION USING CONN-STRING RETURNING SUCCESS-FLAG. MOVE CONN-STRING TO CONNECTION-STRING * Database connection logic here MOVE "Y" TO SUCCESS-FLAG END METHOD. METHOD-ID EXECUTE-QUERY. DATA DIVISION. LINKAGE SECTION. 01 QUERY-STRING PIC X(500). 01 RESULT-SET PIC X(1000). PROCEDURE DIVISION USING QUERY-STRING RETURNING RESULT-SET. MOVE QUERY-STRING TO SQL-STATEMENT * Query execution logic here MOVE "Query results" TO RESULT-SET END METHOD. METHOD-ID CLOSE-CONNECTION. PROCEDURE DIVISION. * Close database connection logic here END METHOD. END-CLASS.

Define data access classes with database operations.

Best Practices and Tips

Following these best practices ensures effective use of the END-CLASS clause for proper class structure and termination.

END-CLASS Design Principles

  • Always include END-CLASS - Never forget to terminate class definitions
  • Match CLASS-ID and END-CLASS - Ensure proper class scope closure
  • Use meaningful class names - Choose descriptive class names
  • Organize class content - Structure class methods and properties logically
  • Document class purpose - Clearly document what each class does
  • Test class structure - Verify that classes compile and work correctly

Common Pitfalls to Avoid

PitfallProblemSolution
Missing END-CLASSCompilation errors, undefined class scopeAlways include END-CLASS after class definition
Mismatched CLASS-ID/END-CLASSClass structure errorsEnsure each CLASS-ID has corresponding END-CLASS
Poor class organizationDifficult to maintain and understandOrganize class content logically
Unclear class namesConfusing code structureUse descriptive and meaningful class names
Not documenting classesDifficult to understand class purposeDocument class purpose and functionality

Performance Considerations

  • Class instantiation overhead - Creating class instances has overhead
  • Method call overhead - Method calls may have performance impact
  • Memory usage - Classes consume additional memory
  • Compilation time - Object-oriented features may increase compilation time
  • Runtime performance - Consider performance impact of OOP features
  • Class hierarchy complexity - Complex inheritance may affect performance

When to Use END-CLASS

Use CaseEND-CLASS SuitabilityReasoning
Object-oriented programmingEssentialRequired for proper class structure
Business object modelingExcellentPerfect for modeling business entities
Code organizationGoodHelps organize code into logical units
Traditional COBOLNot applicableOnly for object-oriented COBOL
Simple programsPoorUnnecessary complexity for simple logic

END-CLASS Clause Quick Reference

UsageSyntaxExample
Basic class terminationEND-CLASS.END-CLASS.
Complete class structureCLASS-ID name. ... END-CLASS.CLASS-ID MyClass. ... END-CLASS.
Multiple classesMultiple CLASS-ID/END-CLASS pairsCLASS-ID Class1. ... END-CLASS.
CLASS-ID Class2. ... END-CLASS.
Class with methodsCLASS-ID name. ... METHOD-ID. ... END METHOD. END-CLASS.CLASS-ID MyClass. ... METHOD-ID MyMethod. ... END METHOD. END-CLASS.
Class with dataCLASS-ID name. DATA DIVISION. ... END-CLASS.CLASS-ID MyClass. DATA DIVISION. ... END-CLASS.

Test Your Knowledge

1. What is the primary purpose of the END-CLASS clause in COBOL?

  • To define data types
  • To terminate a class definition in object-oriented COBOL
  • To control file operations
  • To perform calculations

2. What must precede the END-CLASS clause?

  • Any COBOL statement
  • A CLASS-ID clause
  • A PROCEDURE DIVISION
  • A DATA DIVISION

3. What is the relationship between CLASS-ID and END-CLASS?

  • They are independent
  • CLASS-ID starts a class, END-CLASS ends it
  • They serve the same purpose
  • They are optional

4. When is END-CLASS most useful?

  • In traditional COBOL programs
  • In object-oriented COBOL programs with classes
  • Only during compilation
  • Only during program termination

5. How does END-CLASS relate to object-oriented programming?

  • They are completely independent
  • END-CLASS is essential for proper class structure in OOP
  • END-CLASS overrides OOP features
  • They serve the same purpose

Frequently Asked Questions