MainframeMaster

COBOL Tutorial

COBOL IMPLEMENTS Clause - Quick Reference

Progress0 of 0 lessons

Overview

The IMPLEMENTS clause is used in object-oriented COBOL to specify that a class implements one or more interfaces. This clause enables polymorphism and ensures that the class provides all the methods and properties defined in the specified interfaces.

Purpose and Usage

  • Interface implementation - Provide concrete implementations for interface methods
  • Contract-based programming - Ensure classes meet interface requirements
  • Polymorphic behavior - Enable objects to be treated as interface instances
  • Code flexibility - Allow for pluggable components and services
  • Testability - Enable easier unit testing with mock objects

Interface Implementation Flow

Interface: [Method1] [Method2] [Method3] [Method4]
Class Implementation: [Method1] [Method2] [Method3] [Method4]
Contract: Class must implement ALL interface methods
IMPLEMENTS ensures contract compliance

Classes implementing interfaces must provide all required method implementations.

Syntax

The IMPLEMENTS clause follows specific syntax patterns for defining interface implementations 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
44
45
46
47
48
49
50
51
52
53
* Basic IMPLEMENTS clause syntax CLASS-ID class-name IMPLEMENTS interface-name-1, interface-name-2, ... [INHERITS parent-class-name] [FACTORY] [OBJECT] [ENVIRONMENT DIVISION] [DATA DIVISION] [PROCEDURE DIVISION] END CLASS class-name. * Examples CLASS-ID DATABASE-CONNECTION IMPLEMENTS IDATABASE-INTERFACE FACTORY. CLASS-ID FILE-MANAGER IMPLEMENTS IFILE-OPERATIONS, ILOGGING, ISERIALIZABLE FACTORY. * Complete example CLASS-ID PAYMENT-PROCESSOR IMPLEMENTS IPAYMENT-INTERFACE INHERITS BASE-PROCESSOR FACTORY. DATA DIVISION. WORKING-STORAGE SECTION. 01 PROCESSOR-STATUS PIC X(10). 01 TRANSACTION-COUNT PIC 9(5). OBJECT SECTION. PROCEDURE DIVISION. METHOD-ID PROCESS-PAYMENT. DATA DIVISION. LINKAGE SECTION. 01 AMOUNT PIC 9(8)V99. 01 RETURN-CODE PIC 9(4). PROCEDURE DIVISION USING AMOUNT RETURNING RETURN-CODE. PERFORM VALIDATE-PAYMENT IF PAYMENT-VALID PERFORM PROCESS-TRANSACTION MOVE 0 TO RETURN-CODE ELSE MOVE 1 TO RETURN-CODE END-IF EXIT METHOD. END METHOD PROCESS-PAYMENT. END CLASS PAYMENT-PROCESSOR.

IMPLEMENTS specifies interfaces that a class must implement.

Interface Definition

ClausePurposeExample
INTERFACE-IDDefine interface structureINTERFACE-ID IPAYMENT-INTERFACE
METHOD-IDDefine interface methodsMETHOD-ID PROCESS-PAYMENT
IMPLEMENTSSpecify interface implementationIMPLEMENTS IPAYMENT-INTERFACE
END INTERFACEEnd interface definitionEND INTERFACE IPAYMENT-INTERFACE

