MainframeMaster

COBOL Tutorial

COBOL ACCEPT Statement

Progress0 of 0 lessons

Introduction to ACCEPT Statement

The ACCEPT statement in COBOL is a fundamental input operation that allows programs to receive data from external sources during execution. Unlike file operations that read from predefined data files, ACCEPT provides a means for interactive data entry and system information retrieval.

The ACCEPT statement serves multiple purposes in COBOL programming:

  • Reading user input from terminals or keyboards
  • Obtaining system date and time information
  • Accessing special system registers and values
  • Creating interactive programs and user interfaces
  • Implementing data entry forms and prompts

Understanding ACCEPT is crucial for developing interactive COBOL applications and programs that need to respond to user input or system events.

Basic ACCEPT Syntax and Structure

The ACCEPT statement follows a simple but flexible syntax that can be adapted for different input sources and requirements.

General Syntax

cobol
1
2
3
4
ACCEPT identifier [FROM source] [ON EXCEPTION imperative-statement-1] [NOT ON EXCEPTION imperative-statement-2] [END-ACCEPT]

Where:

  • identifier: The data item that will receive the input
  • FROM source: Optional specification of input source
  • ON EXCEPTION: Error handling for input failures
  • NOT ON EXCEPTION: Success handling

Simple Terminal Input 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
IDENTIFICATION DIVISION. PROGRAM-ID. SIMPLE-ACCEPT. DATA DIVISION. WORKING-STORAGE SECTION. 01 USER-NAME PIC X(20). 01 USER-AGE PIC 9(3). 01 GREETING PIC X(50). PROCEDURE DIVISION. DISPLAY "Enter your name: " WITH NO ADVANCING ACCEPT USER-NAME DISPLAY "Enter your age: " WITH NO ADVANCING ACCEPT USER-AGE STRING "Hello, " DELIMITED BY SIZE USER-NAME DELIMITED BY SPACE "! You are " DELIMITED BY SIZE USER-AGE DELIMITED BY SIZE " years old." DELIMITED BY SIZE INTO GREETING DISPLAY GREETING STOP RUN.

ACCEPT FROM DATE and TIME

One of the most powerful features of ACCEPT is its ability to retrieve system date and time information directly from the operating system.

System Date and Time Formats

COBOL provides several formats for system date and time:

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
DATA DIVISION. WORKING-STORAGE SECTION. 01 CURRENT-DATE. 05 CD-YEAR PIC 9(4). 05 CD-MONTH PIC 9(2). 05 CD-DAY PIC 9(2). 01 CURRENT-TIME. 05 CT-HOUR PIC 9(2). 05 CT-MINUTE PIC 9(2). 05 CT-SECOND PIC 9(2). 05 CT-HUNDREDTH PIC 9(2). 01 DATE-TIME-FORMAT. 05 DT-YEAR PIC 9(4). 05 DT-MONTH PIC 9(2). 05 DT-DAY PIC 9(2). 05 DT-HOUR PIC 9(2). 05 DT-MINUTE PIC 9(2). 05 DT-SECOND PIC 9(2). 05 DT-HUNDREDTH PIC 9(2). PROCEDURE DIVISION. * Get current date ACCEPT CURRENT-DATE FROM DATE * Get current time ACCEPT CURRENT-TIME FROM TIME * Get date and time together ACCEPT DATE-TIME-FORMAT FROM DATE YYYYMMDD ACCEPT DATE-TIME-FORMAT FROM TIME DISPLAY "Current Date: " CD-YEAR "-" CD-MONTH "-" CD-DAY DISPLAY "Current Time: " CT-HOUR ":" CT-MINUTE ":" CT-SECOND STOP RUN.

Date and Time Manipulation

Once you have date and time data, you can perform various operations:

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
DATA DIVISION. WORKING-STORAGE SECTION. 01 SYSTEM-DATE PIC 9(8). 01 SYSTEM-TIME PIC 9(8). 01 FORMATTED-DATE PIC X(10). 01 FORMATTED-TIME PIC X(8). PROCEDURE DIVISION. ACCEPT SYSTEM-DATE FROM DATE YYYYMMDD ACCEPT SYSTEM-TIME FROM TIME * Format date for display STRING SYSTEM-DATE(1:4) "-" SYSTEM-DATE(5:2) "-" SYSTEM-DATE(7:2) INTO FORMATTED-DATE * Format time for display STRING SYSTEM-TIME(1:2) ":" SYSTEM-TIME(3:2) ":" SYSTEM-TIME(5:2) INTO FORMATTED-TIME DISPLAY "Date: " FORMATTED-DATE DISPLAY "Time: " FORMATTED-TIME STOP RUN.

ACCEPT FROM Special Registers

COBOL provides access to special system registers through ACCEPT, allowing programs to retrieve various system and environment information.

