View previous topic :: View next topic |
Author |
Message |
kolusu Site Admin
Joined: 26 Nov 2002 Posts: 12375 Topics: 75 Location: San Jose
|
Posted: Wed May 19, 2004 10:52 am Post subject: Date Calculations In COBOL |
|
|
Since it is the first topic I am going to start off with a slightly easier questions .
The Task here is to perform the following date calculations in COBOL
Gregorian-Date-Format PIC 9(08 ) format 'CCYYMMDD'
[a.] Convert a gregorian-date to julian-date and vice-versa
[b.] Find if the year is a leap year
[c.] Add days to given gregorain date
[d.] Subtract days to given gregorain date
[e.] Difference between 2 dates
[f. ] Get the last day of the month
[g.] Difference between 2 timestamps in seconds
The following Rules apply for questions A thru F
1. You cannot use DB2
2. You need to use COBOL Intrinsic Functions ONLY
Question G can be solved in any manner.
I will post the answers to these questions on Monday 24th May.
Edited by the moderator: Added Gregorian-Date-Format PIC 9(08 ) format 'CCYYMMDD'
Kolusu _________________ Kolusu
www.linkedin.com/in/kolusu |
|
Back to top |
|
|
Cogito-Ergo-Sum Advanced
Joined: 15 Dec 2002 Posts: 637 Topics: 43 Location: Bengaluru, INDIA
|
Posted: Wed May 19, 2004 12:59 pm Post subject: |
|
|
I think, some LE callable services might help here. Can I use them? _________________ ALL opinions are welcome.
Debugging tip:
When you have eliminated all which is impossible, then whatever remains, however improbable, must be the truth.
-- Sherlock Holmes. |
|
Back to top |
|
|
kolusu Site Admin
Joined: 26 Nov 2002 Posts: 12375 Topics: 75 Location: San Jose
|
Posted: Wed May 19, 2004 1:05 pm Post subject: |
|
|
Cogito,
You cannot use LE callable services for questions A thru F.
Kolusu _________________ Kolusu
www.linkedin.com/in/kolusu |
|
Back to top |
|
|
kolusu Site Admin
Joined: 26 Nov 2002 Posts: 12375 Topics: 75 Location: San Jose
|
|
Back to top |
|
|
Bithead Advanced
Joined: 03 Jan 2003 Posts: 550 Topics: 23 Location: Michigan, USA
|
Posted: Thu May 20, 2004 12:33 pm Post subject: |
|
|
Here is my attempt, for what it is worth:
Code: |
[a.] Convert a gregorian-date to julian-date and vice-versa
05 ws-greg-date pic 9(08). (format is CCYYMMDD)
05 ws-juln-date pic 9(07). (format is CCYYDDD)
compute ws-juln-date =
function day-of-integer
(function integer-of-date (ws-greg-date)).
[b.] Find if the year is a leap year
05 ws-year pic 9(04). (format is CCYY)
05 ws-mod pic 9(04).
05 leap-year-sw pic x(01) value 'n'.
88 leap-year value 'y'.
* must be divisble by 4
compute ws-mod =
function mod(ws-year, 4).
* must not be divisble by 100 unless also divisble by 400
if ws-mod = 0
compute ws-mod =
function mod(ws-year, 100)
if ws-mod = 0
compute ws-mod =
function mod(ws-year, 400)
if ws-mod = 0
set leap-year to true
end-if
else
set leap-year to true
end-if
end-if.
[c.] Add days to given gregorain date
05 ws-date-1 pic 9(08).
05 ws-date-2 pic 9(08).
05 ws-days pic 9(03).
compute ws-date-2 =
function date-of-integer
(function integer-of-date (ws-date-1) + ws-days).
[d.] Subtract days to given gregorain date
05 ws-date-1 pic 9(08).
05 ws-date-2 pic 9(08).
05 ws-days pic 9(03).
compute ws-date-2 =
function date-of-integer
(function integer-of-date (ws-date-1) - ws-days).
[e.] Difference between 2 dates
05 ws-date-1 pic 9(08).
05 ws-date-2 pic 9(08).
05 ws-days pic s9(09) comp-3.
compute ws-days =
function integer-of-date (ws-date-1) -
function integer-of-date (ws-date-2).
[f. ] Get the last day of the month
05 ws-greg-date pic 9(08).
05 filler redefines ws-greg-date.
10 ws-greg-ccyy pic 9(04).
10 ws-greg-mm pic 9(02).
10 ws-greg-dd pic 9(02).
05 ws-last-date pic 9(08).
* set to first day of next month
move 1 to ws-greg-dd.
add 1 to ws-greg-mm.
if ws-greg-mm > 12
add 1 to ws-greg-ccyy
move 1 to ws-greg-mm
end-if.
compute ws-last-date =
function date-of-integer
(function integer-of-date (ws-greg-date) - 1).
[g.] Difference between 2 timestamps in seconds
05 ws-timestamp-1.
10 ws-ts1-ccyy pic 9(04).
10 filler pic x(01).
10 ws-ts1-mm pic 9(02).
10 filler pic x(01).
10 ws-ts1-dd pic 9(02).
10 filler pic x(01).
10 ws-ts1-hr pic 9(02).
10 filler pic x(01).
10 ws-ts1-min pic 9(02).
10 filler pic x(01).
10 ws-ts1-sec pic 9(02).
10 filler pic x(01).
10 ws-ts1-rest pic x(06).
05 ws-timestamp-2.
10 ws-ts2-ccyy pic 9(04).
10 filler pic x(01).
10 ws-ts2-mm pic 9(02).
10 filler pic x(01).
10 ws-ts2-dd pic 9(02).
10 filler pic x(01).
10 ws-ts2-hr pic 9(02).
10 filler pic x(01).
10 ws-ts2-min pic 9(02).
10 filler pic x(01).
10 ws-ts2-sec pic 9(02).
10 filler pic x(01).
10 ws-ts2-rest pic x(06).
05 ws-greg-date-1 pic 9(08).
05 filler redefines ws-greg-date-1.
10 ws-greg1-ccyy pic x(04).
10 ws-greg1-mm pic x(02).
10 ws-greg1-dd pic x(02).
05 ws-greg-date-2 pic 9(08).
05 filler redefines ws-greg-date-2.
10 ws-greg2-ccyy pic x(04).
10 ws-greg2-mm pic x(02).
10 ws-greg2-dd pic x(02).
05 ws-seconds pic s9(17) comp-3.
move ws-ts1-ccyy to ws-greg1-ccyy.
move ws-ts1-mm to ws-greg1-mm.
move ws-ts1-dd to ws-greg1-dd.
move ws-ts2-ccyy to ws-greg2-ccyy.
move ws-ts2-mm to ws-greg2-mm.
move ws-ts2-dd to ws-greg2-dd.
compute ws-seconds =
* convert date 1 to seconds
((function integer-of-date (ws-greg-date-1)
* 24 * 60 * 60)
* add hours (converted to seconds)
+ (ws-ts1-hr * 60 * 60)
* add minutes (converted to seconds)
+ (ws-ts1-min * 60)
* add seconds
+ ws-ts1-sec)
-
* convert date 2 to seconds
((function integer-of-date (ws-greg-date-2)
* 24 * 60 * 60)
* add hours (converted to seconds)
+ (ws-ts2-hr * 60 * 60)
* add minutes (converted to seconds)
+ (ws-ts2-min * 60)
* add seconds
+ ws-ts2-sec)
.
|
|
|
Back to top |
|
|
kolusu Site Admin
Joined: 26 Nov 2002 Posts: 12375 Topics: 75 Location: San Jose
|
Posted: Thu May 20, 2004 1:03 pm Post subject: |
|
|
MY rating for bithead's post:
All points are on a scale of 1 to 10. This is purely my personal rating and the rating is based on answers to the requirement. The reasons for the low rating will be revealed at the end of the contest.
Code: |
A. 5 points
B. 9 points
C. 10 points
D. 10 points
E. 10 points
F. 10 points
G. 7 points
Total : 61
|
_________________ Kolusu
www.linkedin.com/in/kolusu |
|
Back to top |
|
|
Brian Beginner
Joined: 12 Aug 2003 Posts: 95 Topics: 6
|
Posted: Fri May 21, 2004 3:58 am Post subject: |
|
|
This is my solution..(for greg-jul/leap/jul-greg)..
hope to post the solution for the others soon...
am not using any intrinsic function...just plain cobol features and logic..
Code: |
*
IDENTIFICATION DIVISION.
PROGRAM-ID. GREG2JUL.
*
ENVIRONMENT DIVISION.
DATA DIVISION.
WORKING-STORAGE SECTION.
01 FILLER.
03 WS-TODAY-DATE PIC X(06).
03 WS-TODAY-DATE-R REDEFINES WS-TODAY-DATE.
05 WS-YY PIC 99.
05 WS-MM PIC 99.
05 WS-DD PIC 99.
03 WS-GREG-DATE PIC 9(08).
03 WS-GREG-DATE-R REDEFINES WS-GREG-DATE.
05 WS-GREG-CCYY PIC 9999.
05 WS-GREG-MM PIC 99.
05 WS-GREG-DD PIC 99.
03 WS-REMAINDERS.
05 WS-QUOT PIC 9(01).
05 WS-4-REM PIC S9(01) COMP.
88 DIVISIBLE-BY-4 VALUE +0.
05 WS-100-REM PIC S9(02) COMP.
88 DIVISIBLE-BY-100 VALUE +0.
05 WS-400-REM PIC S9(03) COMP.
88 DIVISIBLE-BY-400 VALUE +0.
*
01 FILLER.
03 MONTH-DAYS PIC X(24) VALUE
'312831303130313130313031'.
03 FILLER REDEFINES MONTH-DAYS.
05 MONTH-DAYS-R PIC X(02) OCCURS 12.
*
01 FILLER.
03 JULIAN-DATE PIC 9(07) VALUE ZERO.
03 FILLER REDEFINES JULIAN-DATE.
05 J-YEAR PIC 9(04).
05 J-DAYS PIC 9(03).
*
77 LEAP-OR-NOT PIC X.
88 IS-LEAP VALUE 'Y'.
88 IS-NOT-LEAP VALUE 'N'.
*
77 JUL-CTR PIC S9(02) COMP VALUE +0.
77 M-CTR-1 PIC 9(02) VALUE ZERO.
77 JULIAN-MONTHS PIC 9(02) VALUE ZERO.
77 JULIAN-ACTUAL-DAYS PIC 9(02) VALUE ZERO.
77 JUL-DAYS PIC 9(03) VALUE ZERO.
*
LINKAGE SECTION.
01 L-PARMS.
03 FILLER PIC S9(4) COMP.
03 LGDATE PIC 9(8).
03 LJDATE PIC 9(7).
*
PROCEDURE DIVISION USING L-PARMS.
ACCEPT WS-TODAY-DATE FROM DATE.
MOVE LGDATE TO WS-GREG-DATE.
PERFORM CHECK-LEAP.
PERFORM VARYING JUL-CTR FROM 1 BY 1 UNTIL JUL-CTR
EQUAL WS-GREG-MM
MOVE MONTH-DAYS-R (JUL-CTR) TO M-CTR-1
IF JUL-CTR EQUAL 2
IF IS-LEAP
ADD 29 TO JUL-DAYS
ELSE
ADD M-CTR-1 TO JUL-DAYS
END-IF
ELSE
ADD M-CTR-1 TO JUL-DAYS
END-IF
END-PERFORM
ADD WS-GREG-DD TO JUL-DAYS.
DISPLAY 'JULIAN DATE = ' WS-GREG-CCYY'.'JUL-DAYS.
MOVE LJDATE TO JULIAN-DATE.
MOVE J-YEAR TO WS-GREG-CCYY.
PERFORM CHECK-LEAP.
PERFORM SPLIT-JDAYS THRU SPLIT-EXIT.
DISPLAY 'DATE = ' J-YEAR'/'JULIAN-MONTHS'/'JULIAN-ACTUAL-DAYS
STOP RUN.
*
CHECK-LEAP.
SET IS-NOT-LEAP TO TRUE
DIVIDE WS-GREG-CCYY BY +4 GIVING WS-QUOT
REMAINDER WS-4-REM
DIVIDE WS-GREG-CCYY BY +100 GIVING WS-QUOT
REMAINDER WS-100-REM
DIVIDE WS-GREG-CCYY BY +400 GIVING WS-QUOT
REMAINDER WS-400-REM
IF DIVISIBLE-BY-400 OR
(DIVISIBLE-BY-4 AND NOT DIVISIBLE-BY-100)
SET IS-LEAP TO TRUE.
*
SPLIT-JDAYS.
PERFORM VARYING JUL-CTR FROM 1 BY 1 UNTIL JUL-CTR GREATER 12
MOVE MONTH-DAYS-R (JUL-CTR) TO M-CTR-1
IF J-DAYS GREATER M-CTR-1
ADD 1 TO JULIAN-MONTHS
IF JUL-CTR EQUAL 2
IF IS-LEAP
SUBTRACT 29 FROM J-DAYS
ELSE
SUBTRACT M-CTR-1 FROM J-DAYS
END-IF
ELSE
SUBTRACT M-CTR-1 FROM J-DAYS
END-IF
ELSE
MOVE J-DAYS TO JULIAN-ACTUAL-DAYS
ADD 1 TO JULIAN-MONTHS
GO TO SPLIT-EXIT
END-IF
END-PERFORM.
*
SPLIT-EXIT.
EXIT.
*
|
You will get the dates through parm and process it.
This code is fairly untested..but i guess it should work fine.
Cheers
Brian |
|
Back to top |
|
|
kolusu Site Admin
Joined: 26 Nov 2002 Posts: 12375 Topics: 75 Location: San Jose
|
Posted: Fri May 21, 2004 5:04 am Post subject: |
|
|
Brain,
Please read the rules. you need to use intrinsic functions of cobol for questions A thru F
Kolusu _________________ Kolusu
www.linkedin.com/in/kolusu |
|
Back to top |
|
|
Brian Beginner
Joined: 12 Aug 2003 Posts: 95 Topics: 6
|
Posted: Fri May 21, 2004 5:34 am Post subject: |
|
|
Kolusu,
I just thought otherwise. Wanted to simulate the intrinsic functions. Plz feel free to delete my post.
Cheers
Brian |
|
Back to top |
|
|
kolusu Site Admin
Joined: 26 Nov 2002 Posts: 12375 Topics: 75 Location: San Jose
|
Posted: Mon May 24, 2004 7:33 am Post subject: |
|
|
The following is the explanation of my rating for bithead's reply
A: 5 points(He missed the vice-versa part i.e he forgot the conversion of julian date to gregorian date )
B. Just nit picking as there 3 levels of Nested If's
C thru F full points as they are perfect.
G is an excellent solution except but that does not take into consideration the microseconds portion. There will +1 sec or -1 sec error using this method.
Kolusu _________________ Kolusu
www.linkedin.com/in/kolusu |
|
Back to top |
|
|
kolusu Site Admin
Joined: 26 Nov 2002 Posts: 12375 Topics: 75 Location: San Jose
|
Posted: Mon May 24, 2004 7:35 am Post subject: |
|
|
Here are the answers for the questions. Please feel free to rate the solutions.
a. Convert a gregorian-date to julian-date and vice-versa
Code: |
01 WS-GREGORIAN-DATE PIC 9(08).
01 WS-JULIAN-DATE PIC 9(07).
COMPUTE WS-JULIAN-DATE = FUNCTION DAY-OF-INTEGER
(FUNCTION INTEGER-OF-DATE
(WS-GREGORIAN-DATE))
COMPUTE WS-GREGORIAN-DATE = FUNCTION DATE-OF-INTEGER
(FUNCTION INTEGER-OF-DAY
(WS-JULIAN-DATE))
|
b. Find if the year is a leap year
Code: |
01 WS-YEAR PIC 9(04).
EVALUATE TRUE
WHEN FUNCTION MOD (WS-YEAR 4) NOT ZERO
WHEN FUNCTION MOD (WS-YEAR 100) ZERO
AND FUNCTION MOD (WS-YEAR 400) NOT ZERO
DISPLAY 'IT IS NOT A LEAP YEAR ' WS-YEAR
WHEN OTHER
DISPLAY 'IT IS A LEAP YEAR ' WS-YEAR
END-EVALUATE
|
c. Add days to given gregorain date
Code: |
01 WS-ADVANCE-DATE PIC 9(08).
01 WS-ADD-DAYS PIC 9(08).
01 WS-GREGORIAN-DATE PIC 9(08).
COMPUTE WS-ADVANCE-DATE = FUNCTION DATE-OF-INTEGER
(FUNCTION INTEGER-OF-DATE(WS-GREGORIAN-DATE) + WS-ADD-DAYS)
|
d. Subtract days to given gregorain date
Code: |
01 WS-GREGORIAN-DATE PIC 9(08).
01 WS-SUB-DAYS PIC 9(08).
01 WS-RETARD-DATE PIC 9(08).
COMPUTE WS-RETARD-DATE = FUNCTION DATE-OF-INTEGER
(FUNCTION INTEGER-OF-DATE(WS-GREGORIAN-DATE) - WS-SUB-DAYS)
|
e. Difference between 2 dates
Code: |
01 WS-DATE-DIFF PIC S9(08) COMP.
01 WS-DATE1 PIC 9(08).
01 WS-DATE2 PIC 9(08).
COMPUTE WS-DATE-DIFF = FUNCTION INTEGER-OF-DATE(WS-DATE2) -
FUNCTION INTEGER-OF-DATE(WS-DATE1)
|
f. Get the last day of the month .
The only difference for the last day of month will occur only on a leap year. So all we will do is to check the year is a leap year or not.
Code: |
01 WS-MONTH-END-DD PIC X(24) VALUE
'312831303130313130313031'.
01 WS-TBL-MONTH-END REDEFINES WS-MONTH-END-DD.
05 TBL-MONTH-END-DAY PIC 9(02) OCCURS 12 TIMES.
01 WS-GREG-DATE.
05 WS-GREG-YEAR PIC 9(04).
05 WS-GREG-MNTH PIC 9(02).
05 WS-GREG-DAY PIC 9(02).
EVALUATE TRUE
WHEN FUNCTION MOD (WS-GREG-YEAR 4) NOT ZERO
WHEN FUNCTION MOD (WS-GREG-YEAR 100) ZERO
AND FUNCTION MOD (WS-GREG-YEAR 400) NOT ZERO
MOVE '28' TO WS-TBL-MONTH-END (3: 2)
WHEN OTHER
MOVE '29' TO WS-TBL-MONTH-END (3: 2)
END-EVALUATE
MOVE TBL-MONTH-END-DAY(WS-GREG-MNTH)
TO WS-GREG-DAY
DISPLAY 'LAST-DATE OF MONTH:' WS-GREG-DATE
|
g. Difference between 2 timestamps in seconds
We use the language environment callable service CEESECS which will convert timestamp to seconds. The difference between 2 timestamps is an example in the manual for ceesecs.
Language Environment Programming Reference Manual
Code: |
01 WS-SECOND1 COMP-2.
01 WS-SECOND2 COMP-2.
01 WS-TIMESTAMP-1 PIC X(26).
01 WS-TIMESTAMP-2 PIC X(26).
01 WS-FORMAT PIC X(26).
01 WS-DIFFERENCE PIC +9(09).
01 WS-FC-CODE.
05 FC-SEVERITY PIC S9(4) COMP.
05 FC-MESSAGE PIC S9(4) COMP.
05 FILLER PIC X(08).
MOVE '2004-03-23-15.35.39.838149' TO WS-TIMESTAMP-1
MOVE '2004-05-17-13.07.18.234567' TO WS-TIMESTAMP-2
MOVE 'YYYY-MM-DD-HH.MI.SS.999999' TO WS-FORMAT
CALL 'CEESECS' USING WS-TIMESTAMP-1,
WS-FORMAT,
WS-SECOND1,
WS-FC-CODE
IF FC-SEVERITY = +0
CONTINUE
ELSE
DISPLAY 'CEESECS ROUTINE ERROR'
PERFORM INHOUSE-ABEND-ROUTINE
END-IF
CALL 'CEESECS' USING WS-TIMESTAMP-2,
WS-FORMAT,
WS-SECOND2,
WS-FC-CODE
IF FC-SEVERITY = +0
CONTINUE
ELSE
DISPLAY 'CEESECS ROUTINE ERROR'
PERFORM INHOUSE-ABEND-ROUTINE
END-IF
COMPUTE WS-DIFFERENCE = WS-SECOND2 - WS-SECOND1
DISPLAY 'THE DIFFERENCE BETWEEN 2 TIMESTAMPS IS:'
WS-DIFFERENCE
|
Thanks,
Kolusu _________________ Kolusu
www.linkedin.com/in/kolusu |
|
Back to top |
|
|
Dibakar Advanced
Joined: 02 Dec 2002 Posts: 700 Topics: 63 Location: USA
|
Posted: Sun Sep 28, 2008 7:49 pm Post subject: |
|
|
Quote: |
* If 2004 is the year you want to find whether julian or not.
|
Ravikumar, I think you wrote julian instead of leap year at lot pf places. Anyway, nice solution. |
|
Back to top |
|
|
infoman123 Beginner
Joined: 02 Nov 2004 Posts: 57 Topics: 20
|
Posted: Wed Jun 09, 2010 4:54 am Post subject: |
|
|
Hi Kolusu,
Is the intrinsic function in cobol is efficient than finding the same with normal cobol statements.
Regards |
|
Back to top |
|
|
kolusu Site Admin
Joined: 26 Nov 2002 Posts: 12375 Topics: 75 Location: San Jose
|
Posted: Wed Jun 09, 2010 10:27 am Post subject: |
|
|
infoman123 wrote: | Hi Kolusu,
Is the intrinsic function in cobol is efficient than finding the same with normal cobol statements.
Regards |
What exactly are Normal COBOL statements? Intrinsic functions are a part of cobol and ya there is an overhead calling the routines but it is negligible , as you don't even notice the difference. The only problem with these intrinsic functions is that you need to have a VALID input date.
I prefer intrinsic functions rather than a programmer trying to calculate the result. _________________ Kolusu
www.linkedin.com/in/kolusu |
|
Back to top |
|
|
|
|