Ignore:
Timestamp:
Dec 9, 2025, 3:08:05 PM (8 hours ago)
Author:
lebasn
Message:

StratAer?: remove old params and rename others for coherence (flag_nucl and flag_strat_compo). Use integer instead of boolean to choose compo and nucleation methods.

File:
1 edited

Legend:

Unmodified
Added
Removed
  • LMDZ6/trunk/libf/phylmd/StratAer/coagulate.f90

    r5285 r5924  
    2828  USE infotrac_phy
    2929  USE phys_local_var_mod, ONLY: DENSO4, DENSO4B, f_r_wet, f_r_wetB
    30   USE strataer_local_var_mod, ONLY: flag_new_strat_compo
     30  USE strataer_local_var_mod, ONLY: flag_strat_compo
    3131
    3232  IMPLICIT NONE
     
    129129  IF (is_strato(ilon,ilev)) THEN
    130130  !compute actual wet particle radius & volume for every grid box
    131   IF(flag_new_strat_compo) THEN
     131  IF(flag_strat_compo) THEN
    132132     DO i=1, nbtr_bin
    133133        radiuswet(i)=f_r_wetB(ilon,ilev,i)*mdw(i)/2.
     
    174174!--pre-compute the thermal velocity of a particle thvelpar(i) from equation 20
    175175  thvelpar=0.0
    176   IF(flag_new_strat_compo) THEN
     176  IF(flag_strat_compo) THEN
    177177     DO i=1, nbtr_bin
    178178        m_par(i)=4./3.*RPI*radiuswet(i)**3.*DENSO4B(ilon,ilev,i)*1000.
     
    275275!                     =(Vdry(k)*tr_t(ilon,ilev,k)+pdtcoag*num_dry)/( (1.+pdtcoag*denom)*Vdry(k) )
    276276!          with num_dry=...beta(i,j)*Vdry(i)*....
    277 !       so in old STRATAER (.not.flag_new_strat_compo), it was correct
     277!       so in old STRATAER (.not.flag_strat_compo), it was correct
    278278  ENDIF
    279279
Note: See TracChangeset for help on using the changeset viewer.