Ignore:
Timestamp:
Jul 24, 2024, 4:23:34 PM (4 months ago)
Author:
abarral
Message:

rename modules properly lmdz_*
move some unused files to obsolete/
(lint) uppercase fortran keywords

File:
1 edited

Legend:

Unmodified
Added
Removed
  • LMDZ6/branches/Amaury_dev/libf/phylmd/coare_cp_mod.F90

    r5116 r5117  
    66contains
    77
    8   real function psit_30(zet)
     8  REAL function psit_30(zet)
    99    IMPLICIT NONE
    10     real, intent(in) :: zet
     10    REAL, INTENT(IN) :: zet
    1111
    1212    REAL :: x, psik, psic, f, c
     
    2626  END FUNCTION psit_30
    2727
    28   real function psiuo(zet)
     28  REAL function psiuo(zet)
    2929    IMPLICIT NONE
    30     real, intent(in) :: zet
     30    REAL, INTENT(IN) :: zet
    3131
    3232    REAL :: x, psik, psic, f, c
    3333
    34     if (zet<0) THEN
     34    IF (zet<0) THEN
    3535       x=(1.-15.*zet)**.25
    3636       psik=2.*log((1.+x)/2.)+log((1.+x*x)/2.)-2.*atan(x)+2.*atan(1.)
     
    4242     c=min(50.,.35*zet)
    4343     psiuo=-((1.+1.0*zet)**1.0+.667*(zet-14.28)/exp(c)+8.525)
    44   endif
     44  ENDIF
    4545
    4646END FUNCTION psiuo
     
    6767  IMPLICIT NONE
    6868
    69   real, intent(in) :: du,dt,dq,t,q
    70   real, intent(in) :: zu,zt,zq,p,zi
    71   integer, intent(in) :: nits
    72   ! real, dimension (nits), intent(out) :: zo,tau,hsb,hlb
    73   ! real, dimension(nits,3), intent(out) :: var
    74   real, dimension(3), intent(out) :: coeffs
    75   real, intent(out) :: rugosm
    76   real, intent(out) :: rugosh
    77 
    78   real, parameter ::  beta=1.2, von=.4, fdg = 1. ,&
     69  REAL, INTENT(IN) :: du,dt,dq,t,q
     70  REAL, INTENT(IN) :: zu,zt,zq,p,zi
     71  INTEGER, INTENT(IN) :: nits
     72  ! REAL, dimension (nits), INTENT(OUT) :: zo,tau,hsb,hlb
     73  ! REAL, DIMENSION(nits,3), INTENT(OUT) :: var
     74  REAL, DIMENSION(3), INTENT(OUT) :: coeffs
     75  REAL, INTENT(OUT) :: rugosm
     76  REAL, INTENT(OUT) :: rugosh
     77
     78  REAL, parameter ::  beta=1.2, von=.4, fdg = 1. ,&
    7979       tdk = 273.16, pi = 3.141593, grav = 9.82,&
    8080       rgas = 287.1
    8181
    82   integer, dimension(3) :: shape_input
    83 
    84   real bf, cc, rhoa, visa,&
     82  INTEGER, DIMENSION(3) :: shape_input
     83
     84  REAL bf, cc, rhoa, visa,&
    8585       u10, ut, uts, ut0, ug,&
    8686       cd10, ch10, ct, ct10,&
     
    9898
    9999
    100   real old_usr, old_tsr, old_qsr,tmp
    101 
    102   real, external :: grv
    103   integer i,j,k
     100  REAL old_usr, old_tsr, old_qsr,tmp
     101
     102  REAL, external :: grv
     103  INTEGER i,j,k
    104104!---------------- Rajout pour prendre en compte différent Z0 --------------------------------!
    105105!  INTEGER :: NGRVWAVES        ! Pour le choix du z0
     
    153153  Ribu=grav*zu/t*(dt+.61*t*dq)/ut**2
    154154
    155   if (Ribu < 0) THEN
     155  IF (Ribu < 0) THEN
    156156     zetu=CC*Ribu/(1+Ribu/Ribcu)
    157157  else
    158158     zetu=CC*Ribu*(1+27/9*Ribu/CC)
    159   endif
     159  ENDIF
    160160
    161161  L10=zu/zetu
     
    163163  ! if (zetu .GT. 50) THEN
    164164  !    nits=1
    165   ! endif
     165  ! END IF
    166166
    167167  usr=ut*von/(log(zu/zom10)-psiuo(zetu))
     
    171171
    172172  ! charnock constant - lin par morceau - constant
    173   if ( ut <= 10. ) THEN
     173  IF ( ut <= 10. ) THEN
    174174     charn=0.011
    175175  else
    176      if (ut > 18) THEN
     176     IF (ut > 18) THEN
    177177        charn=0.018
    178178     else
    179179        charn=0.011+(ut-10)/(18-10)*(0.018-0.011)
    180180     endif
    181   endif
     181  ENDIF
    182182
    183183!  ZHWAVE = 0.018*ut*ut*(1.+0.015*ut)
     
    220220     Bf=-grav/t*usr*(tsr+.61*t*qsr)
    221221
    222      if (Bf > 0) THEN
     222     IF (Bf > 0) THEN
    223223        ug=Beta*(Bf*zi)**.333
    224224     else
Note: See TracChangeset for help on using the changeset viewer.