HP3000-L Archives

February 2006, Week 2

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:
Tracy Pierce <[log in to unmask]>
Reply To:
Tracy Pierce <[log in to unmask]>
Date:
Thu, 9 Feb 2006 08:50:13 -0800
Content-Type:
text/plain
Parts/Attachments:
text/plain (343 lines)
beating this into the ground, I should say the prior version _compiles_.

this version even 'works' at least for cursory tests: 
enter 1st of 2 dates, ccyymmdd format (all 0=exit):20060731
20060731
enter later of 2 dates, ccyymmdd format:20090901
20090901
difference is 0003 years, 01 months, 01 days.

$200/hr for that?  
- yet another Tracy

 IDENTIFICATION DIVISION.
 PROGRAM-ID. dtdf.
 REMARKS. Date-dif but using years months days as result.
     yes it's ambiguous, but not insurmountably - the result
     can be correct without being the only result possible,
     and correct is even fuzzy.
 ENVIRONMENT DIVISION.
 CONFIGURATION SECTION.
 SOURCE-COMPUTER. HP3000 WITH DEBUGGING MODE.
 SPECIAL-NAMES.
     SW9 IS PARM64, ON STATUS IS KTP-IS-TESTING;
     CONDITION-CODE IS CONDISHUN-CODE.
 DATA DIVISION.
 WORKING-STORAGE SECTION.
 01  jafemaapmajujuauseocnode value
    '312831303130313130313031'.
     05  days pic 99 occurs 12.
 01  date1.
     05  d1ccyy pic 9999.
     05  d1mm   pic 99.
     05  d1dd   pic 99.
 01  date2.
     05  d2ccyy pic 9999.
     05  d2mm   pic 99.
     05  d2dd   pic 99.
 01  diff.
     05  dify   pic 9999.
     05  difm   pic 99.
     05  difd   pic 99.

 PROCEDURE DIVISION.
 MAINL.
     move 'x' to date1
     perform until date1 = '00000000'
     display 'enter 1st of 2 dates, ccyymmdd format (all 0=exit):'
         no advancing accept date1 display date1
     if date1 = '00000000'
         goback
     end-if
     display 'enter later of 2 dates, ccyymmdd format:'
         no advancing accept date2 display date2
     if  date1 > date2
         display 'please enter dates in ascending sequence'
     else
         if  d1dd > d2dd
             subtract 1 from d2mm
             add days ( d2mm ) to d2dd
             if  ( d2mm > 2 )
             and ( d2ccyy / 4 * 4 = d2ccyy )
             and not ( d2ccyy / 100 * 100 = d2ccyy )
*               *d1 is a leap year (unless d2ccyy/400*400=d2ccyy)
*               *the leapyear tests aren't perfect, but the
*               *integer divisibility tests work great -
*               *the quotient is integer-resolved via truncation
*               *before the multiply happens, so division
*               *precision is irrelevant.
*               *but I'm not convinced the leapyear test is
*               *even necessary for this!
                 add 1 to d2dd
             end-if
         end-if
         compute difd = d2dd - d1dd
         if  d2mm < d1mm
             subtract 1 from d2ccyy
             add 12 to d2mm
         end-if
         compute difm = d2mm - d1mm
         compute dify = d2ccyy - d1ccyy
         display 'difference is ' dify ' years, '
                 difm ' months, ' difd ' days.'
     end-if
     end-perform
     GOBACK
     .