Multiple Interface Implementation

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
* Implementing multiple interfaces CLASS-ID COMPREHENSIVE-SERVICE IMPLEMENTS IDATABASE-INTERFACE, ILOGGING-INTERFACE, ISECURITY-INTERFACE FACTORY. DATA DIVISION. WORKING-STORAGE SECTION. 01 SERVICE-STATUS PIC X(10). 01 LOG-LEVEL PIC X(10). OBJECT SECTION. PROCEDURE DIVISION. * IDATABASE-INTERFACE methods METHOD-ID CONNECT. DATA DIVISION. LINKAGE SECTION. 01 CONNECTION-STRING PIC X(100). 01 RETURN-CODE PIC 9(4). PROCEDURE DIVISION USING CONNECTION-STRING RETURNING RETURN-CODE. PERFORM ESTABLISH-DB-CONNECTION EXIT METHOD. END METHOD CONNECT. * ILOGGING-INTERFACE methods METHOD-ID LOG-MESSAGE. DATA DIVISION. LINKAGE SECTION. 01 MESSAGE PIC X(200). 01 LEVEL PIC X(10). PROCEDURE DIVISION USING MESSAGE, LEVEL. PERFORM WRITE-TO-LOG EXIT METHOD. END METHOD LOG-MESSAGE. * ISECURITY-INTERFACE methods METHOD-ID AUTHENTICATE. DATA DIVISION. LINKAGE SECTION. 01 USERNAME PIC X(20). 01 PASSWORD PIC X(20). 01 IS-AUTHENTICATED PIC X. PROCEDURE DIVISION USING USERNAME, PASSWORD RETURNING IS-AUTHENTICATED. PERFORM VALIDATE-CREDENTIALS EXIT METHOD. END METHOD AUTHENTICATE. END CLASS COMPREHENSIVE-SERVICE.

Multiple interfaces can be implemented by separating them with commas.

Common Use Cases

IMPLEMENTS is commonly used in specific scenarios where interface-based programming and polymorphic behavior are needed.

Service Layer Implementation

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
69
70
71
72
73
74
75
76
77
78
79
80
81
82
83
84
85
* Service layer with interface implementation INTERFACE-ID IDATABASE-SERVICE. PROCEDURE DIVISION. METHOD-ID CONNECT. DATA DIVISION. LINKAGE SECTION. 01 CONNECTION-STRING PIC X(100). 01 RETURN-CODE PIC 9(4). PROCEDURE DIVISION USING CONNECTION-STRING RETURNING RETURN-CODE. END METHOD CONNECT. METHOD-ID DISCONNECT. DATA DIVISION. PROCEDURE DIVISION. END METHOD DISCONNECT. 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. END METHOD EXECUTE-QUERY. END INTERFACE IDATABASE-SERVICE. CLASS-ID ORACLE-DATABASE-SERVICE IMPLEMENTS IDATABASE-SERVICE FACTORY. DATA DIVISION. WORKING-STORAGE SECTION. 01 ORACLE-CONNECTION PIC X(100). 01 IS-CONNECTED PIC X VALUE 'N'. OBJECT SECTION. PROCEDURE DIVISION. METHOD-ID CONNECT. DATA DIVISION. LINKAGE SECTION. 01 CONNECTION-STRING PIC X(100). 01 RETURN-CODE PIC 9(4). PROCEDURE DIVISION USING CONNECTION-STRING RETURNING RETURN-CODE. MOVE CONNECTION-STRING TO ORACLE-CONNECTION PERFORM ORACLE-CONNECT IF CONNECTION-SUCCESSFUL MOVE 'Y' TO IS-CONNECTED MOVE 0 TO RETURN-CODE ELSE MOVE 1 TO RETURN-CODE END-IF EXIT METHOD. END METHOD CONNECT. METHOD-ID DISCONNECT. DATA DIVISION. PROCEDURE DIVISION. IF IS-CONNECTED = 'Y' PERFORM ORACLE-DISCONNECT MOVE 'N' TO IS-CONNECTED END-IF EXIT METHOD. END METHOD DISCONNECT. 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. IF IS-CONNECTED = 'Y' PERFORM ORACLE-EXECUTE-QUERY ELSE MOVE 'NOT CONNECTED' TO RESULT-SET END-IF EXIT METHOD. END METHOD EXECUTE-QUERY. END CLASS ORACLE-DATABASE-SERVICE.

Service layers use interfaces to provide consistent APIs.

