HP3000-L Archives

October 2004, Week 3

HP3000-L@RAVEN.UTC.EDU

Options: Use Monospaced Font
Show Text Part by Default
Show All Mail Headers

Message: [<< First] [< Prev] [Next >] [Last >>]
Topic: [<< First] [< Prev] [Next >] [Last >>]
Author: [<< First] [< Prev] [Next >] [Last >>]

Print Reply
Subject:
From:
Brian Donaldson <[log in to unmask]>
Reply To:
Brian Donaldson <[log in to unmask]>
Date:
Mon, 18 Oct 2004 19:48:09 -0400
Content-Type:
text/plain
Parts/Attachments:
text/plain (108 lines)
I have been using CALENDAR and ALMANAC intrinsics in Cobol programs
for the longest time now and they work correctly. They return the
correct dates. So I'm not sure what your problem is.

I wrote a quickie program to satisfy my own curiosity and it is
indeed satisfied!

So here's the source for you to compile and try yourself:

 IDENTIFICATION DIVISION.
 PROGRAM-ID. TEST.
 ENVIRONMENT DIVISION.
 DATA DIVISION.
 WORKING-STORAGE SECTION.
 01  WS-DATE-ERROR-TABLE                COMP.
     05  WS-DATE-ERROR       PIC  9(04) COMP OCCURS 2.
 01  WS-DAY-NUM              PIC S9(04) COMP VALUE ZEROES.
 01  WS-WEEKDAY-NUM          PIC S9(04) COMP VALUE ZEROES.
 01  WS-YEAR-NUM             PIC S9(04) COMP VALUE ZEROES.
 01  WS-MONTH-NUM            PIC S9(04) COMP VALUE ZEROES.
 01  WS-START-DATE           PIC  9(04) COMP VALUE ZEROES.
 PROCEDURE DIVISION.
 A000-MAINLINE.

     CALL INTRINSIC "CALENDAR" GIVING WS-START-DATE.
     INITIALIZE WS-DATE-ERROR-TABLE,
                WS-YEAR-NUM,
                WS-MONTH-NUM,
                WS-DAY-NUM,
                WS-WEEKDAY-NUM.
     CALL INTRINSIC "ALMANAC" USING WS-START-DATE,
                                    WS-DATE-ERROR-TABLE,
                                    WS-YEAR-NUM,
                                    WS-MONTH-NUM,
                                    WS-DAY-NUM,
                                    WS-WEEKDAY-NUM
     END-CALL.
     IF WS-DATE-ERROR(1) NOT = ZEROES THEN
        DISPLAY 'DATE CONVERSION ERROR'
        STOP RUN
     END-IF.
     DISPLAY 'YEAR    IS=>' WS-YEAR-NUM    "<".
     DISPLAY 'MONTH   IS=>' WS-MONTH-NUM   "<".
     DISPLAY 'DAY     IS=>' WS-DAY-NUM     "<".
     DISPLAY 'WEEKDAY IS=>' WS-WEEKDAY-NUM "<".
     STOP RUN.

Here's the run time results:

:RUN TEST.NMPRG
YEAR    IS=>+0104<
MONTH   IS=>+0010<
DAY     IS=>+0018<
WEEKDAY IS=>+0002<

Add 1900 to the year and you get 2004. Fine.
The month is 10 (October). Fine.
The day is 18, which is today, October 18th. Fine.
The weekday is 2, so count Sunday as day one and so today Monday
is day 2.

This works fine.....

So what's the problem........??

Brian Donaldson.

On Mon, 18 Oct 2004 12:03:58 -0500, Peter Smithson
<[log in to unmask]> wrote:

> Hi,
>
>I must be doing something really stupid.
>
>
>The documentation for item 6 (file creation date) is that it uses the
>CALENDAR intrinsic format which says -
>
>Bits   Value/Meaning
>7:9   Day of year
>0:7   Year since 1900
>
>I get a bit confused with this notation.  Is that saying that the low 9
>bits are the year and the high 7 is the year?
>
>So today is year 104, day 292.  So the value I'd expect is
>
>292 + 104 * (2^9) which is 53540.
>
>Or if the year is 04 then it'd be 2340.
>
>When I run a test program on MPE I get 1996 which is day 460 year 03.
>
>I've tried out a few other combinations but I can't get it right.  What
>have I done wrong?  I get the same result from calling CALENDAR.
>
>Thanks.
>
>Peter
>--
>http://www.beluga.freeserve.co.uk
>
>* To join/leave the list, search archives, change list settings, *
>* etc., please visit http://raven.utc.edu/archives/hp3000-l.html *

* To join/leave the list, search archives, change list settings, *
* etc., please visit http://raven.utc.edu/archives/hp3000-l.html *

ATOM RSS1 RSS2