Ignore:
Timestamp:
Mar 13, 2020, 3:23:08 PM (5 years ago)
Author:
emillour
Message:

Venus GCM:
Some cleanup to be able to compile with modern gfortran compiler (5.5+) which
complained about the need for an explicit interface in sed_and_prod_mad.F90
for get_weff().
Turned it into a module in the process.
EM

File:
1 edited

Legend:

Unmodified
Added
Removed
  • trunk/LMDZ.VENUS/libf/phyvenus/cloudvenus/sed_and_prod_mad.F90

    r1676 r2259  
     1MODULE SED_AND_PROD_MAD
     2
     3IMPLICIT NONE
     4
    15!
    26! All parameter variable should be modified regarding the sudied system.
     
    3034! ft = Theoretical Settling velocity at each vertical levels with Fiadero correction
    3135
     36CONTAINS
    3237
    3338!============================================================================
     
    3641FUNCTION get_r0_1(M0,M3) RESULT(ret)
    3742
    38   use free_param
    39   use donnees
     43  use free_param, only: sigma1
    4044
    4145  IMPLICIT NONE
     
    5761FUNCTION get_r0_2(M0,M3) RESULT(ret)
    5862
    59   use free_param
    60   use donnees
     63  use free_param, only: sigma2
    6164
    6265  IMPLICIT NONE
     
    8184  !! Compute effective gravitational acceleration.
    8285
    83   use free_param
    84   use donnees
     86  use donnees, only: g0, rpla
    8587
    8688  IMPLICIT NONE
     
    98100SUBROUTINE aer_production(dt,nlay,plev,zlev,zlay,dm0_1,dm3_1)
    99101
    100   use free_param
    101   use donnees
     102  use free_param, only: sigz, p_aer, r_aer, rho_aer, sig_aer, tx_prod
     103  use donnees, only: pi
    102104
    103105  IMPLICIT NONE
     
    166168  !! from ancient times. It is based on \cite{toon1988b,fiadeiro1977,turco1979} and is an update of the algorithm
    167169  !! originally implemented in the LMDZ-Titan 2D GCM.
    168 
    169   use free_param
    170   use donnees
    171170
    172171  IMPLICIT NONE
     
    240239  !! be computed.
    241240
    242   use free_param
    243   use donnees
     241  use free_param, only: rho_aer
     242  use donnees, only: akn, df, fiadero_max, fiadero_min, no_fiadero_w, rmono
    244243 
    245244  IMPLICIT NONE
     
    267266  REAL                       :: af1,af2,ar1,ar2
    268267  REAL                       :: csto,cslf,ratio,wdt,dzb
    269   REAL                       :: rb2ra, VISAIR, FPLAIR, alpha_k, effg
     268  REAL                       :: rb2ra, VISAIR, FPLAIR, alpha_k
    270269  REAL, DIMENSION(nlay+1) :: zcorf
    271270  ! ------------------
     
    327326  !! It is assumed that the aerosols size-distribution is the same as the mode 1 of cloud drops.
    328327 
    329   use free_param
    330   use donnees
     328  use free_param, only: rho_aer, sig_aer
     329  use donnees, only: pi, wsed_m0, wsed_m3
    331330 
    332331  IMPLICIT NONE
     
    354353  REAL, DIMENSION(nlay+1):: ft,fdcor,wth
    355354  REAL, DIMENSION(nlay)  :: m0vsed,m3vsed,r0
    356   REAL                   :: m,n,p,get_r0_1
     355  REAL                   :: m,n,p
    357356  REAL, PARAMETER        :: fac = 4.D0/3.D0 * pi
    358357  INTEGER                :: nla,nle,i
     
    436435  !!     cld_flux = fac *ft * (m3ccn * rho_aer + SUM(rho_liq(:) + m3liq(:)))
    437436 
    438   use free_param
    439   use donnees
     437  use free_param, only: sigma1, sigma2
     438  use donnees, only: pi, wsed_m0, wsed_m3
    440439 
    441440  IMPLICIT NONE
     
    467466  REAL, DIMENSION(nlay+1):: ft, fdcor, wth
    468467  REAL, DIMENSION(nlay)  :: r0, m3sum
    469   REAL                   :: m, n, p, sig, get_r0_1, get_r0_2
     468  REAL                   :: m, n, p, sig
    470469  REAL, PARAMETER        :: fac = 4.D0/3.D0 * pi
    471470  INTEGER                :: i, nla, nle, nc
     
    540539END SUBROUTINE drop_sedimentation
    541540
    542 !END MODULE SED_AND_PROD
     541END MODULE SED_AND_PROD_MAD
Note: See TracChangeset for help on using the changeset viewer.