Plugin Architecture

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
69
70
71
72
73
74
75
76
77
78
79
80
81
82
83
* Plugin architecture with interface implementation INTERFACE-ID IPLUGIN-INTERFACE. PROCEDURE DIVISION. METHOD-ID INITIALIZE. DATA DIVISION. LINKAGE SECTION. 01 CONFIG-PARAMS PIC X(200). 01 RETURN-CODE PIC 9(4). PROCEDURE DIVISION USING CONFIG-PARAMS RETURNING RETURN-CODE. END METHOD INITIALIZE. METHOD-ID EXECUTE. DATA DIVISION. LINKAGE SECTION. 01 INPUT-DATA PIC X(500). 01 OUTPUT-DATA PIC X(500). PROCEDURE DIVISION USING INPUT-DATA RETURNING OUTPUT-DATA. END METHOD EXECUTE. METHOD-ID CLEANUP. DATA DIVISION. PROCEDURE DIVISION. END METHOD CLEANUP. END INTERFACE IPLUGIN-INTERFACE. CLASS-ID EMAIL-PLUGIN IMPLEMENTS IPLUGIN-INTERFACE FACTORY. DATA DIVISION. WORKING-STORAGE SECTION. 01 SMTP-SERVER PIC X(50). 01 SMTP-PORT PIC 9(4). 01 IS-INITIALIZED PIC X VALUE 'N'. OBJECT SECTION. PROCEDURE DIVISION. METHOD-ID INITIALIZE. DATA DIVISION. LINKAGE SECTION. 01 CONFIG-PARAMS PIC X(200). 01 RETURN-CODE PIC 9(4). PROCEDURE DIVISION USING CONFIG-PARAMS RETURNING RETURN-CODE. PERFORM PARSE-SMTP-CONFIG IF CONFIG-VALID MOVE 'Y' TO IS-INITIALIZED MOVE 0 TO RETURN-CODE ELSE MOVE 1 TO RETURN-CODE END-IF EXIT METHOD. END METHOD INITIALIZE. METHOD-ID EXECUTE. DATA DIVISION. LINKAGE SECTION. 01 INPUT-DATA PIC X(500). 01 OUTPUT-DATA PIC X(500). PROCEDURE DIVISION USING INPUT-DATA RETURNING OUTPUT-DATA. IF IS-INITIALIZED = 'Y' PERFORM SEND-EMAIL MOVE 'EMAIL SENT' TO OUTPUT-DATA ELSE MOVE 'PLUGIN NOT INITIALIZED' TO OUTPUT-DATA END-IF EXIT METHOD. END METHOD EXECUTE. METHOD-ID CLEANUP. DATA DIVISION. PROCEDURE DIVISION. MOVE 'N' TO IS-INITIALIZED EXIT METHOD. END METHOD CLEANUP. END CLASS EMAIL-PLUGIN.

Plugin architectures use interfaces for extensible functionality.

Polymorphic Behavior

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
* Polymorphic behavior with interface implementation IDENTIFICATION DIVISION. PROGRAM-ID INTERFACE-DEMO. DATA DIVISION. WORKING-STORAGE SECTION. 01 PAYMENT-PROCESSOR OBJECT REFERENCE IPAYMENT-INTERFACE. 01 CREDIT-CARD-PROC OBJECT REFERENCE CREDIT-CARD-PROCESSOR. 01 BANK-TRANSFER-PROC OBJECT REFERENCE BANK-TRANSFER-PROCESSOR. 01 AMOUNT PIC 9(8)V99 VALUE 100.50. 01 RESULT PIC 9(4). PROCEDURE DIVISION. * Create processor instances INVOKE CREDIT-CARD-PROCESSOR "NEW" RETURNING CREDIT-CARD-PROC INVOKE BANK-TRANSFER-PROCESSOR "NEW" RETURNING BANK-TRANSFER-PROC * Use credit card processor SET PAYMENT-PROCESSOR TO CREDIT-CARD-PROC INVOKE PAYMENT-PROCESSOR "PROCESS-PAYMENT" USING AMOUNT RETURNING RESULT DISPLAY 'Credit Card Result: ' RESULT * Switch to bank transfer processor SET PAYMENT-PROCESSOR TO BANK-TRANSFER-PROC INVOKE PAYMENT-PROCESSOR "PROCESS-PAYMENT" USING AMOUNT RETURNING RESULT DISPLAY 'Bank Transfer Result: ' RESULT STOP RUN. END PROGRAM INTERFACE-DEMO.

