MainframeMaster

COBOL Tutorial

Working with Dates and Time in COBOL

Progress0 of 0 lessons

Date Formats and Representation in COBOL

Handling dates and time is a critical aspect of business applications. COBOL provides several ways to represent, manipulate, and calculate dates, which have evolved over different versions of the language.

Common Date Formats in COBOL

COBOL applications typically use several standard formats for representing dates:

FormatDescriptionExampleCommon Usage
YYMMDDSix-digit date with 2-digit year230515 (May 15, 2023)Legacy systems, ACCEPT FROM DATE
YYYYMMDDEight-digit date with 4-digit year20230515 (May 15, 2023)Y2K-compliant systems, INTEGER-OF-DATE
YYDDDJulian date (year + day of year)23135 (May 15, 2023, the 135th day)ACCEPT FROM DAY, NASA/scientific applications
YYYYDDDJulian date with 4-digit year2023135 (May 15, 2023)Modern scientific applications
Separate fieldsYear, month, day as distinct fieldsYY=23, MM=05, DD=15User interfaces, flexible formatting
Packed decimalCompressed date storagePIC 9(6) COMP-3 for YYMMDDDatabase storage, file optimization

The choice of date format depends on factors such as compatibility with existing systems, storage efficiency, calculation requirements, and whether Y2K compliance is needed.

Defining Date Fields in the DATA DIVISION

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
* Examples of date field definitions DATA DIVISION. WORKING-STORAGE SECTION. * Basic formats 01 DATE-YYMMDD PIC 9(6). 01 DATE-YYYYMMDD PIC 9(8). 01 DATE-JULIAN PIC 9(5). 01 DATE-JULIAN-LONG PIC 9(7). * Formatted display fields 01 FORMATTED-DATE. 05 MONTH-DISPLAY PIC X(10). 05 DAY-DISPLAY PIC 99. 05 FILLER PIC X VALUE ",". 05 YEAR-DISPLAY PIC 9(4). * Separate components for flexibility 01 DATE-COMPONENTS. 05 DATE-YEAR PIC 9(4). 05 DATE-MONTH PIC 99. 05 DATE-DAY PIC 99. * Edit patterns for display 01 DATE-DISPLAY-MDY PIC 99/99/9999. 01 DATE-DISPLAY-YYYY-MM-DD PIC 9999-99-99. * Group fields for different formats 01 BIRTH-DATE. 05 BIRTH-YYMMDD PIC 9(6). 05 BIRTH-YYYYMMDD REDEFINES BIRTH-YYMMDD PIC 9(8). * Convenient names for date parts 01 MONTHS-TABLE. 05 MONTH-NAMES PIC X(9) OCCURS 12 TIMES VALUE "January" "February" "March" "April" "May" "June" "July" "August" "September" "October" "November" "December".

When defining date fields in COBOL, consider these best practices:

  • Use 4-digit years where possible to ensure Y2K compliance
  • Include separate fields for individual components when the date needs frequent parsing
  • Use edit patterns for formatting display output
  • Consider space efficiency for files and databases with large volumes
  • Include validation mechanisms for date fields that accept user input

Obtaining Date and Time with ACCEPT Statement

The ACCEPT statement with special FROM phrases is the traditional way to retrieve the current date and time in COBOL. Different options provide access to the system date and time in various formats.

Using ACCEPT FROM DATE

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
IDENTIFICATION DIVISION. PROGRAM-ID. DATEACCEPT. DATA DIVISION. WORKING-STORAGE SECTION. 01 CURRENT-DATE-DATA. 05 DATE-YYMMDD PIC 9(6). 05 DATE-REDEF REDEFINES DATE-YYMMDD. 10 DATE-YY PIC 9(2). 10 DATE-MM PIC 9(2). 10 DATE-DD PIC 9(2). 01 FORMATTED-DATE PIC X(20). PROCEDURE DIVISION. MAIN-PARA. * Accept the current date in YYMMDD format ACCEPT DATE-YYMMDD FROM DATE * Display the raw value DISPLAY "Current date (YYMMDD): " DATE-YYMMDD * Access individual components DISPLAY "Year: " DATE-YY DISPLAY "Month: " DATE-MM DISPLAY "Day: " DATE-DD * Create a formatted string STRING DATE-MM "/" DATE-DD "/" DATE-YY DELIMITED BY SIZE INTO FORMATTED-DATE END-STRING DISPLAY "Formatted date: " FORMATTED-DATE STOP RUN.

