Ignore:
Timestamp:
Jul 23, 2024, 7:14:34 PM (8 weeks ago)
Author:
abarral
Message:

Replace 1DUTILS.h by module lmdz_1dutils.f90
Replace 1DConv.h by module lmdz_old_1dconv.f90 (it's only used by old_* files)
Convert *.F to *.f90
Fix gradsdef.h formatting
Remove unnecessary "RETURN" at the end of functions/subroutines

File:
1 moved

Legend:

Unmodified
Added
Removed
  • LMDZ6/branches/Amaury_dev/libf/misc/juldate.f90

    r5104 r5105  
    22! $Id$
    33
    4         SUBROUTINE juldate(ian,imoi,ijou,oh,om,os,tjd,tjdsec)
    5 c       Sous-routine de changement de date:
    6 c       gregorien>>>date julienne
    7 c       En entree:an,mois,jour,heure,min.,sec.
    8 c       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 <= 2) then
    21             year=year-1.
    22             rmon=rmon+12.
    23         endif
    24         cf=year+(rmon/100.)+(ojou/10000.)
    25         if (cf >= 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
    37         end
     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 <= 2) then
     21        year=year-1.
     22        rmon=rmon+12.
     23    endif
     24    cf=year+(rmon/100.)+(ojou/10000.)
     25    if (cf >= 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
     37end subroutine juldate
    3838
    3939
Note: See TracChangeset for help on using the changeset viewer.