source: LMDZ6/trunk/libf/misc/juldate.f90 @ 5286

Last change on this file since 5286 was 5246, checked in by abarral, 11 days ago

Convert fixed-form to free-form sources .F -> .{f,F}90
(WIP: some .F remain, will be handled in subsequent commits)

  • Property copyright set to
    Name of program: LMDZ
    Creation date: 1984
    Version: LMDZ5
    License: CeCILL version 2
    Holder: Laboratoire de m\'et\'eorologie dynamique, CNRS, UMR 8539
    See the license file in the root directory
  • Property svn:eol-style set to native
  • Property svn:keywords set to Author Date Id Revision
File size: 909 bytes
Line 
1!
2! $Id: juldate.f90 5246 2024-10-21 12:58:45Z abarral $
3!
4  subroutine juldate(ian,imoi,ijou,oh,om,os,tjd,tjdsec)
5  ! Sous-routine de changement de date:
6  ! gregorien>>>date julienne
7  ! En entree:an,mois,jour,heure,min.,sec.
8  ! En sortie:tjd
9    IMPLICIT NONE
10    INTEGER,INTENT(IN) :: ian,imoi,ijou,oh,om,os
11    REAL,INTENT(OUT) :: tjd,tjdsec
12
13    REAL :: frac,year,rmon,cf,a,b
14    INTEGER :: ojou
15
16    frac=((os/60.+om)/60.+oh)/24.
17    ojou=dble(ijou)+frac
18        year=dble(ian)
19        rmon=dble(imoi)
20    if (imoi .le. 2) then
21        year=year-1.
22        rmon=rmon+12.
23    endif
24    cf=year+(rmon/100.)+(ojou/10000.)
25    if (cf .ge. 1582.1015) then
26        a=int(year/100)
27        b=2-a+int(a/4)
28    else
29        b=0
30    endif
31    tjd=int(365.25*year)+int(30.6001*(rmon+1))+int(ojou) &
32          +1720994.5+b
33    tjdsec=(ojou-int(ojou))+(tjd-int(tjd))
34    tjd=int(tjd)+int(tjdsec)
35    tjdsec=tjdsec-int(tjdsec)
36    return
37end subroutine juldate
38
39
Note: See TracBrowser for help on using the repository browser.