Key points about ACCEPT FROM DATE:

  • Returns the current date in YYMMDD format (six digits)
  • The receiving field should be defined as PIC 9(6)
  • Uses two-digit year, which has Y2K implications
  • The actual date source is the system date on the computer running the program
  • Available in all COBOL versions since the 1960s

Using ACCEPT FROM DAY and ACCEPT FROM 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
37
38
IDENTIFICATION DIVISION. PROGRAM-ID. DAYTIMEACCEPT. DATA DIVISION. WORKING-STORAGE SECTION. 01 JULIAN-DATE PIC 9(5). 01 JULIAN-REDEF REDEFINES JULIAN-DATE. 05 JULIAN-YY PIC 9(2). 05 JULIAN-DDD PIC 9(3). 01 CURRENT-TIME PIC 9(8). 01 TIME-REDEF REDEFINES CURRENT-TIME. 05 TIME-HH PIC 9(2). 05 TIME-MM PIC 9(2). 05 TIME-SS PIC 9(2). 05 TIME-HUND PIC 9(2). PROCEDURE DIVISION. MAIN-PARA. * Accept Julian date (YYDDD) ACCEPT JULIAN-DATE FROM DAY DISPLAY "Current Julian date: " JULIAN-DATE DISPLAY "Year: " JULIAN-YY DISPLAY "Day of year: " JULIAN-DDD * Accept current time (HHMMSSCC) ACCEPT CURRENT-TIME FROM TIME DISPLAY "Current time: " CURRENT-TIME DISPLAY "Hours: " TIME-HH DISPLAY "Minutes: " TIME-MM DISPLAY "Seconds: " TIME-SS DISPLAY "Hundredths: " TIME-HUND * Show formatted time DISPLAY "Formatted time: " TIME-HH ":" TIME-MM ":" TIME-SS STOP RUN.

  • ACCEPT FROM DAY - Returns the Julian date in YYDDD format:
    • YY - Two-digit year
    • DDD - Day of the year (001-366)
  • ACCEPT FROM TIME - Returns the current time in HHMMSSCC format:
    • HH - Hours (00-23)
    • MM - Minutes (00-59)
    • SS - Seconds (00-59)
    • CC - Hundredths of a second (00-99)

Using ACCEPT FROM DATE YYYYMMDD (Modern COBOL)

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
IDENTIFICATION DIVISION. PROGRAM-ID. MODERNDATEACCEPT. DATA DIVISION. WORKING-STORAGE SECTION. 01 FULL-DATE PIC 9(8). 01 FULL-DATE-REDEF REDEFINES FULL-DATE. 05 FULL-YEAR PIC 9(4). 05 FULL-MONTH PIC 9(2). 05 FULL-DAY PIC 9(2). PROCEDURE DIVISION. MAIN-PARA. * Accept current date with 4-digit year (YYYYMMDD format) ACCEPT FULL-DATE FROM DATE YYYYMMDD DISPLAY "Current date (YYYYMMDD): " FULL-DATE DISPLAY "Year: " FULL-YEAR DISPLAY "Month: " FULL-MONTH DISPLAY "Day: " FULL-DAY * Display formatted with century DISPLAY "Date: " FULL-MONTH "/" FULL-DAY "/" FULL-YEAR STOP RUN.

  • The YYYYMMDD format was introduced in later COBOL standards to address Y2K concerns
  • Not available in older COBOL compilers—verify your compiler supports this feature
  • Provides full 4-digit year representation
  • Eliminates the need for windowing or conversion for 2-digit years
  • Recommended for all new development

Comprehensive Date-Time Formats

Modern COBOL compilers provide more comprehensive date and time handling capabilities beyond the traditional ACCEPT statement options.

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
IDENTIFICATION DIVISION. PROGRAM-ID. FORMATTEDDATEANDTIME. DATA DIVISION. WORKING-STORAGE SECTION. * Current-date special register (IBM Enterprise COBOL and others) 01 CURRENT-DATE-AND-TIME. 05 CURRENT-DATE. 10 CURRENT-YEAR PIC 9(4). 10 CURRENT-MONTH PIC 9(2). 10 CURRENT-DAY PIC 9(2). 05 CURRENT-TIME. 10 CURRENT-HOUR PIC 9(2). 10 CURRENT-MINUTE PIC 9(2). 10 CURRENT-SECOND PIC 9(2). 10 CURRENT-MSEC PIC 9(2). 05 DIFF-FROM-GMT PIC S9(4). PROCEDURE DIVISION. MAIN-PARA. * Obtain current date and time using FUNCTION CURRENT-DATE MOVE FUNCTION CURRENT-DATE TO CURRENT-DATE-AND-TIME DISPLAY "Current Date Information:" DISPLAY "Date: " CURRENT-YEAR "-" CURRENT-MONTH "-" CURRENT-DAY DISPLAY "Time: " CURRENT-HOUR ":" CURRENT-MINUTE ":" CURRENT-SECOND "." CURRENT-MSEC DISPLAY "GMT Difference (minutes): " DIFF-FROM-GMT STOP RUN.

  • FUNCTION CURRENT-DATE returns a 21-character alphanumeric value with fields for:
    • 4-digit year, month, day
    • Hours, minutes, seconds, hundredths of a second
    • Time zone difference from GMT in minutes
  • This function is available in COBOL 2002 and later standards
  • Provides the most complete date and time information in a single call
  • Includes time zone information, which is valuable for global applications