> -----Original Message-----
> From: Tracy Pierce 
> Sent: Thursday, February 09, 2006 7:52 AM
> To: 'Walter Murray'; [log in to unmask]
> Subject: RE: HP COBOL routine to calculate the difference 
> between 2 dates
> 
> Walter,
> 
> you would be correct to say it won't work.  fixing a few 
> things (hey, i didn't say it was tested;-)...
>  IDENTIFICATION DIVISION.
>  PROGRAM-ID. dtdf.
>  REMARKS. Date-dif but using years months days as result.
>      yes it's ambiguous, but not insurmountably - the result
>      can be correct without being the only result possible,
>      and correct is fuzzy anyway.
>  ENVIRONMENT DIVISION.
>  CONFIGURATION SECTION.
>  SOURCE-COMPUTER. HP3000 WITH DEBUGGING MODE.
>  SPECIAL-NAMES.
>      SW9 IS PARM64, ON STATUS IS KTP-IS-TESTING;
>      CONDITION-CODE IS CONDISHUN-CODE.
>  DATA DIVISION.
>  WORKING-STORAGE SECTION.
>  01  jafemaapmajujuauseocnode value
>     '312831303130313130313031'.
>      05  days pic 99 occurs 12.
>  01  date1.
>      05  d1ccyy pic 9999.
>      05  d1mm   pic 99.
>      05  d1dd   pic 99.
>  01  date2.
>      05  d2ccyy pic 9999.
>      05  d2mm   pic 99.
>      05  d2dd   pic 99.
>  01  diff.
>      05  dify   pic 9999.
>      05  difm   pic 99.
>      05  difd   pic 99.
> 
>  PROCEDURE DIVISION.
>  MAINL.
>      display 'enter 1st of 2 dates, ccyymmdd format (all 0=exit):'
>          no advancing accept date1
>      if date1 = '00000000'
>          goback
>      end-if
>      display 'enter later of 2 dates, ccyymmdd format:'
>          no advancing accept date2
>      if  date1 < date2
>          display 'please enter dates in ascending sequence'
>      else
>          if  d1dd < d2dd
>              subtract 1 from d1mm
>              add days ( d1mm ) to d1dd
>              if  ( d1mm > 2 )
>              and ( d1ccyy / 4 * 4 = d1ccyy )
>              and not ( d1ccyy / 100 * 100 = d1ccyy )	
> *               *d1 is a leap year (the 400 year test is 
> omitted sorry)
> *               *but the no-remainder integer divisibility 
> tests work great:
> *               *because the quotient is integer-resolved via 
> truncation
> *               *before the multiply happens, division 
> precision is irrelevant.
> *			*Dunno if leapyear test is even 
> relevant, but cobol doesn't do 'maybe'
>                  add 1 to d1dd
>              end-if
>          end-if
>          compute difd = d1dd - d2dd
>          if  d1mm < d2mm
>              subtract 1 from d1ccyy
>              add 12 to d1mm
>          end-if
>          compute difm = d1mm - d2mm
>          compute dify = d1ccyy - d2ccyy
>          display 'difference is ' dify ' years, '
>                  difm ' months, ' difd ' days.'
>      end-if
>      GOBACK
>      .
> works nicely ;-)
> 
> Tracy Pierce, GGBHTD
> 
>  
> 
> > -----Original Message-----
> > From: HP-3000 Systems Discussion 
> > [mailto:[log in to unmask]] On Behalf Of Walter Murray
> > Sent: Wednesday, February 08, 2006 10:29 PM
> > To: [log in to unmask]
> > Subject: Re: HP COBOL routine to calculate the difference 
> > between 2 dates
> > 
> > I don't want to say that it doesn't work, but some of this 
> code won't
> > compile with HP COBOL.
> > 
> > Also, I'd be leery of the check for leap year.  I don't see 
> where the
> > 100-year rule is being implemented, and it looks to me like 
> > the 400-year
> > check is backwards.
> > 
> > Also, be careful about using an arithmetic expression with 
> > division and
> > multiplication, to check for divisibility.  This might work with HP
> > COBOL, but some compilers use more significant digits for 
> intermediate
> > results in an arithmetic expression, so an expression like 
> (yyyy / 4 *
> > 4) would always evaluate to true.
> > 
> > Walter  
> > 
> > Walter J. Murray
> > 
> > 
> > -----Original Message-----
> > From: HP-3000 Systems Discussion [mailto:[log in to unmask]] On
> > Behalf Of Tracy Pierce
> > Sent: Wednesday, February 08, 2006 2:49 PM
> > To: [log in to unmask]
> > Subject: Re: [HP3000-L] HP COBOL routine to calculate the difference
> > between 2 dates
> > 
> > Eben, I already sent you my arduously bullet-proofed dtdif 
> > routine, but
> > it calcs exact days.  for the calc you requested, try
> > 
> > 01  jafemaapmajujuauseocnode value 
> >    '312831303130313130313031'.
> >     05  days occurs 12.
> > 01  date1.
> >     05  d1ccyy pic 9999.
> >     05  d1mm   pic 99.
> >     05  d1dd   pic 99.
> > 01  date2.
> >     05  d2ccyy pic 9999.
> >     05  d2mm   pic 99.
> >     05  d2dd   pic 99.
> > 01  diff.
> >     05  dify   pic 9999.
> >     05  difm   pic 99.
> >     05  difd   pic 99.
> > 
> > 
> > if date1 < date2
> >   display 'please enter dates in ascending sequence'
> > else
> >   if  d1dd < d2dd    
> >     subtract 1 from d1mm
> >     add days ( d1mm ) to d1dd
> >     if  ( d1mm > 2 or ( d1mm = 2 and d1dd > 28 ))
> >     and ( d1ccyy / 4 * 4 = d1ccyy )
> >     and not ( d1ccyy / 400 * 400 = d1ccyy )
> > *     *d1 is a leap year; this is not pseudo code, it works.
> >       add 1 to d1dd
> >     end-if
> >   end-if
> >   compute difd = d1dd - d2dd
> >   if  d1mm < d2mm
> >       subtract 1 from d1yy
> >       add 12 to d1mm
> >   endif
> >   compute difm = d1mm - d2mm
> >   compute dify = d1ccyy - d2ccyy
> >   display 'difference is ' dify ' years, ' difm ' months, ' difd '
> > days.'
> > end-if
> > .  
> > 
> > 
> > Tracy Pierce, GGBHTD
> > 
> >  
> > 
> > > -----Original Message-----
> > > From: Tracy Pierce 
> > > Sent: Wednesday, February 08, 2006 2:21 PM
> > > To: 'Eben Yong'
> > > Subject: RE: HP COBOL routine to calculate the difference 
> > > between 2 dates
> > > 
> > > see prior.  after reading the explanation, it occurs to me 
> > > that it could be a lot simpler to state:
> > > 
> > > 01  date1 pic s9(9) comp.
> > > 01  date2 pic s9(9) comp.
> > > 01  diff  pic s9(9) comp.
> > > 
> > > move 19530202 to date1
> > > move 20060208 to date2
> > > move zero     to diff
> > > call dtdif using date1 date2 diff
> > > *diff holds my age in days.
> > > 
> > > or
> > > 
> > > move 19530202 to date1
> > > move 0        to date2
> > > move 365      to diff
> > > *date2 holds the date 365 days after date1.
> > > 
> > > > -----Original Message-----
> > > > From: HP-3000 Systems Discussion 
> > > > [mailto:[log in to unmask]] On Behalf Of Eben Yong
> > > > Sent: Wednesday, February 08, 2006 1:44 PM
> > > > To: [log in to unmask]
> > > > Subject: HP COBOL routine to calculate the difference 
> > > between 2 dates
> > > > 
> > > > I'm slightly embarrassed to even post this question, as I 
> > > > feel I should be 
> > > > able to produce this code in a snap, but for some reason my 
> > > > brain must be 
> > > > somewhat tired today.  In any event, excuses aside, here is 
> > > > the question:
> > > > 
> > > > Would someone pls share their COBOL code that will 
> calculate the 
> > > > difference between two given dates, and return the results in 
> > > > terms of 
> > > > years, months, and days?
> > > > 
> > > > For example, the difference between 20060125 and 20040611 
> > > is 1 year 7 
> > > > months and 14 days.  
> > > > 
> > > > Care to share?  
> > > > Thanks as always,
> > > > Eben Yong
> > > > Health Plan of San Mateo
> > > > 
> > > > * 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 *
> > 
> > * 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