Common Special Registers

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
DATA DIVISION. WORKING-STORAGE SECTION. 01 SYSTEM-INFO. 05 SYS-DATE PIC 9(8). 05 SYS-TIME PIC 9(8). 05 SYS-DAY-OF-WEEK PIC 9(1). 05 SYS-DAY-OF-YEAR PIC 9(3). 01 ENVIRONMENT-INFO. 05 USER-ID PIC X(8). 05 PROGRAM-NAME PIC X(8). 05 RETURN-CODE PIC 9(4). PROCEDURE DIVISION. * Get system date and time ACCEPT SYS-DATE FROM DATE YYYYMMDD ACCEPT SYS-TIME FROM TIME * Get day information ACCEPT SYS-DAY-OF-WEEK FROM DAY-OF-WEEK ACCEPT SYS-DAY-OF-YEAR FROM DAY-OF-YEAR * Get environment information ACCEPT USER-ID FROM ENVIRONMENT "USER" ACCEPT PROGRAM-NAME FROM ENVIRONMENT "PROGRAM-NAME" DISPLAY "System Date: " SYS-DATE DISPLAY "System Time: " SYS-TIME DISPLAY "Day of Week: " SYS-DAY-OF-WEEK DISPLAY "Day of Year: " SYS-DAY-OF-YEAR DISPLAY "User ID: " USER-ID DISPLAY "Program: " PROGRAM-NAME STOP RUN.

Interactive Input Handling

Creating effective interactive programs requires proper input handling, validation, and user experience considerations.

Input Validation and Error 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
33
34
IDENTIFICATION DIVISION. PROGRAM-ID. INTERACTIVE-INPUT. DATA DIVISION. WORKING-STORAGE SECTION. 01 USER-INPUT. 05 INPUT-VALUE PIC X(20). 05 NUMERIC-VALUE PIC 9(5). 05 VALID-INPUT PIC X(1) VALUE 'N'. 01 ERROR-MESSAGE PIC X(50). 01 PROMPT-MESSAGE PIC X(30). PROCEDURE DIVISION. PERFORM GET-VALID-NUMBER DISPLAY "You entered: " NUMERIC-VALUE STOP RUN. GET-VALID-NUMBER. MOVE 'N' TO VALID-INPUT PERFORM UNTIL VALID-INPUT = 'Y' DISPLAY "Enter a number (1-99999): " WITH NO ADVANCING ACCEPT INPUT-VALUE IF INPUT-VALUE IS NUMERIC MOVE INPUT-VALUE TO NUMERIC-VALUE IF NUMERIC-VALUE > 0 AND NUMERIC-VALUE <= 99999 MOVE 'Y' TO VALID-INPUT ELSE DISPLAY "Number must be between 1 and 99999" END-IF ELSE DISPLAY "Please enter a valid number" END-IF END-PERFORM.

Menu-Driven Interface

Creating user-friendly menus with ACCEPT:

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
IDENTIFICATION DIVISION. PROGRAM-ID. MENU-SYSTEM. DATA DIVISION. WORKING-STORAGE SECTION. 01 MENU-CHOICE PIC 9(1). 01 CONTINUE-FLAG PIC X(1) VALUE 'Y'. PROCEDURE DIVISION. PERFORM UNTIL CONTINUE-FLAG = 'N' DISPLAY "=== MAIN MENU ===" DISPLAY "1. Option One" DISPLAY "2. Option Two" DISPLAY "3. Option Three" DISPLAY "0. Exit" DISPLAY "Enter your choice: " WITH NO ADVANCING ACCEPT MENU-CHOICE EVALUATE MENU-CHOICE WHEN 1 PERFORM OPTION-ONE WHEN 2 PERFORM OPTION-TWO WHEN 3 PERFORM OPTION-THREE WHEN 0 MOVE 'N' TO CONTINUE-FLAG WHEN OTHER DISPLAY "Invalid choice. Please try again." END-EVALUATE END-PERFORM DISPLAY "Goodbye!" STOP RUN. OPTION-ONE. DISPLAY "You selected Option One" DISPLAY "Press Enter to continue..." ACCEPT MENU-CHOICE. OPTION-TWO. DISPLAY "You selected Option Two" DISPLAY "Press Enter to continue..." ACCEPT MENU-CHOICE. OPTION-THREE. DISPLAY "You selected Option Three" DISPLAY "Press Enter to continue..." ACCEPT MENU-CHOICE.

Advanced ACCEPT Techniques

Advanced ACCEPT usage includes exception handling, multiple input sources, and integration with other COBOL features.

Exception Handling with ACCEPT

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
DATA DIVISION. WORKING-STORAGE SECTION. 01 INPUT-DATA PIC X(50). 01 ERROR-COUNT PIC 9(2) VALUE ZERO. 01 MAX-ATTEMPTS PIC 9(2) VALUE 3. PROCEDURE DIVISION. PERFORM GET-INPUT-WITH-RETRY DISPLAY "Input received: " INPUT-DATA STOP RUN. GET-INPUT-WITH-RETRY. PERFORM UNTIL ERROR-COUNT >= MAX-ATTEMPTS DISPLAY "Enter data: " WITH NO ADVANCING ACCEPT INPUT-DATA ON EXCEPTION ADD 1 TO ERROR-COUNT DISPLAY "Input error. Attempt " ERROR-COUNT " of " MAX-ATTEMPTS NOT ON EXCEPTION EXIT PERFORM END-ACCEPT END-PERFORM IF ERROR-COUNT >= MAX-ATTEMPTS DISPLAY "Maximum attempts reached. Using default value." MOVE "DEFAULT-INPUT" TO INPUT-DATA END-IF.