Date Calculation Techniques

Calculating with dates—such as finding the difference between dates, adding days to a date, or determining specific conditions—is a common requirement in business applications.

Basic Date Arithmetic

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
* Adding days to a date using date components WORKING-STORAGE SECTION. 01 ORIGINAL-DATE. 05 ORIG-YEAR PIC 9(4) VALUE 2023. 05 ORIG-MONTH PIC 9(2) VALUE 05. 05 ORIG-DAY PIC 9(2) VALUE 15. 01 DAYS-TO-ADD PIC 9(5) VALUE 45. 01 NEW-DATE. 05 NEW-YEAR PIC 9(4). 05 NEW-MONTH PIC 9(2). 05 NEW-DAY PIC 9(2). 01 DAYS-IN-MONTH-TABLE. 05 FILLER PIC X(24) VALUE "312831303130313130313031". 05 DAYS-IN-MONTH REDEFINES FILLER PIC 9(2) OCCURS 12 TIMES. 01 MONTH-IDX PIC 9(2). 01 YEAR-IS-LEAP PIC 9 VALUE 0. 88 LEAP-YEAR VALUE 1. PROCEDURE DIVISION. * Determine if original year is a leap year IF FUNCTION MOD(ORIG-YEAR, 400) = 0 OR (FUNCTION MOD(ORIG-YEAR, 4) = 0 AND FUNCTION MOD(ORIG-YEAR, 100) <> 0) SET LEAP-YEAR TO TRUE END-IF * Adjust February days if leap year IF LEAP-YEAR MOVE 29 TO DAYS-IN-MONTH(2) ELSE MOVE 28 TO DAYS-IN-MONTH(2) END-IF * Add days and adjust month/year as needed MOVE ORIG-DAY TO NEW-DAY MOVE ORIG-MONTH TO NEW-MONTH MOVE ORIG-YEAR TO NEW-YEAR PERFORM VARYING MONTH-IDX FROM 1 BY 1 UNTIL DAYS-TO-ADD = 0 ADD 1 TO NEW-DAY SUBTRACT 1 FROM DAYS-TO-ADD * Check if we need to move to next month IF NEW-DAY > DAYS-IN-MONTH(NEW-MONTH) MOVE 1 TO NEW-DAY ADD 1 TO NEW-MONTH * Check if we need to move to next year IF NEW-MONTH > 12 MOVE 1 TO NEW-MONTH ADD 1 TO NEW-YEAR * Recalculate leap year status for the new year IF FUNCTION MOD(NEW-YEAR, 400) = 0 OR (FUNCTION MOD(NEW-YEAR, 4) = 0 AND FUNCTION MOD(NEW-YEAR, 100) <> 0) SET LEAP-YEAR TO TRUE ELSE SET LEAP-YEAR TO FALSE END-IF * Update February days based on leap year status IF LEAP-YEAR MOVE 29 TO DAYS-IN-MONTH(2) ELSE MOVE 28 TO DAYS-IN-MONTH(2) END-IF END-IF END-IF END-PERFORM DISPLAY "Original date: " ORIG-YEAR "-" ORIG-MONTH "-" ORIG-DAY DISPLAY "Days added: " DAYS-TO-ADD DISPLAY "New date: " NEW-YEAR "-" NEW-MONTH "-" NEW-DAY

This example demonstrates manual date calculation by:

  • Determining if the year is a leap year to correctly handle February
  • Tracking days in each month
  • Incrementing day by day with appropriate handling for month and year rollovers
  • Recalculating leap year status when crossing year boundaries

While this approach works, it's complex and error-prone. The date function approach shown in subsequent examples is recommended for most applications.

Using FUNCTION DATE-OF-INTEGER and INTEGER-OF-DATE

Modern COBOL provides powerful intrinsic functions for working with dates. The INTEGER-OF-DATE and DATE-OF-INTEGER functions are particularly useful for date arithmetic and simplify many complex date operations.

