To that end, I'd like to calculate the julian day. It's described on the
wiki: http://en.wikipedia.org/wiki/Julian_day
This is what I have so far:
implicit none
real :: a, y, m, jdn, jd
integer :: day, month, year
INTEGER date_time(8)
CHARACTER(LEN=10) big_ben(3)
CALL DATE_AND_TIME(big_ben(1), big_ben(2), big_ben(3), date_time)
PRINT *,'date_time array values:'
PRINT *,'year=',date_time(1)
PRINT *,'month_of_year=',date_time(2)
PRINT *,'day_of_month=',date_time(3)
PRINT *,'time difference in minutes=',date_time(4)
PRINT *,'hour of day=',date_time(5)
PRINT *,'minutes of hour=',date_time(6)
PRINT *,'seconds of minute=',date_time(7)
PRINT *,'milliseconds of second=',date_time(8)
PRINT *, 'DATE=',big_ben(1)
PRINT *, 'TIME=',big_ben(2)
PRINT *, 'ZONE=',big_ben(3)
day = date_time(3)
month = date_time(2)
year = date_time(1)
a = (14.0 - 1.0*month)/12.0
y = year + 4800 - a
m = month + (12* a) - 3
jdn = day + (((153* m) + 2) / 5.0) + (365 * y) + &
& (y / 4.0) - 32083
print *, "jdn is ", jdn
endprogram
! g95 jul1.f95 -o t.exe
C:\MinGW\source>t
date_time array values:
year= 2009
month_of_year= 1
day_of_month= 30
time difference in minutes= -420
hour of day= 21
minutes of hour= 25
seconds of minute= 55
milliseconds of second= 546
DATE=20090130
TIME=212555.546
ZONE=-0700
jdn is 2454875.5
C:\MinGW\source>
The correct number is 2454862, so this needs some work. I have a couple
questions:
q1) Has anyone done this before in fortran?
q2) A calculation like this intermixes reals and integers. a is likely a
non-integer rational. I don't know how promotions go in fortran. Is this
the best way to write it:
a = (14.0 - 1.0*month)/12.0
q3) I would think that there are 24 valid julian times at any moment, given
which 15° slice one inhabits. Where is the greatest one?
Thanks for your comment.
--
larry gates
The way I see it, if you declare something portable, you'll always be
wrong, and if you declare it non-portable, you'll always be right. :-)
-- Larry Wall in <1998062322...@wall.org>
> q1) Has anyone done this before in fortran?
I think there is an example in NUMERICAL RECIPES.
Have a look at datesub.f90 on Alan Miller's website
http://users.bigpond.net.au/amiller/
or H.D.Knoble's website
http://ftp.cac.psu.edu/pub/ger/fortran/hdk/00-index.txt
--
Clive Page
this is taken from our book.
http://www.fortranplus.co.uk/fortran_books.html
and the code is at
http://www.fortranplus.co.uk/resources/ch2611.f90
cheers
ian
n 31 Jan, 11:22, Clive Page <j...@main.machine> wrote:
> In message <7k9jszq77xag$.1l621jvo29piz....@40tude.net>, Larry Gates
Thanks for your response, phil. I would be reliant on UNM's library for
that, and they only have one of the two, so it's a bit of a crapshoot as
well as it being closed on saturday night.
Last time I went down, I asked at the desk of the CS dept how I might find
Brian T. Smith, professor emeritus and co-author of my current for fortran
reading: _The Fortran 2003 Handbook_. He doesn't keep any office hours,
but they gave me his home phone number!
I do want to call him, invite him to a coffeehouse, and ask him about the
fortran he's seen and written about. I'm gonna wait till I finish the
book, though, so I wouldn't ask something stupid.
--
larry gates
People who understand context would be steamed to have someone else
dictating how they can call it.
-- Larry Wall in <1997102217...@wall.org>
>
> q3) I would think that there are 24 valid julian times at any moment, given
> which 15° slice one inhabits. Where is the greatest one?
Wrong for at least 2 reasons. 1. Some places are never an exact number
of hours ahead of Greenwich, e.g. South Australia. 2. New Zealand,
which is exactly 12h ahead for half the year, is 13h ahead when we are
on summer time. (Then there's the Chatham islands, 45 min ahead of the
rest of NZ)
John Harper
Thanks, Clive, I'd never seen Skip's site before. What you have to do is
select the file you want and cut_and_paste it into the end of url so as to
ace the index after /hdk/.
http://ftp.cac.psu.edu/pub/ger/fortran/hdk/00-index.txt
(I'd never thought of a folder name in an url as a regex before.)
Anyways, I think you can tell that I'm cleaning my house while I get this
typed up. I do a lot better with typing on this 2 month 24 day since Miss
Nguyen ran me over in her car because she wasn't looking in the direction
she was accelerating her vehicle. She tells the cop I ran into her and
somehow hasn't directed her insurance to pick up my medical bills. I've
been thinking an awful lot about that insurance adjuster's face needing an
adjustment by a two by three by four, maybe even five.
C:\MinGW\source> g95 skip1.f -o y.exe
C:\DOCUME~1\dan\LOCALS~1\Temp/ccGeaMPU.o:skip1.f:(.text+0x20): undefined
referen
ce to `getdat_'
C:\MinGW\source>
So getdat needs a year, a month and a day. I post source after the sig
that I think relevant.
Furthermore, Chicago has something for B-rod's ukainian friends.
--
larry gates
If you want to program in C, program in C. It's a nice language. I
use it occasionally... :-)
-- Larry Wall in <75...@jpl-devvax.JPL.NASA.GOV>
C This file: http://ftp.aset.psu.edu/pub/ger/fortran/hdk/datesub.for
C
C======DATESUB.FOR with Sample Drivers.
C COLLECTED AND PUT TOGETHER JANUARY 1972, H. D. KNOBLE .
C ORIGINAL REFERENCES ARE CITED IN EACH ROUTINE.
C
INTEGER YYYY,MM,DD,JD,WD,DDD,MMA,DDA,NDIFF,I
INTEGER*2 YYYY2,MM2,DD2
C
C====IDAY IS A COMPANION TO CALEND; GIVEN A CALENDAR DATE, YYYY, MM,
C DD, IDAY IS RETURNED AS THE DAY OF THE YEAR.
C EXAMPLE: IDAY(1984,4,22)=113
IDAY(YYYY,MM,DD)=3055*(MM+2)/100-(MM+10)/13*2-91
, +(1-(MOD(YYYY,4)+3)/4+(MOD(YYYY,100)+99)/100
, -(MOD(YYYY,400)+399)/400)*(MM+10)/13+DD
C
C====IZLR(YYYY,MM,DD) GIVES THE WEEKDAY NUMBER 0=SUNDAY, 1=MONDAY,
C ... 6=SATURDAY. EXAMPLE: IZLR(1970,1,1)=4=THURSDAY
IZLR(YYYY,MM,DD)=MOD((13*(MM+10-(MM+10)/13*12)-1)/5+DD+77
, +5*(YYYY+(MM-14)/12-(YYYY+(MM-14)/12)/100*100)/4
, + (YYYY+(MM-14)/12)/400-(YYYY+(MM-14)/12)/100*2,7)
C
C Compute date this year for changing clocks back to EST.
C See program: estdst.f90
C
C Is this a leap year? I.e. is 12/31/yyyy the 366th day of the year?
CALL GETDAT(YYYY2,MM2,DD2)
C---GETDAT is builtin using some Compilers.
YYYY=YYYY2
IF(IDAY(YYYY,12,31).EQ.366) THEN
WRITE(*,*) YYYY,' is a Leap Year'
ELSE
WRITE(*,*) YYYY,' is not a Leap Year'
ENDIF
C
C DAYSUB SHOULD RETURN: 1970, 1, 1, 4, 1
CALL DAYSUB(JD(1970,1,1),YYYY,MM,DD,WD,DDD)
IF(YYYY.NE.1970.OR.MM.NE.1.OR.DD.NE.1.OR.WD.NE.4.OR.DDD.NE.1)
* THEN
WRITE(*,*)'DAYSUB Failed; YYYY,MM,DD,WD,DDD=',YYYY,MM,DD,WD,DDD
STOP 1
ENDIF
C DIFFERENCE BETWEEN TWO SAME MONTHS AND DAYS OVER 1 LEAP YEAR IS 366.
NDIFF=NDAYS(5,22,1984,5,22,1983)
IF(NDIFF.NE.366) THEN
WRITE(*,*) 'NDAYS FAILED; NDIFF=',NDIFF
ELSE
C RECOVER MONTH AND DAY FROM YEAR AND DAY NUMBER.
CALL CALEND(YYYY,DDD,MMA,DDA)
IF(MMA.NE.1.AND.DDA.NE.1) THEN
WRITE(*,*) 'CALEND FAILED; MMA,DDA=',MMA,DDA
ELSE
WRITE(*,*) '** DATE MANIPULATION SUBROUTINES SIMPLE TEST OK.'
END IF
END IF
STOP
END
SUBROUTINE CALEND(YYYY,DDD,MM,DD)
C=====CALEND WHEN GIVEN A VALID YEAR, YYYY, AND DAY OF THE
C YEAR, DDD, RETURNS THE MONTH, MM, AND DAY OF THE
C MONTH, DD.
C SEE ACM ALGORITHM 398, TABLELESS DATE CONVERSION, BY
C DICK STONE, CACM 13(10):621.
INTEGER YYYY,DDD,MM,DD,T
T=0
IF(MOD(YYYY,4).EQ.0) T=1
C-------THE FOLLOWING STATEMENT IS NECESSARY IF YYYY IS LESS TNAN
C 1900 OR GREATER THAN 2100.
IF(MOD(YYYY,400).NE.0.AND.MOD(YYYY,100).EQ.0) T=0
DD=DDD
IF(DDD.GT.59+T) DD=DD+2-T
MM=((DD+91)*100)/3055
DD=(DD+91)-(MM*3055)/100
MM=MM-2
C-------MM WILL BE CORRECT IFF DDD IS CORRECT FOR YYYY.
IF(MM.GE.1 .AND. MM.LE.12) RETURN
WRITE(*,1) DDD
1 FORMAT('0$$$CALEND: DAY OF THE YEAR INPUT =',I11,
, ' IS OUT OF RANGE.')
STOP 8
END
SUBROUTINE CDATE(JD,YYYY,MM,DD)
C=====GIVEN A JULIAN DAY NUMBER, NNNNNNNN, YYYY,MM,DD ARE RETURNED AS
C AS THE CALENDAR DATE. JD=NNNNNNNN IS THE JULIAN DATE
C FROM AN EPOCK IN THE VERY DISTANT PAST. SEE CACM
C 1968 11(10):657, LETTER TO THE EDITOR BY FLIEGEL AND
C VAN FLANDERN.
C EXAMPLE CALL CDATE(2440588,YYYY,MM,DD) RETURNS 1970 1 1 .
C
INTEGER JD,YYYY,MM,DD,L,N
L=JD+68569
N=4*L/146097
L=L-(146097*N + 3)/4
YYYY=4000*(L+1)/1461001
L=L-1461*YYYY/4+31
MM=80*L/2447
DD=L-2447*MM/80
L=MM/11
MM=MM + 2 - 12*L
YYYY=100*(N-49) + YYYY + L
RETURN
END
SUBROUTINE DAYSUB(JD,YYYY,MM,DD,WD,DDD)
C=====GIVEN JD, A JULIAN DAY # (SEE ASF JD), THIS ROUTINE
C CALCULATES DD, THE DAY NUMBER OF THE MONTH; MM, THE MONTH
C NUMBER; YYYY THE YEAR; WD THE WEEKDAY NUMBER, AND DDD
C THE DAY NUMBER OF THE YEAR.
C ARITHMETIC STATEMENT FUNCTIONS 'IZLR' AND 'IDAY' ARE TAKEN
C FROM REMARK ON ALGORITHM 398, BY J. DOUGLAS ROBERTSON,
C CACM 15(10):918.
C
C EXAMPLE: CALL DAYSUB(2440588,YYYY,MM,DD,WD,DDD) YIELDS 1970 1 1 4 1.
C
INTEGER JD,YYYY,MM,DD,WD,DDD
C
C====IZLR(YYYY,MM,DD) GIVES THE WEEKDAY NUMBER 0=SUNDAY, 1=MONDAY,
C ... 6=SATURDAY. EXAMPLE: IZLR(1970,1,1)=4=THURSDAY
C
IZLR(YYYY,MM,DD)=MOD((13*(MM+10-(MM+10)/13*12)-1)/5+DD+77
, +5*(YYYY+(MM-14)/12-(YYYY+(MM-14)/12)/100*100)/4
, + (YYYY+(MM-14)/12)/400-(YYYY+(MM-14)/12)/100*2,7)
C
C====IDAY IS A COMPANION TO CALEND; GIVEN A CALENDAR DATE, YYYY, MM,
C DD, IDAY IS RETURNED AS THE DAY OF THE YEAR.
C EXAMPLE: IDAY(1984,4,22)=113
C
IDAY(YYYY,MM,DD)=3055*(MM+2)/100-(MM+10)/13*2-91
, +(1-(MOD(YYYY,4)+3)/4+(MOD(YYYY,100)+99)/100
, -(MOD(YYYY,400)+399)/400)*(MM+10)/13+DD
C
CALL CDATE(JD,YYYY,MM,DD)
WD=IZLR(YYYY,MM,DD)
DDD=IDAY(YYYY,MM,DD)
RETURN
END
FUNCTION JD(YYYY,MM,DD)
INTEGER YYYY,MM,DD
C DATE ROUTINE JD(YYYY,MM,DD) CONVERTS CALENDER DATE TO
C JULIAN DATE. SEE CACM 1968 11(10):657, LETTER TO THE
C EDITOR BY HENRY F. FLIEGEL AND THOMAS C. VAN FLANDERN.
C EXAMPLE JD(1970,1,1)=2440588
JD=DD-32075+1461*(YYYY+4800+(MM-14)/12)/4
, +367*(MM-2-((MM-14)/12)*12)/12-3*
, ((YYYY+4900+(MM-14)/12)/100)/4
RETURN
END
FUNCTION NDAYS(MM1,DD1,YYYY1, MM2,DD2,YYYY2)
INTEGER YYYY1,MM1,DD1,YYYY2,MM2,DD2
C=====NDAYS IS RETURNED AS THE NUMBER OF DAYS BETWEEN TWO
C DATES; THAT IS MM1/DD1/YYYY1 MINUS MM2/DD2/YYYY2,
C WHERE DATEI AND DATEJ HAVE ELEMENTS MM, DD, YYYY.
C-------NDAYS WILL BE POSITIVE IFF DATE1 IS MORE RECENT THAN DATE2.
NDAYS=JD(YYYY1,MM1,DD1)-JD(YYYY2,MM2,DD2)
RETURN
END
c g95 skip1.f -o y.exe
But jtime in hawaii is either less than or greater than you.
This notion speaks to "order."
--
larry gates
It'd be really nice to find a way to explain continuations to people
without inflicting the typical torturous explanations on people who
aren't interested in brain pretzels.
-- Larry Wall
He won't get sniffy - he's a good guy. Send my regards if you do.
Regards,
Nick Maclaren.
In a discussion on this list named "Date representation", starting 11
september 2008,
I showed an example of my F90 implementation of date-time
representation and conversion.
After some digestion by Arjen Markus, you can download the Module from
http://flibs.sf.net. With copy/paste from that discussion here is the
example:
USE libdate
TYPE(DateType) :: t,t_stop
t = DateType(1994,1, 1, 0,0) ! 1 january 1994
t_stop = DateType(2008,9,11,12,0) ! noon today
DO WHILE (t.LT.t_stop)
......
WRITE(*,*) DOY(t) ! Integer number Day Of Year
......
t = t + DateType(0,0,0,1,0) ! timestep of 1 hour
ENDDO
Another function from LibDate is function Date2Julian(t).
Try and see! The code is there and free!
Regards,
Arjan
> you may also be interested in a modern version of this.
> we turned it into a date class.
>
> this is taken from our book.
>
> http://www.fortranplus.co.uk/fortran_books.html
>
> and the code is at
>
> http://www.fortranplus.co.uk/resources/ch2611.f90
>
> cheers
>
> ian
Looks great, Ian, I'll put your book in queue to buy. I much prefer free
form. I can't shake the feeling that f77 code is YELLING AT ME.
C:\MinGW\source>g95 skip2.f90 -o u.exe
C:\MinGW\source>u
date_stamp = Sunday, 1 February 2009
date_stamp = 1 February 2009
date_stamp = Sunday, 1 Feb 2009
date_stamp = 1 Feb 2009
turn clocks ahead to dst on:
5 april 2009
2009 is not a leap year
** date manipulation subroutines
** simple test ok.
C:\MinGW\source>
That's a sexy little program there. It takes me a bit to figure out how to
call things, but it's all there for me to tap into. Source listing after
sig.
--
larry gates
It's, uh, pseudo code. Yeah, that's the ticket...
[...]
And "unicode" is pseudo code for $encoding. :-)
-- Larry Wall in <1998080717...@wall.org>
MODULE date_module
! Collected and put together january 1972,
! h. d. knoble.
! Original references are cited in each routine.
! Code converted using to_f90 by alan miller
! Date: 1999-12-22 time: 10:23:47
! Compatible with imagine1 f compiler: 2002-07-19
! At this time the functions and
! subroutines were as described below
! FUNCTION iday(yyyy, mm, dd) RESULT(ival)
! FUNCTION izlr(yyyy, mm, dd) RESULT(ival)
! SUBROUTINE calend(yyyy, ddd, mm, dd)
! SUBROUTINE cdate(jd, yyyy, mm, dd)
! SUBROUTINE daysub(jd, yyyy, mm, dd, wd, ddd)
! FUNCTION jd(yyyy, mm, dd) RESULT(ival)
! FUNCTION ndays(mm1, dd1, yyyy1,
! mm2, dd2, yyyy2) RESULT(ival)
! SUBROUTINE date_stamp( string, want_day, short )
! Code converted by ian chivers and jane sleightholme
! November 2004 - May 2005
! The changes are to go from
! working with integer variables
! for year, day and month to
! user defined date variables.
! .. Implicit None Statement ..
IMPLICIT NONE
! ..
! .. Default Accessibility ..
PRIVATE
! ..
! .. Derived Type Declarations ..
TYPE, PUBLIC :: date
PRIVATE
INTEGER :: day
INTEGER :: month
INTEGER :: year
END TYPE date
! ..
! .. Public Statements ..
PUBLIC :: calendar_to_julian,&
date_, &
date_stamp, &
date_to_day_in_year, &
date_to_weekday_number, &
get_day, &
get_month, &
get_year, &
julian_to_date, &
julian_to_date_and_week_and_day, &
ndays, &
year_and_day_to_date
! ..
! The above are the contained
! functions and subroutines
! in this module.
! Here is a short description of each one
! date_to_day_in_year - function
! returns the day in the year
! original arguments of day,month,year
! now date
! dayinyear
! date_to_weekday_number - function
! returns the week day number
! original argument d,m,y
! now date
! weekdaynum
! year_and_day_to_date - subroutine
! returns the day and month from
! year and day in year
! julian_to_date - subroutine
! returns a year_and_day_to_datear date from
! a julian date
! ndays - function
! returns the number of days between
! two dates
! julian_to_date_and_week_and_day - subroutine
! given a julian day this routine
! calculates year, month day and
! week day number and day number
! calendar_to_julian - function
! returns julian date from
! year_and_day_to_datear date
CONTAINS
! arithmetic functions "izlr" and "iday"
! are taken from remark on
! algorithm 398, by j. douglas robertson,
! cacm 15(10):918.
FUNCTION date_to_day_in_year(x)
! Convert from date to day in year
! .. Implicit None Statement ..
IMPLICIT NONE
! ..
! .. Function Return Value ..
INTEGER :: date_to_day_in_year
! ..
! .. Structure Arguments ..
TYPE (date), INTENT (IN) :: x
! ..
! .. Intrinsic Functions ..
INTRINSIC modulo
! ..
date_to_day_in_year = 3055*(x%month+2)/100 &
- (x%month+10)/13*2 - 91 + &
(1-(modulo(x%year,4)+3)/4 &
+ (modulo(x%year,100)+99)/100 &
- (modulo(x%year, &
400)+399)/400)*(x%month+10)/13 + x%day
END FUNCTION date_to_day_in_year
FUNCTION date_to_weekday_number(x)
! .. Implicit None Statement ..
IMPLICIT NONE
! ..
! .. Function Return Value ..
INTEGER :: date_to_weekday_number
! ..
! .. Structure Arguments ..
TYPE (date), INTENT (IN) :: x
! ..
! .. Intrinsic Functions ..
INTRINSIC modulo
! ..
date_to_weekday_number = &
modulo((13*(x%month+10 &
-(x%month+10)/13*12)-1)/5+x &
%day+77+5*(x%year+(x%month-14)/12 &
-(x%year+(x%month-14)/12)/100*100)/4 &
+(x%year+(x%month-14)/12)/400 &
-(x%year+(x%month-14)/12)/100*2,7)
END FUNCTION date_to_weekday_number
FUNCTION year_and_day_to_date(year,day) RESULT (x)
! .. Implicit None Statement ..
IMPLICIT NONE
! ..
! .. Function Return Value ..
TYPE (date) :: x
! ..
! .. Scalar Arguments ..
INTEGER, INTENT (IN) :: day, year
! ..
! .. Local Scalars ..
INTEGER :: t
! ..
! .. Intrinsic Functions ..
INTRINSIC modulo
! ..
x%year = year
t = 0
IF (modulo(year,4)==0) THEN
t = 1
END IF
!------the following statement is
! necessary IF year is < 1900 or > 2100.
IF (modulo(year,400)/=0 &
.AND. modulo(year,100)==0) THEN
t = 0
END IF
x%day = day
IF (day>59+t) THEN
x%day = x%day + 2 - t
END IF
x%month = ((x%day+91)*100)/3055
x%day = (x%day+91) - (x%month*3055)/100
x%month = x%month - 2
IF (x%month>=1 .AND. x%month<=12) THEN
RETURN
END IF
! x%month will be correct
! iff day is correct for year.
WRITE (unit=*,fmt='(a,i11,a)') &
'$$year_and_day_to_date: day of the year input =', &
day, ' is out of range.'
END FUNCTION year_and_day_to_date
FUNCTION julian_to_date(julian) RESULT (x)
! Given a julian day number the date is returned.
! julian is the julian date from an epocch
! in the very distant past. see cacm 1968 11(10):657,
! letter to the editor by fliegel and van flandern.
! .. Implicit None Statement ..
IMPLICIT NONE
! ..
! .. Scalar Arguments ..
INTEGER, INTENT (IN) :: julian
! ..
! .. Local Scalars ..
INTEGER :: l, n
! ..
! .. Function Return Value ..
TYPE (date) :: x
! ..
l = julian + 68569
n = 4*l/146097
l = l - (146097*n+3)/4
x%year = 4000*(l+1)/1461001
l = l - 1461*x%year/4 + 31
x%month = 80*l/2447
x%day = l - 2447*x%month/80
l = x%month/11
x%month = x%month + 2 - 12*l
x%year = 100*(n-49) + x%year + l
END FUNCTION julian_to_date
SUBROUTINE &
julian_to_date_and_week_and_day(jd,x,wd,ddd)
! given jd, a julian day # (see asf jd),
! this routine calculates dd,
! the day number of the month;
! mm, the month number; yyyy the year;
! wd the weekday number, and
! ddd the day number of the year.
! example:
! CALL julian_to_date_and_week_and_day
! (2440588, yyyy, mm, dd, wd, ddd)
! yields 1970 1 1 4 1.
! .. Implicit None Statement ..
IMPLICIT NONE
! ..
! .. Scalar Arguments ..
INTEGER, INTENT (OUT) :: ddd, wd
INTEGER, INTENT (IN) :: jd
! ..
! .. Structure Arguments ..
TYPE (date), INTENT (OUT) :: x
! ..
x = julian_to_date(jd)
wd = date_to_weekday_number(x)
ddd = date_to_day_in_year(x)
END SUBROUTINE julian_to_date_and_week_and_day
FUNCTION calendar_to_julian(x) RESULT (ival)
! .. Implicit None Statement ..
IMPLICIT NONE
! ..
! .. Function Return Value ..
INTEGER :: ival
! ..
! .. Structure Arguments ..
TYPE (date), INTENT (IN) :: x
! ..
! date routine calendar_to_julian converts date to
! julian date. see cacm 1968 11(10):657,
! letter to the
! editor by henry f. fliegel and
! thomas c. van flandern.
! example calendar_to_julian(1970, 1, 1) = 2440588
ival = x%day - 32075 &
+ 1461*(x%year+4800+(x%month-14)/12)/4 + &
367*(x%month-2-((x%month-14)/12)*12)/12 &
- 3*((x%year+4900+(x%month-14)/ &
12)/100)/4
END FUNCTION calendar_to_julian
FUNCTION ndays(date1,date2)
! .. Implicit None Statement ..
IMPLICIT NONE
! ..
! .. Function Return Value ..
INTEGER :: ndays
! ..
! .. Structure Arguments ..
TYPE (date), INTENT (IN) :: date1, date2
! ..
! dates; that is mm1/dd1/yyyy1 minus
! mm2/dd2/yyyy2,
! where datei and datej have elements mm, dd, yyyy.
! ndays will be positive iff
! date1 is more recent than date2.
ndays = calendar_to_julian(date1) &
- calendar_to_julian(date2)
END FUNCTION ndays
SUBROUTINE date_stamp(string,want_day,short)
! Returns the current date as a character string
! e.g.
! want_day short string
! .TRUE. .TRUE. Thursday, 23 Dec 1999
! .TRUE. .FALSE. Thursday, 23 December 1999
! <- defaul/
! .FALSE. .TRUE. 23 Dec 1999
! .FALSE. .FALSE. 23 December 1999
! .. Implicit None Statement ..
IMPLICIT NONE
! ..
! .. Scalar Arguments ..
LOGICAL, OPTIONAL, INTENT (IN) :: short, want_day
CHARACTER (*), INTENT (OUT) :: string
! ..
! .. Local Scalars ..
INTEGER :: pos
LOGICAL :: sh, want_d
! ..
! .. Local Arrays ..
INTEGER :: val(8)
CHARACTER (9) :: day(0:6) = (/ 'Sunday ' &
, 'Monday ' &
, 'Tuesday ' &
, 'Wednesday' &
, 'Thursday ' &
, 'Friday ' &
, 'Saturday '/)
CHARACTER (9) :: month(1:12) = &
(/ 'January ' &
, 'February ' &
, 'March ' &
, 'April ' &
, 'May ' &
, 'June ' &
, 'July ' &
, 'August ' &
, 'September' &
, 'October ' &
, 'November ' &
, 'December '/)
! ..
! .. Intrinsic Functions ..
INTRINSIC date_and_time, len_trim, present, trim
! ..
! .. Local Structures ..
TYPE (date) :: x
! ..
want_d = .TRUE.
IF (present(want_day)) want_d = want_day
sh = .FALSE.
IF (present(short)) sh = short
CALL date_and_time(values=val)
x = date_(val(3),val(2),val(1))
IF (want_d) THEN
pos = date_to_weekday_number(x)
string = trim(day(pos)) // ','
pos = len_trim(string) + 2
ELSE
pos = 1
string = ' '
END IF
WRITE (string(pos:pos+1),'(i2)') val(3)
IF (sh) THEN
string(pos+3:pos+5) = month(val(2)) (1:3)
pos = pos + 7
ELSE
string(pos+3:) = month(val(2))
pos = len_trim(string) + 2
END IF
WRITE (string(pos:pos+3),'(i4)') val(1)
RETURN
END SUBROUTINE date_stamp
FUNCTION date_(dd,mm,yyyy) RESULT (x)
! .. Implicit None Statement ..
IMPLICIT NONE
! ..
! .. Function Return Value ..
TYPE (date) :: x
! ..
! .. Scalar Arguments ..
INTEGER, INTENT (IN) :: dd, mm, yyyy
! ..
x = date(dd,mm,yyyy)
END FUNCTION date_
FUNCTION get_year(x)
! .. Implicit None Statement ..
IMPLICIT NONE
! ..
! .. Function Return Value ..
INTEGER :: get_year
! ..
! .. Structure Arguments ..
TYPE (date), INTENT (IN) :: x
! ..
get_year = x%year
END FUNCTION get_year
FUNCTION get_month(x)
! .. Implicit None Statement ..
IMPLICIT NONE
! ..
! .. Function Return Value ..
INTEGER :: get_month
! ..
! .. Structure Arguments ..
TYPE (date), INTENT (IN) :: x
! ..
get_month = x%month
END FUNCTION get_month
FUNCTION get_day(x)
! .. Implicit None Statement ..
IMPLICIT NONE
! ..
! .. Function Return Value ..
INTEGER :: get_day
! ..
! .. Structure Arguments ..
TYPE (date), INTENT (IN) :: x
! ..
get_day = x%day
END FUNCTION get_day
END MODULE date_module
PROGRAM ch2611
! .. Use Statements ..
USE date_module, ONLY : calendar_to_julian, &
date, date_, &
date_stamp, &
date_to_day_in_year, &
date_to_weekday_number, &
get_day, &
get_month, &
get_year, &
julian_to_date_and_week_and_day, &
ndays, &
year_and_day_to_date
! ..
! .. Implicit None Statement ..
IMPLICIT NONE
! ..
! .. Local Scalars ..
INTEGER :: dd, ddd, i, mm, ndiff, wd, yyyy
CHARACTER (50) :: message
! ..
! .. Local Arrays ..
INTEGER :: val(8)
! ..
! .. Intrinsic Functions ..
! compute date this year for changing clocks
! back to est.
! i.e.compute date for the last
! sunday in october for this year.
INTRINSIC date_and_time
! ..
! .. Local Structures ..
TYPE (date) :: date1, date2, x
! ..
! Test date_stamp
message = ' date_stamp = '
CALL date_stamp(message(15:))
WRITE (*,'(a)') message
message = ' date_stamp = '
CALL date_stamp(message(15:),want_day=.FALSE.)
WRITE (*,'(a)') message
message = ' date_stamp = '
CALL date_stamp(message(15:),short=.TRUE.)
WRITE (*,'(a)') message
message = ' date_stamp = '
CALL date_stamp &
(message(15:),want_day=.FALSE.,short=.TRUE.)
WRITE (*,'(a)') message
CALL date_and_time(values=val)
yyyy = val(1)
mm = 10
DO i = 31, 26, -1
x = date_(i,mm,yyyy)
IF (date_to_weekday_number(x)==0) THEN
PRINT *, 'turn clocks back to est on: '
print *, i, ' october ', get_year(x)
EXIT
END IF
END DO
! compute date this year for
! turning clocks ahead to dst
! i.e., compute date for the first
! sunday in april for this year.
CALL date_and_time(values=val)
yyyy = val(1)
mm = 4
DO i = 1, 8
x = date_(i,mm,yyyy)
IF (date_to_weekday_number(x)==0) THEN
PRINT *, 'turn clocks ahead to dst on: '
print *, i, ' april ', get_year(x)
EXIT
END IF
END DO
CALL date_and_time(values=val)
yyyy = val(1)
mm = 12
dd = 31
x = date_(dd,mm,yyyy)
! is this a leap year? i.e., is
! 12/31/yyyy the 366th day of the year?
IF (date_to_day_in_year(x)==366) THEN
PRINT *, get_year(x), ' is a leap year'
ELSE
PRINT *, get_year(x), ' is not a leap year'
END IF
x = date_(1,1,1970)
CALL julian_to_date_and_week_and_day &
(calendar_to_julian(x),x,wd,ddd)
IF (get_year(x)/=1970 .OR. &
get_month(x)/=1 .OR. &
get_day(x)/=1 .OR. &
wd/=4 .OR. ddd/=1) THEN
PRINT *, 'julian_to_date_and_week_and_day failed'
print *,' date, wd, ddd = ', &
get_year(x), get_month(x), get_day(x), wd, ddd
STOP
END IF
! difference between to same
! months and days over 1 leap year is 366.
date1 = date_(22,5,1984)
date2 = date_(22,5,1983)
ndiff = ndays(date1,date2)
yyyy = 1970
x = year_and_day_to_date(yyyy,ddd)
IF (ndiff/=366) THEN
PRINT *, 'ndays failed; ndiff = ', ndiff
ELSE
! recover month and day
! from year and day number.
IF (get_month(x)/=1 .AND. get_day(x)/=1) THEN
PRINT *, 'year_and_day_to_date failed'
print *,' mma, dda = ', get_month(x), &
get_day(x)
ELSE
PRINT *, '** date manipulation subroutines'
print *, '** simple test ok.'
END IF
END IF
END PROGRAM ch2611
! g95 skip2.f90 -o u.exe
Maybe I'll call him sooner. In social situations, I'm painfully shy for no
apparent reason.
--
larry gates
There are still some other things to do, so don't think if I didn't fix
your favorite bug that your bug report is in the bit bucket. (It may be,
but don't think it. :-) Larry Wall in <72...@jpl-devvax.JPL.NASA.GOV>
Arjan,
I didn't see a date manipulation prog at that site.
You speak of Arjen in the third person. I always thought that you were
Arjen, maybe a little jazzed up on Jaegermeister and a spliffy.
It's a football holy day here in the states. I'm taking the cardinals and
the points. Peace.
--
larry gates
"Help save the world!" -- Larry Wall in README
On http://flibs.sourceforge.net/ Arjen provides you with a whole bunch
of categories.
Check out "Computational facilities" and the last contribution in this
category is "libdate".
> You speak of Arjen in the third person. I always thought that you were Arjen,
Nope! Our names are similar (but not identical!). In the Netherlands
you can
find Arjan, Arjen, Arijan, Arijjan, Arie-Jan, Arien, Arian, Adriaan
and many more.
Sorry for the confusion, but Arjan <> Arjen!
> maybe a little jazzed up on Jaegermeister and a spliffy.
Cheers!
Arjan
If you haven't seen it already, you might want to dig out a copy of
http://emr.cs.iit.edu/home/reingold/calendar-book/index.shtml
from your local library. I have the 1st edition and it's an excellent
source of algorithms for the topic.
Regards
Mark Westwood
On Feb 2, 9:58 am, Arjan <arjan.van.d...@rivm.nl> wrote:
> > I didn't see a date manipulation prog at that site.
>
> Onhttp://flibs.sourceforge.net/Arjen provides you with a whole bunch
Arjan <arjan.v...@rivm.nl> wrote:
> Nope! Our names are similar (but not identical!). In the Netherlands
> you can
> find Arjan, Arjen, Arijan, Arijjan, Arie-Jan, Arien, Arian, Adriaan
> and many more.
> Sorry for the confusion, but Arjan <> Arjen!
I find it ironicaly amusing for "Larry" to be confused by similarity of
names, when he in turn does such a good job of confusing me by
dissimilarity of names.
I suppose I could be wrong in assuming that "Larry Gates" is the same
person as "George" and multiple other pseudonyms previously used to post
here. I don't have a list, but I'm sure I recall other names with much
the same writing style.
Not that there is anything concretely wrong with using such multiple
pseudonyms. It just tends to confuse me. Admitedly, quite a few things
about his writing tend to confuse me. In fact, after each pseudonym
change, that's what slowly starts to clue me in that maybe this is the
same person because I'm having the same kinds of difficulties in
understanding the posts.
Just yesterday, I was imagining my response if, say, Brian Smith or Andy
Vaught were to call me up and ask if I knew this person X who just
contacted them mentioning comp.lang.fortran. I'd have to reply that I
had never heard of X, but that it might be Larry/George/whoever. Not
sure why that imagined scenario ran through my mind, but it did.
--
Richard Maine | Good judgment comes from experience;
email: last name at domain . net | experience comes from bad judgment.
domain: summertriangle | -- Mark Twain
>
> I find it ironicaly amusing for "Larry" to be confused by similarity of
> names, when he in turn does such a good job of confusing me by
> dissimilarity of names.
>
> I suppose I could be wrong in assuming that "Larry Gates" is the same
> person as "George" and multiple other pseudonyms previously used to post
> here. I don't have a list, but I'm sure I recall other names with much
> the same writing style.
>
I've sort of made a hobby out of tracking his pseudonyms. I believe he
has been George, Ron Ford, Richard Nixon, Gerry Ford, and Wade Ward.
Of course, I have been user1, John Smith, John Doe, and accidentally
posted using my real name once or twice :-)
juldate=367*year-7*(year+(month+9)/12)/4-3*((year+(month-9)/7)/100+1)/
4+275*month/9+day-730516
All the variables are integers; computations use Fortran Integer
arithmetic. I'm not sure that the final date is correct (it may give
the wrong year.) I don't think it's valid for more than 4000 years.
> you may also be interested in a modern version of this.
> we turned it into a date class.
C:\MinGW\source>g95 skip3.f90 -o u.exe
C:\MinGW\source>u
date_stamp = Monday, 2 February 2009
date_stamp = 2 February 2009
date_stamp = Monday, 2 Feb 2009
date_stamp = 2 Feb 2009
turn clocks ahead to dst on:
5 april 2009
2009 is not a leap year
** date manipulation subroutines
idate is 2440588
** simple test ok.
C:\MinGW\source>
Seems a little shy to me.
idate = calendar_to_julian(x)
print *, "idate is ", idate
--
larry gates
That should probably be written:
no !@#$%^&*:@!semicolon
-- Larry Wall in <1997101618...@wall.org>
http://i429.photobucket.com/albums/qq15/george196884/adsfgsdf.jpg
What's in a name, in particular on usenet. I used to use pseudonyms of my
cowboy friends, like Wade Ward or Lane Straatman. Now I like to match my
name up with my random sig.
I'm more identifiable as "the tall guy."
--
larry gates
"We all agree on the necessity of compromise. We just can't agree on
when it's necessary to compromise."
-- Larry Wall in <1991Nov13.1...@netlabs.com>
> I'm more identifiable as "the tall guy."
Tall? I am 1.97 m!
Arjen, what's your length?
Let's settle this! Once and for all!
Arjan ;-))))))
Heh, looks like my bike did after a lady ran me over with her car a
number of years ago. Still have the remnants of a scar on my forehead
as a souvenir from that encounter.
> I'm more identifiable as "the tall guy."
I'm pretty tall as well, but it seems Arjan has already beat me.
--
JB
I'm a walking international standard: exactly 2 meters. My foot is also
exactly a foot long.
--
larry gates
Must be a different Larry Wall. There are at least 137 of us in the U.S.
-- Larry Wall in <1998093000...@wall.org>
> Larry
>
> If you haven't seen it already, you might want to dig out a copy of
>
> http://emr.cs.iit.edu/home/reingold/calendar-book/index.shtml
>
> from your local library. I have the 1st edition and it's an excellent
> source of algorithms for the topic.
>
> Regards
>
> Mark Westwood
The essays looked particularly intriguing, but they come as .ps files. I
don't have the feintest idea how to open it up if wordpard and adobe won't
pull it off.
It looks like paring down Skip's date_time stuff is the path of least
resistance:
MODULE date_module
IMPLICIT NONE
TYPE, PUBLIC :: date
PRIVATE
INTEGER :: day
INTEGER :: month
INTEGER :: year
END TYPE date
PUBLIC :: calendar_to_julian
CONTAINS
FUNCTION calendar_to_julian(x) RESULT (ival)
IMPLICIT NONE
! .. Function Return Value ..
INTEGER :: ival
! ..
! .. Structure Arguments ..
TYPE (date), INTENT (IN) :: x
! ..
! date routine calendar_to_julian converts date to
! julian date. see cacm 1968 11(10):657,
! letter to the
! editor by henry f. fliegel and
! thomas c. van flandern.
! example calendar_to_julian(1970, 1, 1) = 2440588
ival = x%day - 32075 &
+ 1461*(x%year+4800+(x%month-14)/12)/4 + &
367*(x%month-2-((x%month-14)/12)*12)/12 &
- 3*((x%year+4900+(x%month-14)/ &
12)/100)/4
END FUNCTION calendar_to_julian
END MODULE date_module
PROGRAM ch2612
USE date_module, ONLY : calendar_to_julian
IMPLICIT NONE
INTEGER :: val(8)
TYPE (date) :: date1, date2, x
CALL date_and_time(values=val)
x%day = date_time(3)
x%month = date_time(2)
x%year = date_time(1)
print *, "day is ", x
! x = date_(1,1,1970)
! CALL julian_to_date_and_week_and_day &
! (calendar_to_julian(x),x,wd,ddd)
END PROGRAM ch2612
! g95 skip4.f90 -o p.exe
C:\MinGW\source>g95 skip4.f90 -o p.exe
In file skip4.f90:67
TYPE (date) :: date1, date2, x
1
Error: Derived type 'date' at (1) is being used before it is defined
C:\MinGW\source>
This error has me mystified.
--
larry gates
Every day it gets a little harder to distinguish my senility from
my insanity...
-- Larry Wall in <20050507200...@wall.org>
Well, the message is perhaps slightly misleading in that it implies date
is defined somewhere later. In fact, date is never defined anywhere in
the main program, either before or after its use. Date is defined in the
module date_module. But note the ONLY clause on your USE statement. You
told it to only access calendar_to_julian, so that's all it accessed.
No, an ONLY like that does not also imply "and also anything related or
even needed to make constructive use of calendar_to_julian." It really
does mean what you asked for and only that.
> Larry Gates <la...@example.invalid> wrote:
> ...
>> PROGRAM ch2612
>>
>> USE date_module, ONLY : calendar_to_julian
>> IMPLICIT NONE
>> INTEGER :: val(8)
>> TYPE (date) :: date1, date2, x
> ...
>> TYPE (date) :: date1, date2, x
>> 1
>> Error: Derived type 'date' at (1) is being used before it is defined
>> ...
>> This error has me mystified.
>
> Well, the message is perhaps slightly misleading in that it implies date
> is defined somewhere later. In fact, date is never defined anywhere in
> the main program, either before or after its use. Date is defined in the
> module date_module. But note the ONLY clause on your USE statement. You
> told it to only access calendar_to_julian, so that's all it accessed.
I thought of that and went back to skip's original, which is a much more
comprenhsive thing. What's nice is that Ian had a version in free form.
What's depressing is that I didn't see 'date' in this:
USE date_module, ONLY : calendar_to_julian, &
date, date_, &
date_stamp, &
date_to_day_in_year, &
date_to_weekday_number, &
get_day, &
get_month, &
get_year, &
julian_to_date_and_week_and_day, &
ndays, &
year_and_day_to_date
Blind as a bat.
>
> No, an ONLY like that does not also imply "and also anything related or
> even needed to make constructive use of calendar_to_julian." It really
> does mean what you asked for and only that.
C:\MinGW\source>g95 skip5.f90 -o p.exe
C:\MinGW\source>p
day is 3 2 2009
jdate is 2454866
C:\MinGW\source>
Thanks, Richard, that's the right answer.
--
larry gates
Well, that's more-or-less what I was saying, though obviously addition
is a little more cosmic than the bitwise operators.
-- Larry Wall in <1997090518...@wall.org>
> On 2009-02-03, Larry Gates <la...@example.invalid> wrote:
>> http://i429.photobucket.com/albums/qq15/george196884/adsfgsdf.jpg
>
> Heh, looks like my bike did after a lady ran me over with her car a
> number of years ago. Still have the remnants of a scar on my forehead
> as a souvenir from that encounter.
She tells the cop that I ran into her, but if you look at that front wheel,
it shows how she overtook me and ran my bike and me over.
This looks good now:
C:\MinGW\source>type jul2.f95
MODULE date_module
IMPLICIT NONE
TYPE, PUBLIC :: date
INTEGER :: day
INTEGER :: month
INTEGER :: year
END TYPE date
PUBLIC :: calendar_to_julian
CONTAINS
FUNCTION calendar_to_julian(x) RESULT (ival)
IMPLICIT NONE
INTEGER :: ival
TYPE (date), INTENT (IN) :: x
ival = x%day - 32075 &
+ 1461*(x%year+4800+(x%month-14)/12)/4 + &
367*(x%month-2-((x%month-14)/12)*12)/12 &
- 3*((x%year+4900+(x%month-14)/ &
12)/100)/4
END FUNCTION calendar_to_julian
END MODULE date_module
PROGRAM ch2612
USE date_module, ONLY : calendar_to_julian, date
IMPLICIT NONE
INTEGER :: val(8), jdate, h, m,s
double precision :: jtime
TYPE (date) :: x
CALL date_and_time(values=val)
x%day = val(3)
x%month = val(2)
x%year = val(1)
print *, "day is ", x
jdate = calendar_to_julian(x)
print *, "jdate is ", jdate
h = val(5)
m = val(6)
s = val(7)
print *, "h m s are ", h,m,s
jtime = jdate*1.0 + ((h-12)/24.0)+ m/1440.0 + s/86400.0
print *, "julian time is ", jtime
endprogram
! g95 jul2.f95 -Wall -o t.exe
C:\MinGW\source>g95 jul2.f95 -Wall -o t.exe
C:\MinGW\source>t
day is 3 2 2009
jdate is 2454866
h m s are 22 19 57
julian time is 2454866.4305208335
C:\MinGW\source>
Did you take in account that the julian calendar has a year zero but the
Gregorian calendar has not.
I use an astronomical program celestia on my PC that inserts a year zero in
the Gregorian calendar.
Hence the morningstar roze in the year -2 instead of 3 BC according to this
program.
It could give a problem with the leapyears too.
Menno van Barneveld.
"Larry Gates" <la...@example.invalid> schreef in bericht
news:1qjzf4hrznfox.1byy0q8y6vkye$.dlg@40tude.net...
> Larry,
>
> Did you take in account that the julian calendar has a year zero but the
> Gregorian calendar has not.
> I use an astronomical program celestia on my PC that inserts a year zero in
> the Gregorian calendar.
> Hence the morningstar roze in the year -2 instead of 3 BC according to this
> program.
>
> It could give a problem with the leapyears too.
>
> Menno van Barneveld.
Do I guess correctly that the romans didn't really know how to represent
zero?
The morning star would have been contrary to the journey of wise men.
First of all, we assume they didn't come from less than 26 degrees in
latitude. Their camels would have done poorly.
I'd be just the type who would get on a camel and try to follow a major
planet when I expected a minor planet as a morningstar, and indeed, that
would take a person west in that region.
Is there a single "right" julian time on the fractional part?
2454868.64747
--
larry gates
To Perl, or not to Perl, that is the kvetching.
-- Larry Wall in <1998012003...@wall.org>
That depends on whether you want it to be in the astronomical convention
(noon is .0) or the non-astronomical convention (midnigh is .0). Apart
from that little detail - what are twelve hours among friends after two
and a half million days? - everything is clear...
Jan
>
> Do I guess correctly that the romans didn't really know how to represent
> zero?
The Romans did have the word nullus for it, but it was not concidered to be
a natural number.
It stayed this way for centuries. The use of 0 as a number comes from India.
But the the first day of a month is called day one and in the same way the
first year is counted as year one.
Point zero is the start of that year. Counting backwards it is the same,
year -1,-2 and so on.
The month's and the days are not reversed. Point zero is also the end of
December the 31st of -1.
So year zero does not exist.
The first symbol zero is known from the Maya's in the first century BC. It
looks like a rugby ball.
At August the 12th -3 a conjunction was seen of the planets Venus and
Jupiter, coming above the horizon in the East at about a quarter past three
A.M. Jerusalem time.
Venus stands for Mary and Jupiter stands for Joseph.
Let's suppose the Persian Magics had to travel about 1000 km on their
camels. They did not arive the same time at the stable. I can imagen that.
There is a right julian time on the fractional part. It is timed from 12:00
h A.M. U.T. ( Greenwich time).
So of .64747 is
hourReal = 12 + .64747 * 24 ! minus your time zone when you use local
time
day = aint(hourReal/24)
hourInt = aint(hourReal) - day * 24
minute = aint((hourReal-hourInt) * 60)
second = ((hourReal-hourInt) * 60-minute)*60
Correct for your time zone, to make your astronomical data all with positive
time stamps.
Menno.
>
> The morning star would have been contrary to the journey of wise men.
> First of all, we assume they didn't come from less than 26 degrees in
> latitude. Their camels would have done poorly.
>
> I'd be just the type who would get on a camel and try to follow a major
> planet when I expected a minor planet as a morningstar, and indeed, that
> would take a person west in that region.
>
> Is there a single "right" julian time on the fractional part?
>
> 2454868.64747
> --
> larry gates
>
The astronomical aspect of the journey of the Magi was recently
discussed in one mailing list I follow:
http://groups.google.com/group/NavList/browse_thread/thread/72fb037a3e1a30df?hl=en#
Julian dates -- the SOFA (IAU Standards of Fundamental Astronomy) site
has Fortran 77 code to convert Gregorian calendar dates to Julian
dates and vice versa.
http://www.iau-sofa.rl.ac.uk/2009_0201_F/Calendars.html
However, their algorithm is good only as far back as year -4800 or so.
Last year I got an email from someone using my Windows astronomy DLL,
saying it was messing up in the extreme past. This person was testing
a new precession model over a wide time span. I pressed for more
detail, but never got a response, so I'm not sure where the error was
occurring. It may have been in my Julian date code, which used the
SOFA routine.
I later re-wrote the DLL as a set of .NET Framework assemblies in
order to make it language independent. In the process I wrote my own
time routines from scratch to escape the limitations of the SOFA code.
They convert between calendar date (Gregorian or Julian) and Julian
date. Their range exceeds 5,000,000 BC to 5,000,000 AD, and time
resolution is better than 1 nanosecond throughout (possible because
the JD is split into two double precision components: date and time of
day). Integer overflow imposes the date limits; the algorithms
themselves have unlimited range. The code is C#, but since the
calendar portion is just integer arithmetic, it should be
understandable to any programmer. If you wish I'll send it to you.
Eventually all the source will be on my site, but I haven't got around
to it yet.
In an earlier message I noticed you using MinGW. That's what I used to
compile the Fortran 77 code to build my Win32 astronomy DLL. It
includes the complete SOFA libraries. All I did was concatenate the
individual .for files (there must be 100+) into one monolithic file,
then feed that to MinGW. My recollection is that it went perfectly:
the only change to the source code was one simple bug fix, and on my
old 850 MHz machine the compile was fast with no signs of strain.
http://home.earthlink.net/~s543t-24dst/sofajpl/index.html
(The bug was fixed after I sent the SOFA people an email.)
--
Paul Hirose <jvcmz...@earINVALIDthlink.net>
To reply by email remove INVALID