Multiple Input Sources

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
DATA DIVISION. WORKING-STORAGE SECTION. 01 USER-DATA. 05 USER-NAME PIC X(20). 05 USER-DEPT PIC X(10). 05 ENTRY-DATE PIC 9(8). 05 ENTRY-TIME PIC 9(6). PROCEDURE DIVISION. DISPLAY "=== Data Entry Form ===" DISPLAY "Enter your name: " WITH NO ADVANCING ACCEPT USER-NAME DISPLAY "Enter your department: " WITH NO ADVANCING ACCEPT USER-DEPT * Get system date and time ACCEPT ENTRY-DATE FROM DATE YYYYMMDD ACCEPT ENTRY-TIME FROM TIME DISPLAY "=== Entry Summary ===" DISPLAY "Name: " USER-NAME DISPLAY "Department: " USER-DEPT DISPLAY "Entry Date: " ENTRY-DATE DISPLAY "Entry Time: " ENTRY-TIME STOP RUN.

Best Practices for ACCEPT Usage

Following best practices ensures reliable and user-friendly input handling in COBOL applications.

Input Validation Guidelines

  • Always validate input data before processing
  • Provide clear error messages for invalid input
  • Implement retry mechanisms for critical input
  • Use appropriate data types and lengths
  • Consider user experience in prompt design

Performance Considerations

  • Minimize the number of ACCEPT operations
  • Use batch input when possible for large datasets
  • Implement timeout mechanisms for long-running programs
  • Consider alternative input methods for high-volume applications

Security and Data Protection

  • Validate all input to prevent injection attacks
  • Implement proper access controls for sensitive data
  • Use secure input methods for passwords and sensitive information
  • Log input activities for audit purposes

Common ACCEPT Errors and Troubleshooting

Understanding common ACCEPT-related errors helps in debugging and preventing issues in production applications.

Typical Error Scenarios

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
* Common ACCEPT error patterns and solutions * Error: Data truncation 01 SHORT-FIELD PIC X(5). 01 LONG-INPUT PIC X(20). PROCEDURE DIVISION. DISPLAY "Enter data: " WITH NO ADVANCING ACCEPT LONG-INPUT MOVE LONG-INPUT TO SHORT-FIELD * May cause truncation DISPLAY "Truncated: " SHORT-FIELD STOP RUN. * Error: Invalid data type 01 NUMERIC-FIELD PIC 9(5). 01 TEXT-INPUT PIC X(10). PROCEDURE DIVISION. DISPLAY "Enter number: " WITH NO ADVANCING ACCEPT TEXT-INPUT IF TEXT-INPUT IS NOT NUMERIC DISPLAY "Error: Non-numeric input received" ELSE MOVE TEXT-INPUT TO NUMERIC-FIELD END-IF STOP RUN.

Debugging Techniques

  • Use DISPLAY statements to show input values
  • Implement comprehensive error logging
  • Test with various input scenarios
  • Validate data immediately after ACCEPT
  • Use compiler debugging options when available

Exercise: Interactive Calculator

Create an interactive calculator program that uses ACCEPT for user input. The program should:

  • Accept two numbers from the user
  • Accept an operation choice (+, -, *, /)
  • Perform the calculation
  • Display the result
  • Ask if the user wants to perform another calculation

Consider these questions:

  • How would you validate numeric input?
  • What error handling would you implement?
  • How would you handle division by zero?
  • What user interface elements would improve usability?

FAQ

What is the ACCEPT statement in COBOL?

The ACCEPT statement in COBOL is used to read data from external sources such as the terminal, system date/time, or other input devices. It allows COBOL programs to receive input from users or system sources during program execution.

What are the different types of ACCEPT operations in COBOL?

COBOL ACCEPT operations include terminal input (ACCEPT identifier), system date/time (ACCEPT identifier FROM DATE/TIME), and special registers (ACCEPT identifier FROM mnemonic-name). Each type serves different input purposes.

How do you use ACCEPT for terminal input in COBOL?

For terminal input, use 'ACCEPT identifier' where identifier is a data item. The program will pause and wait for user input. Example: 'ACCEPT USER-NAME' reads input into the USER-NAME field.

What is the difference between ACCEPT and READ in COBOL?

ACCEPT reads from external sources like terminals or system functions, while READ accesses data from files. ACCEPT is for interactive input, READ is for file processing. ACCEPT doesn't require file definitions.

How do you handle ACCEPT input validation in COBOL?

ACCEPT input validation involves checking the received data for format, range, and content validity. Use IF statements, numeric tests, and data validation routines after ACCEPT to ensure input meets program requirements.