Converting Between Dates and Integers

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
IDENTIFICATION DIVISION. PROGRAM-ID. DATEFUNCTIONS. DATA DIVISION. WORKING-STORAGE SECTION. 01 DATE-1 PIC 9(8) VALUE 20230515. 01 DATE-2 PIC 9(8) VALUE 20231225. 01 INT-DATE-1 PIC 9(7). 01 INT-DATE-2 PIC 9(7). 01 DATE-DIFF PIC 9(5). 01 FUTURE-DATE PIC 9(8). PROCEDURE DIVISION. MAIN-PARA. * Convert dates to integers (days since Dec 31, 1600) COMPUTE INT-DATE-1 = FUNCTION INTEGER-OF-DATE(DATE-1) COMPUTE INT-DATE-2 = FUNCTION INTEGER-OF-DATE(DATE-2) DISPLAY "Date 1 (YYYYMMDD): " DATE-1 DISPLAY "Date 1 as integer: " INT-DATE-1 DISPLAY "Date 2 (YYYYMMDD): " DATE-2 DISPLAY "Date 2 as integer: " INT-DATE-2 * Calculate days between dates COMPUTE DATE-DIFF = INT-DATE-2 - INT-DATE-1 DISPLAY "Days between dates: " DATE-DIFF * Add 30 days to Date 1 COMPUTE INT-DATE-1 = INT-DATE-1 + 30 COMPUTE FUTURE-DATE = FUNCTION DATE-OF-INTEGER(INT-DATE-1) DISPLAY "Date 1 + 30 days: " FUTURE-DATE * Calculate date 90 days ago from Date 2 COMPUTE INT-DATE-2 = INT-DATE-2 - 90 COMPUTE FUTURE-DATE = FUNCTION DATE-OF-INTEGER(INT-DATE-2) DISPLAY "Date 2 - 90 days: " FUTURE-DATE STOP RUN.

How these functions work:

  • INTEGER-OF-DATE - Converts a date in YYYYMMDD format to an integer representing the number of days since December 31, 1600
  • DATE-OF-INTEGER - Converts an integer (days since December 31, 1600) back to a date in YYYYMMDD format
  • These functions automatically handle leap years, month lengths, and other calendar complexities
  • They provide a straightforward way to perform date arithmetic without complex logic for month and year boundaries

Practical Date Calculations

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
* Calculate the end date of a 30-day payment period 01 INVOICE-DATE PIC 9(8) VALUE 20231005. 01 DUE-DATE PIC 9(8). 01 INT-INVOICE-DATE PIC 9(7). 01 INT-DUE-DATE PIC 9(7). 01 PAYMENT-DAYS PIC 9(3) VALUE 30. PROCEDURE DIVISION. * Convert invoice date to integer COMPUTE INT-INVOICE-DATE = FUNCTION INTEGER-OF-DATE(INVOICE-DATE) * Add payment period COMPUTE INT-DUE-DATE = INT-INVOICE-DATE + PAYMENT-DAYS * Convert back to YYYYMMDD format COMPUTE DUE-DATE = FUNCTION DATE-OF-INTEGER(INT-DUE-DATE) DISPLAY "Invoice date: " INVOICE-DATE DISPLAY "Due date: " DUE-DATE * Calculate age based on birth date 01 BIRTH-DATE PIC 9(8) VALUE 19850612. 01 CURRENT-DATE-X. 05 CURRENT-YEAR PIC 9(4). 05 CURRENT-MONTH PIC 9(2). 05 CURRENT-DAY PIC 9(2). 01 INT-BIRTH-DATE PIC 9(7). 01 INT-TODAY PIC 9(7). 01 AGE-YEARS PIC 9(3). 01 TODAY-FULL PIC 9(8). 01 TEMP-DATE PIC 9(8). PROCEDURE DIVISION. * Get current date MOVE FUNCTION CURRENT-DATE(1:8) TO CURRENT-DATE-X * Reconstruct YYYYMMDD format COMPUTE TODAY-FULL = CURRENT-YEAR * 10000 + CURRENT-MONTH * 100 + CURRENT-DAY * Convert dates to integers COMPUTE INT-BIRTH-DATE = FUNCTION INTEGER-OF-DATE(BIRTH-DATE) COMPUTE INT-TODAY = FUNCTION INTEGER-OF-DATE(TODAY-FULL) * Calculate approximate age in years COMPUTE AGE-YEARS = (INT-TODAY - INT-BIRTH-DATE) / 365 * More precisely, check if birthday has occurred this year COMPUTE TEMP-DATE = CURRENT-YEAR * 10000 + (BIRTH-DATE - (BIRTH-DATE / 10000) * 10000) * If birthday hasn't occurred yet this year, subtract 1 IF TEMP-DATE > TODAY-FULL SUBTRACT 1 FROM AGE-YEARS END-IF DISPLAY "Birth date: " BIRTH-DATE DISPLAY "Current date: " TODAY-FULL DISPLAY "Age: " AGE-YEARS " years"