Polymorphic behavior allows objects to be treated as interface instances.

Best Practices and Tips

Following these best practices ensures effective use of the IMPLEMENTS clause for interface-based programming.

IMPLEMENTS Design Principles

  • Complete implementation - Implement all interface methods
  • Method signature matching - Ensure exact parameter and return type matches
  • Interface segregation - Keep interfaces focused and cohesive
  • Documentation - Document interface contracts and implementations
  • Error handling - Implement proper error handling in interface methods
  • Testing - Test interface implementations thoroughly

Common Pitfalls to Avoid

PitfallProblemSolution
Incomplete implementationCompilation errorsImplement all interface methods
Signature mismatchMethod not recognizedMatch interface method signatures exactly
Large interfacesDifficult to implementKeep interfaces small and focused
No error handlingUnreliable implementationsImplement proper error handling
Poor documentationConfusion about contractsDocument interface requirements

Performance Considerations

  • Interface call overhead - Interface method calls may have slight overhead
  • Multiple interface implementation - Can increase class complexity
  • Memory footprint - Consider the memory usage of interface implementations
  • Method resolution - Interface method resolution may be slower than direct calls
  • Optimization opportunities - Some compilers optimize interface calls
  • Interface granularity - Balance flexibility with performance

When to Use IMPLEMENTS

Use CaseIMPLEMENTS SuitabilityReasoning
Service contractsExcellentPerfect for defining service APIs
Plugin architecturesExcellentIdeal for extensible systems
Polymorphic behaviorGoodEnables polymorphic programming
Simple inheritancePoorUse INHERITS instead
Performance-critical codePoorInterface overhead may be too high

IMPLEMENTS Clause Quick Reference

UsageSyntaxExample
Single interfaceIMPLEMENTS interface-nameIMPLEMENTS IDATABASE-INTERFACE
Multiple interfacesIMPLEMENTS interface1, interface2IMPLEMENTS IFILE, ILOG, ISECURITY
With inheritanceINHERITS parent IMPLEMENTS interfaceINHERITS BASE IMPLEMENTS IINTERFACE
Interface definitionINTERFACE-ID interface-nameINTERFACE-ID IPAYMENT-INTERFACE
Method definitionMETHOD-ID method-nameMETHOD-ID PROCESS-PAYMENT

Test Your Knowledge

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

  • To define class inheritance
  • To specify that a class implements interfaces
  • To create new objects
  • To define data structures

2. What happens if a class implements an interface but doesn't provide all required methods?

  • The program will run normally
  • A compilation error will occur
  • The missing methods will be automatically generated
  • The interface will be ignored

3. How do you specify multiple interfaces in the IMPLEMENTS clause?

  • Use the AND keyword
  • Separate interface names with commas
  • Use multiple IMPLEMENTS clauses
  • Use the OR keyword

4. Which of the following is a benefit of using the IMPLEMENTS clause?

  • Reduced memory usage
  • Polymorphic behavior and code flexibility
  • Faster execution speed
  • Simpler syntax

5. What is the relationship between IMPLEMENTS and INHERITS?

  • They are the same thing
  • IMPLEMENTS is for interfaces, INHERITS is for classes
  • INHERITS is for interfaces, IMPLEMENTS is for classes
  • They cannot be used together

Frequently Asked Questions