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

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

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

revision 334 by guez, Thu Jun 13 14:40:06 2019 UTC revision 335 by guez, Thu Sep 12 21:22:46 2019 UTC
# Line 4  module ju2ymds_m Line 4  module ju2ymds_m
4    
5  contains  contains
6    
7    SUBROUTINE ju2ymds (julian, year, month, day, sec)    SUBROUTINE ju2ymds(julian, year, month, day, sec)
8    
9      ! This subroutine computes from the julian day the year,      ! This subroutine computes from the julian day the year,
10      ! month, day and seconds      ! month, day and seconds
# Line 15  contains Line 15  contains
15    
16      ! See also: http://www.magnet.ch/serendipity/hermetic/cal_stud/jdn.htm      ! See also: http://www.magnet.ch/serendipity/hermetic/cal_stud/jdn.htm
17    
18      ! In the case of the Gregorian calendar we have chosen to use      ! In the case of the Gregorian calendar we have chosen to use the
19      ! the Lilian day numbers. This is the day counter which starts      ! Lilian day numbers. This is the day counter which starts on the
20      ! on the 15th October 1582. This is the day at which Pope      ! 15th October 1582. This is the day at which Pope Gregory XIII
21      ! Gregory XIII introduced the Gregorian calendar.      ! introduced the Gregorian calendar.  Compared to the true Julian
22      ! Compared to the true Julian calendar, which starts some 7980      ! calendar, which starts some 7980 years ago, the Lilian days are
23      ! years ago, the Lilian days are smaler and are dealt with easily      ! smaller and are dealt with easily on 32 bit machines. With the
24      ! on 32 bit machines. With the true Julian days you can only the      ! true Julian days you can only compute the fraction of the day in
25      ! fraction of the day in the real part to a precision of a 1/4 of      ! the real part to a precision of a 1/4 of a day with 32 bits.
     ! a day with 32 bits.  
26    
27      use calendar, only: un_jour, lock_unan      use calendar, only: un_jour, lock_unan
28      use ioconf_calendar_m, only: mon_len, un_an      use ioconf_calendar_m, only: mon_len, un_an
29    
30      REAL, INTENT(IN):: julian      double precision, INTENT(IN):: julian
31      INTEGER, INTENT(OUT):: year, month, day      INTEGER, INTENT(OUT):: year, month, day
32      REAL, INTENT(OUT):: sec      REAL, INTENT(OUT), optional:: sec
33    
34      ! Local:      ! Local:
35      INTEGER l, n, i, jd, j, d, m, y, ml      INTEGER l, n, i, jd, j, d, m, y, ml
     INTEGER add_day  
36    
37      !--------------------------------------------------------------------      !--------------------------------------------------------------------
38    
39      jd = INT(julian)      jd = INT(julian)
40      sec = (julian - jd) * un_jour      if (present(sec)) sec = (julian - jd) * un_jour
41    
42      lock_unan = .TRUE.      lock_unan = .TRUE.
43    
     IF (sec > un_jour) THEN  
        add_day = INT(sec / un_jour)  
        sec = sec - add_day * un_jour  
        jd = jd+add_day  
     ENDIF  
   
44      ! Gregorian      ! Gregorian
45      IF ( (un_an > 365.0).AND.(un_an < 366.0) ) THEN      IF ( (un_an > 365.0).AND.(un_an < 366.0) ) THEN
46         jd = jd+2299160         jd = jd+2299160

Legend:
Removed from v.334  
changed lines
  Added in v.335

  ViewVC Help
Powered by ViewVC 1.1.21