These examples demonstrate practical applications of date functions:

  • Calculating a due date by adding days to an invoice date
  • Computing a person's age based on birth date
  • The age calculation includes an adjustment to check if the birthday has occurred in the current year
  • These calculations handle month boundaries, leap years, and other calendar complexities automatically

Additional Date Functions

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
* Day-of-week calculation 01 TEST-DATE PIC 9(8) VALUE 20230515. 01 INT-DATE PIC 9(7). 01 DAY-OF-WEEK PIC 9. 01 DAY-NAMES-TABLE. 05 DAY-NAMES PIC X(9) OCCURS 7 TIMES VALUE "Monday" "Tuesday" "Wednesday" "Thursday" "Friday" "Saturday" "Sunday". PROCEDURE DIVISION. * Calculate day of week (1=Monday, 7=Sunday) COMPUTE INT-DATE = FUNCTION INTEGER-OF-DATE(TEST-DATE) COMPUTE DAY-OF-WEEK = FUNCTION MOD(INT-DATE, 7) + 1 DISPLAY "Date: " TEST-DATE DISPLAY "Day of week: " DAY-NAMES(DAY-OF-WEEK) * Month-end date calculation 01 INPUT-DATE PIC 9(8) VALUE 20230515. 01 MONTH-END-DATE PIC 9(8). 01 NEXT-MONTH-START PIC 9(8). 01 INT-DATE PIC 9(7). PROCEDURE DIVISION. * Extract year and month from input date COMPUTE NEXT-MONTH-START = (INPUT-DATE / 100) * 100 + 101 * Handle December - advance to January of next year IF FUNCTION MOD(NEXT-MONTH-START, 10000) = 1301 COMPUTE NEXT-MONTH-START = ((NEXT-MONTH-START / 10000) + 1) * 10000 + 101 END-IF * Convert to integer, subtract 1 day, and convert back COMPUTE INT-DATE = FUNCTION INTEGER-OF-DATE(NEXT-MONTH-START) - 1 COMPUTE MONTH-END-DATE = FUNCTION DATE-OF-INTEGER(INT-DATE) DISPLAY "Input date: " INPUT-DATE DISPLAY "Month end date: " MONTH-END-DATE

These examples show more advanced date calculations:

  • Determining the day of the week for a given date
  • Finding the last day of the month
  • Using FUNCTION MOD for cyclic values like days of the week
  • Handling year boundaries in month-based calculations

Year 2000 (Y2K) Considerations

The Year 2000 (Y2K) problem was a significant concern for COBOL applications, many of which used two-digit years. Understanding these issues and their solutions remains relevant today, especially when maintaining legacy code or designing for long-term sustainability.

The Y2K Problem

The core issue of Y2K was the use of two-digit years, which made years like 1900 and 2000 indistinguishable (both represented as "00"). This caused problems with:

  • Date comparisons (determining which date comes before or after another)
  • Age calculations (potentially yielding negative ages)
  • Sort orders in files and databases
  • Date arithmetic that crossed the century boundary
  • Leap year determination for the year 2000

