/[lmdze]/trunk/IOIPSL/Calendar/ymds2ju.f90
ViewVC logotype

Diff of /trunk/IOIPSL/Calendar/ymds2ju.f90

Parent Directory Parent Directory | Revision Log Revision Log | View Patch Patch

revision 92 by guez, Wed Mar 26 18:16:05 2014 UTC revision 93 by guez, Tue Apr 1 15:50:48 2014 UTC
# Line 6  contains Line 6  contains
6    
7    SUBROUTINE ymds2ju (year, month, day, sec, julian)    SUBROUTINE ymds2ju (year, month, day, sec, julian)
8    
9      use calendar, only: un_jour      ! Converts year, month, day and seconds into a julian day
10      use ymds2ju_internal_m  
11        ! In 1968 in a letter to the editor of Communications of the ACM
12        ! (CACM, volume 11, number 10, October 1968, p.657) Henry F. Fliegel
13        ! and Thomas C. Van Flandern presented such an algorithm.
14    
15        ! See also: http://www.magnet.ch/serendipity/hermetic/cal_stud/jdn.htm
16    
17        ! In the case of the Gregorian calendar we have chosen to use
18        ! the Lilian day numbers. This is the day counter which starts
19        ! on the 15th October 1582.
20        ! This is the day at which Pope Gregory XIII introduced the
21        ! Gregorian calendar.
22        ! Compared to the true Julian calendar, which starts some
23        ! 7980 years ago, the Lilian days are smaler and are dealt with
24        ! easily on 32 bit machines. With the true Julian days you can only
25        ! the fraction of the day in the real part to a precision of
26        ! a 1/4 of a day with 32 bits.
27    
28        USE calendar, ONLY: lock_unan, un_jour
29        USE ioconf_calendar_m, ONLY: mon_len, un_an
30    
31      INTEGER, INTENT(IN):: year, month, day      INTEGER, INTENT(IN):: year, month, day
32      REAL, INTENT(IN):: sec      REAL, INTENT(IN):: sec
33      REAL, INTENT(OUT):: julian      REAL, INTENT(OUT):: julian
34    
35        ! Local:
36    
37      INTEGER:: julian_day      INTEGER:: julian_day
38      REAL:: julian_sec      REAL:: julian_sec
39        INTEGER:: jd, m, y, d, ml
40    
41      !--------------------------------------------------------------------      !--------------------------------------------------------------------
42    
43      CALL ymds2ju_internal(year, month, day, sec, julian_day, julian_sec)      lock_unan = .TRUE.
44    
45        m = month
46        y = year
47        d = day
48    
49        ! We deduce the calendar from the length of the year as it
50        ! is faster than an INDEX on the calendar variable.
51    
52        ! Gregorian
53        IF ( (un_an > 365.0).AND.(un_an < 366.0) ) THEN
54           jd = (1461*(y+4800+INT(( m-14 )/12)))/4 &
55                &      +(367*(m-2-12*(INT(( m-14 )/12))))/12 &
56                &      -(3*((y+4900+INT((m-14)/12))/100))/4 &
57                &      +d-32075
58           jd = jd-2299160
59           ! No leap or All leap
60        ELSE IF (ABS(un_an-365.0) <= EPSILON(un_an) .OR. &
61             &   ABS(un_an-366.0) <= EPSILON(un_an)) THEN
62           ml = SUM(mon_len(1:m-1))
63           jd = y*INT(un_an)+ml+(d-1)
64           ! Calendar with regular month
65        ELSE
66           ml = INT(un_an)/12
67           jd = y*INT(un_an)+(m-1)*ml+(d-1)
68        ENDIF
69    
70        julian_day = jd
71        julian_sec = sec
72    
73      julian = julian_day + julian_sec / un_jour      julian = julian_day + julian_sec / un_jour
74    
75    END SUBROUTINE ymds2ju    END SUBROUTINE ymds2ju

Legend:
Removed from v.92  
changed lines
  Added in v.93

  ViewVC Help
Powered by ViewVC 1.1.21