Changeset 2957


Ignore:
Timestamp:
May 5, 2023, 9:13:28 AM (18 months ago)
Author:
emillour
Message:

Generic PCM:
Fix a buggy behavior concerning H2O aerosol variance; aeroptproperties is not
designed to handle aerosol variance which is not constant, whereas h2o_reffrad
returns a variance which varies (between 0.09 and 0.13) with location and time.
Revert to a simpler setup where the H2O aerosol variance is uniform and set by
the user (nueff_iaero_h2o flag in callphys.def; default value 0.1)
Also added some "intent()" in optci arguments and increased length of string
to store varaible name in writediagfi.
EM

Location:
trunk/LMDZ.GENERIC
Files:
4 edited

Legend:

Unmodified
Added
Removed
  • trunk/LMDZ.GENERIC/README

    r2954 r2957  
    17921792While at it also moved "Nmix_co2" and "radfixed" from callkeys_mod to radii_mod
    17931793since they are only used in that module.
     1794
     1795== 05/05/2023 == EM
     1796Fix a buggy behavior concerning H2O aerosol variance; aeroptproperties is not
     1797designed to handle aerosol variance which is not constant, whereas h2o_reffrad
     1798returns a variance which varies (between 0.09 and 0.13) with location and time.
     1799Revert to a simpler setup where the H2O aerosol variance is uniform and set by
     1800the user (nueff_iaero_h2o flag in callphys.def; default value 0.1)
     1801Also added some "intent()" in optci arguments and increased length of string
     1802to store varaible name in writediagfi.
  • trunk/LMDZ.GENERIC/libf/phystd/optci.F90

    r2875 r2957  
    4242
    4343
    44   real*8 DTAUI(L_NLAYRAD,L_NSPECTI,L_NGAUSS)
     44  real*8,intent(out) :: DTAUI(L_NLAYRAD,L_NSPECTI,L_NGAUSS)
    4545  real*8 DTAUKI(L_LEVELS,L_NSPECTI,L_NGAUSS)
    4646  real*8 TAUI(L_NLEVRAD,L_NSPECTI,L_NGAUSS)
    47   real*8 TAUCUMI(L_LEVELS,L_NSPECTI,L_NGAUSS)
    48   real*8 PLEV(L_LEVELS)
    49   real*8 TLEV(L_LEVELS)
    50   real*8 TMID(L_LEVELS), PMID(L_LEVELS)
    51   real*8 COSBI(L_NLAYRAD,L_NSPECTI,L_NGAUSS)
    52   real*8 WBARI(L_NLAYRAD,L_NSPECTI,L_NGAUSS)
     47  real*8,intent(out) :: TAUCUMI(L_LEVELS,L_NSPECTI,L_NGAUSS)
     48  real*8,intent(in) :: PLEV(L_LEVELS)
     49  real*8,intent(in) :: TLEV(L_LEVELS) ! not used
     50  real*8,intent(in) :: TMID(L_LEVELS)
     51  real*8,intent(in) :: PMID(L_LEVELS)
     52  real*8,intent(out) :: COSBI(L_NLAYRAD,L_NSPECTI,L_NGAUSS)
     53  real*8,intent(out) :: WBARI(L_NLAYRAD,L_NSPECTI,L_NGAUSS)
    5354
    5455  ! for aerosols
    55   real*8  QXIAER(L_LEVELS,L_NSPECTI,NAERKIND)
    56   real*8  QSIAER(L_LEVELS,L_NSPECTI,NAERKIND)
    57   real*8  GIAER(L_LEVELS,L_NSPECTI,NAERKIND)
    58   real*8  TAUAERO(L_LEVELS,NAERKIND)
     56  real*8,intent(in) ::  QXIAER(L_LEVELS,L_NSPECTI,NAERKIND)
     57  real*8,intent(in) ::  QSIAER(L_LEVELS,L_NSPECTI,NAERKIND)
     58  real*8,intent(in) ::  GIAER(L_LEVELS,L_NSPECTI,NAERKIND)
     59  real*8,intent(in) ::  TAUAERO(L_LEVELS,NAERKIND)
    5960  real*8  TAUAEROLK(L_LEVELS,L_NSPECTI,NAERKIND)
    6061  real*8  TAEROS(L_LEVELS,L_NSPECTI,NAERKIND)
     
    6667  real*8  LCOEF(4), LKCOEF(L_LEVELS,4)
    6768
    68   real*8 taugsurf(L_NSPECTI,L_NGAUSS-1)
     69  real*8,intent(out) :: taugsurf(L_NSPECTI,L_NGAUSS-1)
    6970  real*8 DCONT,DAERO
    7071  double precision wn_cont, p_cont, p_air, T_cont, dtemp, dtempc
     
    7273
    7374  ! variable species mixing ratio variables
    74   real*8  QVAR(L_LEVELS), WRATIO(L_LEVELS), MUVAR(L_LEVELS)
     75  real*8,intent(in) :: QVAR(L_LEVELS)
     76  real*8,intent(in) :: MUVAR(L_LEVELS)
     77  real*8  WRATIO(L_LEVELS)
    7578  real*8  KCOEF(4)
    7679  integer NVAR(L_LEVELS)
  • trunk/LMDZ.GENERIC/libf/phystd/radii_mod.F90

    r2954 r2957  
    77!     CO2 cloud properties (initialized in inifis)
    88      real,save :: Nmix_co2 ! Number mixing ratio of CO2 ice particles
     9!$OMP THREADPRIVATE(Nmix_co2)
    910
    1011      ! flag to specify if we assume a constant fixed radius for particles
    1112      logical,save :: radfixed ! initialized in inifis
     13!$OMP THREADPRIVATE(radfixed)
    1214
    1315!     water cloud optical properties (initialized in su_aer_radii below)
     
    1719      real, save ::  Nmix_h2o_ice
    1820!$OMP THREADPRIVATE(rad_h2o,rad_h2o_ice,Nmix_h2o,Nmix_h2o_ice)
    19       real, parameter ::  coef_chaud=0.13
    20       real, parameter ::  coef_froid=0.09
     21
     22      real,save :: nueff_iaero_h2o ! effective variance of H2O aerosol
     23                                   ! (initialized in su_aer_radii below)
     24!$OMP THREADPRIVATE(nueff_iaero_h2o)
     25! coefficients for a variable nueff() for h2o aerosol; disabled for now
     26      real, parameter ::  coef_hot=0.13
     27      real, parameter ::  coef_cold=0.09
    2128
    2229
     
    7683
    7784         if(iaer.eq.iaero_h2o)then ! H2O ice
    78             reffrad(1:ngrid,1:nlayer,iaer) = 1.e-5
    79             nueffrad(1:ngrid,1:nlayer,iaer) = 0.1
     85           nueff_iaero_h2o=0.1 ! default value for variance of h2o aerosols
     86           call getin_p("nueff_iaero_h2o",nueff_iaero_h2o)
     87           if (is_master) write(*,*)" nueff_iaero_h2o = ",nueff_iaero_h2o
     88           reffrad(1:ngrid,1:nlayer,iaer) = 1.e-5
     89           nueffrad(1:ngrid,1:nlayer,iaer) = nueff_iaero_h2o
    8090         endif
    8191
     
    8595         endif
    8696 
    87          if(iaer.eq.iaero_h2so4)then ! H2O ice
     97         if(iaer.eq.iaero_h2so4)then ! H2SO4 ice
    8898            reffrad(1:ngrid,1:nlayer,iaer) = 1.e-6
    8999            nueffrad(1:ngrid,1:nlayer,iaer) = 0.1
     
    214224               zfice = MIN(MAX(zfice,0.0),1.0)
    215225               reffrad(ig,l)= rad_h2o * (1.-zfice) + rad_h2o_ice * zfice
    216                nueffrad(ig,l) = coef_chaud * (1.-zfice) + coef_froid * zfice
     226!               nueffrad(ig,l) = coef_hot * (1.-zfice) + coef_cold * zfice
    217227            enddo
    218228         enddo
     
    224234               zrad_liq  = CBRT( 3*pq(ig,l)/(4*Nmix_h2o*pi*rhowater) )
    225235               zrad_ice  = CBRT( 3*pq(ig,l)/(4*Nmix_h2o_ice*pi*rhowaterice) )
    226                nueffrad(ig,l) = coef_chaud * (1.-zfice) + coef_froid * zfice
     236!               nueffrad(ig,l) = coef_hot * (1.-zfice) + coef_cold * zfice
    227237               zrad = zrad_liq * (1.-zfice) + zrad_ice * zfice
    228238
     
    231241            enddo     
    232242      end if
     243
     244! For now only constant nueff is enabled (otherwise some specific handling
     245! of variable nueff is required in aeroptproperties)
     246      nueffrad(1:ngrid,1:nlayer)=nueff_iaero_h2o
    233247
    234248   end subroutine h2o_reffrad
  • trunk/LMDZ.GENERIC/libf/phystd/writediagfi.F

    r2574 r2957  
    7878
    7979      integer,save :: zitau=0
    80       character(len=20),save :: firstnom='1234567890'
     80      character(len=40),save :: firstnom='1234567890'
    8181!$OMP THREADPRIVATE(zitau,firstnom)
    8282
Note: See TracChangeset for help on using the changeset viewer.