Y2K Solutions in COBOL

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
* Solution 1: Expansion to four-digit years 01 OLD-DATE-YYMM PIC 9(4) VALUE 2304. 01 EXPANDED-DATE. 05 CENTURY PIC 9(2) VALUE 20. 05 YEAR-YY PIC 9(2). 05 MONTH-MM PIC 9(2). 01 FULL-YYYYMM PIC 9(6). PROCEDURE DIVISION. * Extract the YY and MM parts COMPUTE YEAR-YY = OLD-DATE-YYMM / 100 COMPUTE MONTH-MM = FUNCTION MOD(OLD-DATE-YYMM, 100) * Create expanded date COMPUTE FULL-YYYYMM = CENTURY * 10000 + YEAR-YY * 100 + MONTH-MM DISPLAY "Original date (YYMM): " OLD-DATE-YYMM DISPLAY "Expanded date (YYYYMM): " FULL-YYYYMM * Solution 2: Windowing technique 01 TWO-DIGIT-YEAR PIC 9(2) VALUE 15. 01 FULL-YEAR PIC 9(4). 01 PIVOT-YEAR PIC 9(2) VALUE 50. PROCEDURE DIVISION. * Apply windowing rule: years 00-49 are 2000-2049, * years 50-99 are 1950-1999 IF TWO-DIGIT-YEAR < PIVOT-YEAR COMPUTE FULL-YEAR = 2000 + TWO-DIGIT-YEAR ELSE COMPUTE FULL-YEAR = 1900 + TWO-DIGIT-YEAR END-IF DISPLAY "Two-digit year: " TWO-DIGIT-YEAR DISPLAY "Full year (windowed): " FULL-YEAR * Solution 3: Windowing encapsulation in a function paragraph 01 INPUT-YY PIC 9(2). 01 RESULT-YYYY PIC 9(4). PROCEDURE DIVISION. MOVE 95 TO INPUT-YY PERFORM EXPAND-YEAR DISPLAY "Input YY: " INPUT-YY ", Expanded: " RESULT-YYYY MOVE 05 TO INPUT-YY PERFORM EXPAND-YEAR DISPLAY "Input YY: " INPUT-YY ", Expanded: " RESULT-YYYY STOP RUN. EXPAND-YEAR. IF INPUT-YY < 50 COMPUTE RESULT-YYYY = 2000 + INPUT-YY ELSE COMPUTE RESULT-YYYY = 1900 + INPUT-YY END-IF.

Common Y2K solutions in COBOL included:

  • Expansion - Converting two-digit years to four-digit years throughout the system
  • Windowing - Using a "sliding window" to interpret two-digit years within a 100-year range
  • Encapsulation - Creating reusable routines to handle date interpretation consistently
  • Date Libraries - Implementing comprehensive date handling libraries
  • Compiler Options - Using compiler features for date handling

Best Practices for Date Handling Post-Y2K

Learning from the Y2K experience, these best practices should be followed for robust date handling in COBOL applications:

  • Always use four-digit years in new development
  • Use DATE-OF-INTEGER and INTEGER-OF-DATE for date arithmetic
  • Document date formats clearly in field definitions
  • Implement validation routines for all date inputs
  • Use consistent date formats throughout an application
  • Consider time zone issues for global applications
  • Test date handling with boundary cases (month/year transitions, leap years)
  • Create a date utilities library for common operations
  • Avoid hard-coding year comparisons or fixed date values
  • Implement proper error handling for date operations

Lessons from Y2K for Modern Development

The Y2K experience provided valuable lessons for software development that still apply today:

  • Design for the long term - Consider how data will be interpreted decades later
  • Avoid shortcuts in data representation - Saving a few bytes can cost billions later
  • Document assumptions - Make implicit assumptions explicit in documentation
  • Centralize key functionality - Use libraries for common operations like date handling
  • Test edge cases - Test with unusual dates, century boundaries, etc.
  • Consider maintenance - Write code that future maintainers will understand
  • Plan for technology evolution - Today's standards may change

Practical Examples of Date and Time Handling

Let's examine some common real-world scenarios involving date and time calculations in COBOL business applications.

Example: Date Validation Routine

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
IDENTIFICATION DIVISION. PROGRAM-ID. DATEVALIDATION. DATA DIVISION. WORKING-STORAGE SECTION. 01 TEST-DATE. 05 TEST-YEAR PIC 9(4). 05 TEST-MONTH PIC 9(2). 05 TEST-DAY PIC 9(2). 01 DAYS-IN-MONTH-TABLE. 05 FILLER PIC X(24) VALUE "312831303130313130313031". 05 DAYS-IN-MONTH REDEFINES FILLER PIC 9(2) OCCURS 12 TIMES. 01 IS-VALID-FLAG PIC X VALUE "N". 88 IS-VALID-DATE VALUE "Y". 01 MONTH-DAYS PIC 9(2). PROCEDURE DIVISION. * Test with valid date MOVE 2023 TO TEST-YEAR MOVE 5 TO TEST-MONTH MOVE 15 TO TEST-DAY PERFORM VALIDATE-DATE DISPLAY "2023-05-15 is valid: " IS-VALID-FLAG * Test with invalid date MOVE 2023 TO TEST-YEAR MOVE 2 TO TEST-MONTH MOVE 30 TO TEST-DAY PERFORM VALIDATE-DATE DISPLAY "2023-02-30 is valid: " IS-VALID-FLAG * Test with leap year MOVE 2024 TO TEST-YEAR MOVE 2 TO TEST-MONTH MOVE 29 TO TEST-DAY PERFORM VALIDATE-DATE DISPLAY "2024-02-29 is valid: " IS-VALID-FLAG STOP RUN. VALIDATE-DATE. MOVE "N" TO IS-VALID-FLAG * First check year, month, and day are in valid ranges IF TEST-YEAR >= 1600 AND TEST-YEAR <= 9999 AND TEST-MONTH >= 1 AND TEST-MONTH <= 12 AND TEST-DAY >= 1 AND TEST-DAY <= 31 * Get days in this month MOVE DAYS-IN-MONTH(TEST-MONTH) TO MONTH-DAYS * Check for February in leap year IF TEST-MONTH = 2 AND (FUNCTION MOD(TEST-YEAR, 400) = 0 OR (FUNCTION MOD(TEST-YEAR, 4) = 0 AND FUNCTION MOD(TEST-YEAR, 100) <> 0)) MOVE 29 TO MONTH-DAYS END-IF * Final check: day is valid for this month IF TEST-DAY <= MONTH-DAYS MOVE "Y" TO IS-VALID-FLAG END-IF END-IF.

This validation routine:

  • Checks that year, month, and day values are within valid ranges
  • Verifies that the day is valid for the specific month, accounting for different month lengths
  • Handles February correctly for leap years using the leap year calculation rule
  • Returns a flag indicating whether the date is valid
  • Can be incorporated into any program that needs date validation

Example: Business Date Calculations

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
* Payment terms calculation (Net 30, 2/10 Net 30) 01 INVOICE-DATE PIC 9(8) VALUE 20230510. 01 INT-DATE PIC 9(7). 01 DISCOUNT-DATE PIC 9(8). 01 DUE-DATE PIC 9(8). 01 DAYS-TO-DISCOUNT PIC 9(2) VALUE 10. 01 DAYS-TO-PAYMENT PIC 9(3) VALUE 30. PROCEDURE DIVISION. * Convert invoice date to integer COMPUTE INT-DATE = FUNCTION INTEGER-OF-DATE(INVOICE-DATE) * Calculate discount date (invoice date + 10 days) COMPUTE DISCOUNT-DATE = FUNCTION DATE-OF-INTEGER(INT-DATE + DAYS-TO-DISCOUNT) * Calculate due date (invoice date + 30 days) COMPUTE DUE-DATE = FUNCTION DATE-OF-INTEGER(INT-DATE + DAYS-TO-PAYMENT) DISPLAY "Invoice date: " INVOICE-DATE DISPLAY "2% discount if paid by: " DISCOUNT-DATE DISPLAY "Payment due by: " DUE-DATE * Interest accrual calculation 01 LOAN-START-DATE PIC 9(8) VALUE 20230301. 01 CURRENT-DATE-X PIC 9(8) VALUE 20230515. 01 INT-START-DATE PIC 9(7). 01 INT-CURRENT-DATE PIC 9(7). 01 DAYS-OUTSTANDING PIC 9(5). 01 LOAN-AMOUNT PIC 9(7)V99 VALUE 10000.00. 01 ANNUAL-RATE PIC 9(2)V9(4) VALUE 0.0525. 01 DAILY-RATE PIC 9(9)V9(9). 01 INTEREST-AMOUNT PIC 9(5)V99. PROCEDURE DIVISION. * Convert dates to integers COMPUTE INT-START-DATE = FUNCTION INTEGER-OF-DATE(LOAN-START-DATE) COMPUTE INT-CURRENT-DATE = FUNCTION INTEGER-OF-DATE(CURRENT-DATE-X) * Calculate days outstanding COMPUTE DAYS-OUTSTANDING = INT-CURRENT-DATE - INT-START-DATE * Calculate daily interest rate (annual rate / 365) COMPUTE DAILY-RATE = ANNUAL-RATE / 365 * Calculate interest amount COMPUTE INTEREST-AMOUNT = LOAN-AMOUNT * DAILY-RATE * DAYS-OUTSTANDING DISPLAY "Loan start date: " LOAN-START-DATE DISPLAY "Current date: " CURRENT-DATE-X DISPLAY "Days outstanding: " DAYS-OUTSTANDING DISPLAY "Annual interest rate: " ANNUAL-RATE DISPLAY "Interest accrued: $" INTEREST-AMOUNT

These examples show common business date calculations:

  • Payment terms calculation with early discount and due dates
  • Interest accrual based on days outstanding
  • Both examples use the INTEGER-OF-DATE and DATE-OF-INTEGER functions for clean date arithmetic
  • These patterns are common in financial applications, invoice processing, and loan management systems

Example: Formatting Dates for Display

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
* Format date YYYYMMDD to MM/DD/YYYY 01 INPUT-DATE PIC 9(8) VALUE 20230515. 01 FORMATTED-DATE PIC X(10). 01 DATE-COMPONENTS. 05 DATE-YYYY PIC 9(4). 05 DATE-MM PIC 9(2). 05 DATE-DD PIC 9(2). PROCEDURE DIVISION. * Extract date components COMPUTE DATE-YYYY = INPUT-DATE / 10000 COMPUTE DATE-MM = FUNCTION MOD(INPUT-DATE / 100, 100) COMPUTE DATE-DD = FUNCTION MOD(INPUT-DATE, 100) * Format as MM/DD/YYYY STRING DATE-MM "/" DATE-DD "/" DATE-YYYY DELIMITED BY SIZE INTO FORMATTED-DATE END-STRING DISPLAY "Raw date: " INPUT-DATE DISPLAY "Formatted date: " FORMATTED-DATE * Format date with month name 01 INPUT-DATE PIC 9(8) VALUE 20230515. 01 LONG-FORMAT PIC X(20). 01 DATE-COMPONENTS. 05 DATE-YYYY PIC 9(4). 05 DATE-MM PIC 9(2). 05 DATE-DD PIC 9(2). 01 MONTH-NAME PIC X(10). 01 MONTH-NAMES-TABLE. 05 FILLER PIC X(120) VALUE "January February March April May June " & "July August SeptemberOctober November December ". 05 MONTHS REDEFINES MONTH-NAMES-TABLE. 10 MONTH PIC X(10) OCCURS 12 TIMES. PROCEDURE DIVISION. * Extract date components COMPUTE DATE-YYYY = INPUT-DATE / 10000 COMPUTE DATE-MM = FUNCTION MOD(INPUT-DATE / 100, 100) COMPUTE DATE-DD = FUNCTION MOD(INPUT-DATE, 100) * Get month name MOVE MONTHS(DATE-MM) TO MONTH-NAME * Format as Month DD, YYYY STRING MONTH-NAME DELIMITED BY SPACE " " DELIMITED BY SIZE DATE-DD DELIMITED BY SIZE ", " DELIMITED BY SIZE DATE-YYYY DELIMITED BY SIZE INTO LONG-FORMAT END-STRING DISPLAY "Raw date: " INPUT-DATE DISPLAY "Formatted date: " LONG-FORMAT

These examples demonstrate:

  • Extracting year, month, and day components from a compact YYYYMMDD date
  • Formatting dates in common display formats (MM/DD/YYYY)
  • Using month names for more readable date display
  • Using STRING operations to construct the formatted output
  • These techniques are essential for report generation and user interfaces

Best Practices for Date and Time Operations

  • Always validate dates from external sources before performing calculations
  • Use INTEGER-OF-DATE and DATE-OF-INTEGER for date arithmetic when available
  • Store dates in a consistent internal format (YYYYMMDD recommended)
  • Format dates appropriately for user display and reports
  • Consider creating a date utilities module for common operations
  • Document date formats in comments and field definitions
  • Add range validation for all date components (year, month, day)
  • Handle leap year calculation correctly when manipulating February dates
  • Use four-digit years for all new development
  • Be aware of time zone implications in global applications
  • Test with boundary dates (month ends, year ends, leap days)
  • Include error handling for all date operations

Test Your Knowledge

1. What is the correct way to obtain the current date in COBOL using the ACCEPT statement?

  • ACCEPT CURRENT-DATE
  • ACCEPT CURRENT-DATE FROM DATE
  • ACCEPT CURRENT-DATE FROM SYSTEM
  • ACCEPT CURRENT-DATE FROM SYSIN

2. Which COBOL intrinsic function converts a date in YYYYMMDD format to a day number (days since December 31, 1600)?

  • FUNCTION DAY-TO-INTEGER
  • FUNCTION INTEGER-OF-DATE
  • FUNCTION DATE-TO-DAYS
  • FUNCTION CONVERT-DATE-TO-INTEGER

3. What format does the ACCEPT identifier FROM DAY statement return in standard COBOL?

  • DD/MM/YY
  • MMDDYY
  • YYMMDD
  • YYDDD

4. What was the primary issue with date handling leading to the Year 2000 (Y2K) problem?

  • COBOL couldn't handle dates after 1999
  • Two-digit year representations made 2000 indistinguishable from 1900
  • The Julian date format couldn't represent years beyond 1999
  • The DATE intrinsic function was not Y2K compliant

5. Which technique can be used to calculate the number of days between two dates in COBOL?

  • Direct subtraction of date fields
  • Using the DAYS-BETWEEN function
  • Converting dates to integers with INTEGER-OF-DATE and then subtracting
  • Using the DATE-DIFFERENCE function

Frequently Asked Questions