Ignore:
Timestamp:
Dec 9, 2025, 3:08:05 PM (2 days 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.

Location:
LMDZ6/trunk/libf/phylmd/StratAer
Files:
10 edited

Legend:

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

    r5268 r5924  
    1818
    1919  USE phys_local_var_mod, ONLY: mdw, budg_sed_part, DENSO4, DENSO4B, f_r_wet, f_r_wetB, vsed_aer
    20   USE strataer_local_var_mod, ONLY: flag_new_strat_compo
     20  USE strataer_local_var_mod, ONLY: flag_strat_compo
    2121  USE dimphy, ONLY : klon,klev
    2222  USE infotrac_phy
     
    9090
    9191      ! stokes-velocity with cunnigham slip- flow correction
    92       IF(flag_new_strat_compo) THEN
     92      IF(flag_strat_compo) THEN
    9393         ! stokes-velocity with cunnigham slip- flow correction
    9494         ZVAER(JL,JK,nb) = 2./9.*(DENSO4B(JL,JK,nb)*1000.-ZRHO)*RG/zvis(JL,JK)*(f_r_wetB(JL,JK,nb)*mdw(nb)/2.)**2.* &
  • 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
  • LMDZ6/trunk/libf/phylmd/StratAer/interp_sulf_input.f90

    r5559 r5924  
    1919  USE aerophys
    2020  USE yomcst_mod_h
    21   USE strataer_local_var_mod, ONLY : flag_newclim_file,flag_verbose_strataer
     21  USE strataer_local_var_mod, ONLY : flag_verbose_strataer
    2222
    2323IMPLICIT NONE
     
    125125     
    126126    !--init ncdf variables
    127     IF(flag_newclim_file) THEN
    128       nc_fname = "ocs_so2_h2so4_annual_lmdz.nc"
    129       nc_lat   = "LAT"
    130       nc_lon   = "LON"
    131     ELSE
    132       ! old file for retro compatibility
    133       nc_fname = "ocs_so2_annual_lmdz.nc"
    134       nc_lat   = "lat"
    135       nc_lon   = "lon"
    136     ENDIF
    137 
     127    nc_fname = "ocs_so2_h2so4_annual_lmdz.nc"
     128    nc_lat   = "LAT"
     129    nc_lon   = "LON"
     130   
    138131    !--reading emission files
    139132    CALL nf95_open(nc_fname, nf90_nowrite, ncid_in)
     
    180173    IF(flag_verbose_strataer) print *,'code erreur SO2_lifetime_in=', ncerr, varid
    181174   
    182     IF(flag_newclim_file) THEN
    183        CALL nf95_inq_varid(ncid_in, "O3", varid)
    184        ncerr = nf90_get_var(ncid_in, varid, O3_clim_in)
    185        IF(flag_verbose_strataer) print *,'code erreur O3=', ncerr, varid
    186        
    187        CALL nf95_inq_varid(ncid_in, "H2SO4_LIFET", varid)
    188        ncerr = nf90_get_var(ncid_in, varid, H2SO4_lifetime_in)
    189        IF(flag_verbose_strataer) print *,'code erreur H2SO4_lifetime_in=', ncerr, varid
    190     ENDIF
     175    CALL nf95_inq_varid(ncid_in, "O3", varid)
     176    ncerr = nf90_get_var(ncid_in, varid, O3_clim_in)
     177    IF(flag_verbose_strataer) print *,'code erreur O3=', ncerr, varid
     178   
     179    CALL nf95_inq_varid(ncid_in, "H2SO4_LIFET", varid)
     180    ncerr = nf90_get_var(ncid_in, varid, H2SO4_lifetime_in)
     181    IF(flag_verbose_strataer) print *,'code erreur H2SO4_lifetime_in=', ncerr, varid
    191182   
    192183    CALL nf95_close(ncid_in)
     
    215206     
    216207      ! O3 from 2d model is not tracer, in VMR
    217       IF(flag_newclim_file) THEN
    218          H2SO4_lifetime_mth(:,j,:) = H2SO4_lifetime_in(:,n_lat+1-j,:,mth_cur)
    219          ! new input files
    220          O3_clim_mth(:,j,:) = 1.e-6*O3_clim_in(:,n_lat+1-j,:,mth_cur)
    221       ELSE
    222          H2SO4_lifetime_mth(:,j,:) = 1.e-6
    223          O3_clim_mth(:,j,:) = 1.e-6
    224       ENDIF
     208      H2SO4_lifetime_mth(:,j,:) = H2SO4_lifetime_in(:,n_lat+1-j,:,mth_cur)
     209      ! new input files
     210      O3_clim_mth(:,j,:) = 1.e-6*O3_clim_in(:,n_lat+1-j,:,mth_cur)
    225211    ENDDO
    226212
     
    279265           MAX(0.0,MIN(paprs_glo(i,k),paprs_input(kk))-MAX(paprs_glo(i,k+1),paprs_input(kk+1))) &
    280266           *SO2_lifetime_tmp(i,kk)/(paprs_glo(i,k)-paprs_glo(i,k+1))
    281       IF(flag_newclim_file) THEN
    282          H2SO4_lifetime_glo(i,k)=H2SO4_lifetime_glo(i,k)+ &
    283               MAX(0.0,MIN(paprs_glo(i,k),paprs_input(kk)) &
    284               -MAX(paprs_glo(i,k+1),paprs_input(kk+1))) &
    285               *H2SO4_lifetime_tmp(i,kk)/(paprs_glo(i,k)-paprs_glo(i,k+1))
    286       ENDIF
     267      H2SO4_lifetime_glo(i,k)=H2SO4_lifetime_glo(i,k)+ &
     268           MAX(0.0,MIN(paprs_glo(i,k),paprs_input(kk)) &
     269           -MAX(paprs_glo(i,k+1),paprs_input(kk+1))) &
     270           *H2SO4_lifetime_tmp(i,kk)/(paprs_glo(i,k)-paprs_glo(i,k+1))
    287271     
    288272      OCS_clim_glo(i,k)=OCS_clim_glo(i,k)+ &
     
    292276           MAX(0.0,MIN(paprs_glo(i,k),paprs_input(kk))-MAX(paprs_glo(i,k+1),paprs_input(kk+1))) &
    293277           *SO2_clim_tmp(i,kk)/(paprs_glo(i,k)-paprs_glo(i,k+1))
    294       IF(flag_newclim_file) THEN
    295          O3_clim_glo(i,k)=O3_clim_glo(i,k)+ &
    296               MAX(0.0,MIN(paprs_glo(i,k),paprs_input(kk)) &
    297               -MAX(paprs_glo(i,k+1),paprs_input(kk+1))) &
    298               *O3_clim_tmp(i,kk)/(paprs_glo(i,k)-paprs_glo(i,k+1))
    299       ENDIF
     278      O3_clim_glo(i,k)=O3_clim_glo(i,k)+ &
     279           MAX(0.0,MIN(paprs_glo(i,k),paprs_input(kk)) &
     280           -MAX(paprs_glo(i,k+1),paprs_input(kk+1))) &
     281           *O3_clim_tmp(i,kk)/(paprs_glo(i,k)-paprs_glo(i,k+1))
    300282      ENDDO
    301283    ENDDO
  • LMDZ6/trunk/libf/phylmd/StratAer/micphy_tstep.f90

    r5268 r5924  
    5757       & 1.*(7.990811e-4 + 1.*(-7.458060e-4 + 1.*2.58139e-4 )))))
    5858
    59   IF(.not.flag_new_strat_compo) THEN
     59  IF(.not.flag_strat_compo) THEN
    6060     ! STRAACT (R2SO4, t_seri -> H2SO4 activity coefficient (ACTSO4)) for cond/evap
    6161     CALL STRAACT(ACTSO4)
     
    9797      ENDIF
    9898      ! compute cond/evap rate in kg(H2SO4)/kgA/s
    99       IF(flag_new_strat_compo) THEN
     99      IF(flag_strat_compo) THEN
    100100         R2SO4ik(:)   = R2SO4B(ilon,ilev,:)
    101101         DENSO4ik(:)  = DENSO4B(ilon,ilev,:)
     
    144144        & *pplay(ilon,ilev)/t_seri(ilon,ilev)/RD/1.E6/mH2SO4mol
    145145    ! compute cond/evap rate in kg(H2SO4)/kgA/s (now only evap for pdtphys)
    146     IF(flag_new_strat_compo) THEN
     146    IF(flag_strat_compo) THEN
    147147       CALL condens_evapor_rate_kelvin(rhoa,t_seri(ilon,ilev),pplay(ilon,ilev), &
    148148            & R2SO4(ilon,ilev),DENSO4(ilon,ilev),f_r_wet(ilon,ilev), &
  • LMDZ6/trunk/libf/phylmd/StratAer/nucleation_tstep_mod.f90

    r5285 r5924  
    1111  USE aerophys
    1212  USE infotrac_phy
    13   USE strataer_local_var_mod, ONLY : flag_new_nucl
     13  USE print_control_mod, ONLY : lunout
     14  USE strataer_local_var_mod, ONLY : flag_nucl
    1415
    1516  IMPLICIT NONE
     
    4142
    4243  ! call nucleation routine
    43   IF (.NOT.flag_new_nucl) THEN
    44     ! Use older routine from Hanna Vehkamäki (FMI)
    45     CALL binapara(t_seri,rh,rhoa,jnuc_n,x_n,ntot_n,rc_n)
    46     ! when total number of molecules is too small
    47     ! then set jnuc_n to collision rate of two H2SO4 molecules (following personal communication of Ulrike Niemeier and Hanna Vehkamäki)
    48     IF (ntot_n < 4.0) THEN
    49       VH2SO4mol=mH2SO4mol/(1.E-3*(a_xm+t_seri*(b_xm+t_seri*c_xm))) !cm3
    50       jnuc_n = rhoa**2. *(3./4.*RPI)**(1./6.) *(12.*RKBOL*t_seri/mH2SO4mol)**0.5 &
    51            & *100.*(2.*VH2SO4mol**(1./3.))**2. !1/(cm3s)
    52       ntot_n=2.0
    53       x_n=1.0
    54     ENDIF
    55   ELSE
    56     ! Use new routine from Anni Maattanen (LATMOS)
    57     csi=0.0   ! no charged nucleation for now
    58     ipr=-1.0  ! dummy value to make sure charged nucleation does not occur
    59     airn=0.0  ! NOT IN USE
    60 !   airn=pplay/t_seri/RD/1.E3*RNAVO/RMD ! molec cm-3 (for future use, to be confirmed)
    61     CALL newbinapara(t_seri,rh,rhoa,csi,airn,ipr,jnuc_n,ntot_n,jnuc_i,ntot_i, &
    62                    & x_n,x_i,na_n,na_i,rc_n,rc_i,n_i,kinetic_n,kinetic_i)
    63   ENDIF
    64 
     44  SELECT CASE(flag_nucl)
     45       CASE(1)
     46          ! Use older routine from Hanna Vehkamäki (FMI)
     47          CALL binapara(t_seri,rh,rhoa,jnuc_n,x_n,ntot_n,rc_n)
     48          ! when total number of molecules is too small
     49          ! then set jnuc_n to collision rate of two H2SO4 molecules (following personal communication of Ulrike Niemeier and Hanna Vehkamäki)
     50          IF (ntot_n < 4.0) THEN
     51             VH2SO4mol=mH2SO4mol/(1.E-3*(a_xm+t_seri*(b_xm+t_seri*c_xm))) !cm3
     52             jnuc_n = rhoa**2. *(3./4.*RPI)**(1./6.) *(12.*RKBOL*t_seri/mH2SO4mol)**0.5 &
     53                  & *100.*(2.*VH2SO4mol**(1./3.))**2. !1/(cm3s)
     54             ntot_n=2.0
     55             x_n=1.0
     56          ENDIF
     57         
     58       CASE(2)
     59          ! Use new routine from Anni Maattanen (LATMOS)
     60          csi=0.0   ! no charged nucleation for now
     61          ipr=-1.0  ! dummy value to make sure charged nucleation does not occur
     62          airn=0.0  ! NOT IN USE
     63          !   airn=pplay/t_seri/RD/1.E3*RNAVO/RMD ! molec cm-3 (for future use, to be confirmed)
     64          CALL newbinapara(t_seri,rh,rhoa,csi,airn,ipr,jnuc_n,ntot_n,jnuc_i,ntot_i, &
     65               & x_n,x_i,na_n,na_i,rc_n,rc_i,n_i,kinetic_n,kinetic_i)
     66
     67       CASE DEFAULT
     68          ! Unknown value
     69          WRITE(lunout,*) 'ERROR : unknown value for nucleation method flag_nucl=',flag_nucl,' ! Only 1 or 2 are avalaible.'
     70          CALL abort_physic('nucleation_tstep_mod','Wrong value for flag_nucl.',1)
     71         
     72       END SELECT
     73       
    6574  ! convert jnuc_n from particles/cm3/s to kg(H2SO4)/kgA/s
    6675  nucl_rate=jnuc_n*ntot_n*x_n*mH2SO4mol/(pplay/t_seri/RD/1.E6)
  • LMDZ6/trunk/libf/phylmd/StratAer/ocs_to_so2.f90

    r5268 r5924  
    99  USE yomcst_mod_h, ONLY : RG
    1010  USE phys_local_var_mod, ONLY : OCS_lifetime, budg_3D_ocs_to_so2, budg_ocs_to_so2
    11   USE strataer_local_var_mod, ONLY : flag_min_rreduce
    12 
     11 
    1312  IMPLICIT NONE
    1413
     
    3736            rreduce = OCS_lifetime(ilon,ilev)
    3837            ! Check lifetime rreduce < timestep*3 (such as H2SO4 loss > 0.28*H2SO4) with exp(-1/3)=0.72
    39             IF(flag_min_rreduce) THEN
    40                IF (rreduce .LT. (3.*pdtphys)) rreduce = 3.*pdtphys
    41             ENDIF
     38            IF (rreduce .LT. (3.*pdtphys)) rreduce = 3.*pdtphys
    4239            budg_3D_ocs_to_so2(ilon,ilev)=tr_seri(ilon,ilev,id_OCS_strat)*(1.0-exp(-pdtphys/rreduce))
    4340            tr_seri(ilon,ilev,id_OCS_strat)=tr_seri(ilon,ilev,id_OCS_strat) - budg_3D_ocs_to_so2(ilon,ilev)
  • LMDZ6/trunk/libf/phylmd/StratAer/so2_to_h2so4.f90

    r5605 r5924  
    1010  ! lifetime (sec) et O3_clim (VMR)
    1111  USE phys_local_var_mod, ONLY : SO2_lifetime,H2SO4_lifetime,O3_clim,budg_3D_so2_to_h2so4,budg_so2_to_h2so4,SO2_chlm
    12   USE strataer_local_var_mod, ONLY : flag_OH_reduced, flag_H2SO4_photolysis, flag_min_rreduce
     12  USE strataer_local_var_mod, ONLY : flag_OH_reduced, flag_H2SO4_photolysis
    1313 
    1414  IMPLICIT NONE
     
    100100              ! Check lifetime rreduce < timestep*1.5 (such as SO2 loss > 0.5*SO2) with exp(-1/1.5)=0.52
    101101              ! Check lifetime rreduce < timestep*3 (such as SO2 loss > 0.28*SO2) with exp(-1/3)=0.72
    102               IF(flag_min_rreduce) THEN
    103                  IF (rreduce .LT. (3.*pdtphys)) rreduce = 3.*pdtphys
    104               ENDIF
     102              IF (rreduce .LT. (3.*pdtphys)) rreduce = 3.*pdtphys
    105103              budg_3D_so2_to_h2so4(ilon,ilev)=tr_seri(ilon,ilev,id_SO2_strat)*(1.0-exp(-pdtphys/rreduce))
    106104              tr_seri(ilon,ilev,id_SO2_strat)=tr_seri(ilon,ilev,id_SO2_strat) - budg_3D_so2_to_h2so4(ilon,ilev)
     
    132130                 ! Check lifetime rreduce < timestep*1.5 (such as H2SO4 loss > 0.5*H2SO4) with exp(-1/1.5)=0.52
    133131                 ! Check lifetime rreduce < timestep*3 (such as H2SO4 loss > 0.28*H2SO4) with exp(-1/3)=0.72
    134                  IF(flag_min_rreduce) THEN
    135                     IF (rreduce .LT. (3.*pdtphys)) rreduce = 3.*pdtphys
    136                  ENDIF
     132                 IF (rreduce .LT. (3.*pdtphys)) rreduce = 3.*pdtphys
    137133                 dummyso4toso2 = (mSO2mol/mH2SO4mol)*tr_seri(ilon,ilev,id_H2SO4_strat)*(1.0-exp(-pdtphys/rreduce))
    138134                 budg_3D_so2_to_h2so4(ilon,ilev) = budg_3D_so2_to_h2so4(ilon,ilev) + dummyso4toso2
  • LMDZ6/trunk/libf/phylmd/StratAer/stratH2O_methox.f90

    r5338 r5924  
    2020  USE aerophys
    2121  USE yomcst_mod_h
    22   USE strataer_local_var_mod, ONLY : flag_newclim_file
    2322 
    2423IMPLICIT NONE
  • LMDZ6/trunk/libf/phylmd/StratAer/strataer_local_var_mod.f90

    r5652 r5924  
    1414  !$OMP THREADPRIVATE(flag_emit_distrib)
    1515 
    16   ! flag to choose nucleation nucleation method
    17   LOGICAL,SAVE :: flag_new_nucl   ! T=new routine from A. Maattanen (LATMOS), F=older routine from H. Vehkamäki (FMI)
    18   !$OMP THREADPRIVATE(flag_new_nucl)
    19  
    20   ! Use relative humidity from 2D model stratospheric H2O because LMDz is too dry in the stratosphere
    21   ! (no CH4 oxidation)
    22   LOGICAL,SAVE :: flag_H2O2d_nucleation
    23   !$OMP THREADPRIVATE(flag_H2O2d_nucleation)
     16  ! flag to choose nucleation method
     17  INTEGER,SAVE :: flag_nucl   ! 1: routine from H. Vehkamäki (FMI), 2: routine from A. Maattanen (LATMOS)
     18  !$OMP THREADPRIVATE(flag_nucl)
    2419 
    2520  ! OH reduction from SO2. OH is reduced when its reaction with SO2 competes sufficiently with its reaction
     
    3328  !$OMP THREADPRIVATE(flag_H2SO4_photolysis)
    3429 
    35   ! flag for minimum lifetime (=1.5 pdt phys)
    36   LOGICAL,SAVE :: flag_min_rreduce
    37   !$OMP THREADPRIVATE(flag_min_rreduce)
    38  
    39   ! flag to read new climato (O3, H2O & H2SO4_LIFET)
    40   LOGICAL,SAVE :: flag_newclim_file
    41   !$OMP THREADPRIVATE(flag_newclim_file)
    42  
    43   ! flag to choose new H2SO4 density and weight percent from Tabazadeh et al. (1994).
    44   LOGICAL,SAVE :: flag_new_strat_compo
    45   !$OMP THREADPRIVATE(flag_new_strat_compo)
     30  ! Parameterization method to compute H2SO4/H2O aerosol composition
     31  INTEGER,SAVE :: flag_strat_compo  !  1: S. Bekki et al., 2: Tabazadeh et al. 1997
     32  !$OMP THREADPRIVATE(flag_strat_compo)
    4633 
    4734  ! Verbose mode to get more print info
     
    184171    flag_emit = 0                   ! Background (default)
    185172    flag_emit_distrib = 0           ! Gaussian (default)
    186     flag_new_nucl = .TRUE.          ! Define nucleation routine (default: A. Maattanen - LATMOS)
     173    flag_nucl = 2                   ! Define nucleation routine (default: A. Maattanen - LATMOS)
    187174    flag_verbose_strataer = .FALSE. ! verbose mode
    188     flag_newclim_file = .TRUE.      ! Define input climato file (default: all climato)
    189     flag_H2O2d_nucleation = .FALSE. ! Use H2O 2D climato (default: No)
    190175    flag_OH_reduced = .FALSE.       ! OH reduce (default: No)
    191176    flag_H2SO4_photolysis = .FALSE. ! H2SO4 photolysis (default: No)
    192     flag_min_rreduce = .TRUE.       ! Minimum lifetime=1.5 pdt phys (default: Yes)
    193     flag_new_strat_compo =.FALSE.   ! H2SO4/H2O weight percent & density routine (default: S. Bekki)
     177    flag_strat_compo = 2            ! H2SO4/H2O composition routine (default: Tabazadeh et al. 1997)
    194178    ok_qemiss = .FALSE.             ! H2O emission flag
    195179   
     
    219203    CALL getin_p('flag_emit_distrib',flag_emit_distrib)
    220204    CALL getin_p('flag_verbose_strataer',flag_verbose_strataer)
    221     CALL getin_p('flag_new_nucl',flag_new_nucl)
    222     CALL getin_p('flag_newclim_file',flag_newclim_file)
    223     CALL getin_p('flag_H2O2d_nucleation',flag_H2O2d_nucleation)
     205    CALL getin_p('flag_nucl',flag_nucl)
    224206    CALL getin_p('flag_OH_reduced',flag_OH_reduced)
    225207    CALL getin_p('flag_H2SO4_photolysis',flag_H2SO4_photolysis)
    226     CALL getin_p('flag_min_rreduce',flag_min_rreduce)
    227     CALL getin_p('flag_new_strat_compo',flag_new_strat_compo)
     208    CALL getin_p('flag_strat_compo',flag_strat_compo)
    228209    CALL getin_p('ok_qemiss',ok_qemiss)
    229    
    230     !============= Test flag coherence =============
    231     IF (.NOT. flag_newclim_file) THEN
    232        IF (flag_H2SO4_photolysis .OR. flag_OH_reduced .OR. flag_H2O2d_nucleation) THEN
    233           WRITE(lunout,*) 'ERROR : flag_newclim_file=',flag_newclim_file, &
    234                ' whereas flag_H2SO4_photolysis=',flag_H2SO4_photolysis,', flag_OH_reduced=',flag_OH_reduced, &
    235                ' and flag_H2O2d_nucleation=',flag_H2O2d_nucleation
    236           CALL abort_physic('strataer_local_var_mod','Incompatible options in physiq_def file !',1)
    237        ENDIF
    238        IF(flag_min_rreduce) THEN
    239           WRITE(lunout,*) 'Warning : flag_min_rreduce will be ignored with old climato file !'
    240        ENDIF
    241     ENDIF
    242210   
    243211    !============= Print params =============
    244212    IF (is_master) THEN
    245213       WRITE(lunout,*) 'flag_emit = ',flag_emit
    246        WRITE(lunout,*) 'IN STRATAER : flag_new_nucl = ',flag_new_nucl
    247        WRITE(lunout,*) 'IN STRATAER : flag_newclim_file = ',flag_newclim_file
     214       WRITE(lunout,*) 'IN STRATAER : flag_nucl = ',flag_nucl
    248215       WRITE(lunout,*) 'IN STRATAER : flag_emit_distrib = ',flag_emit_distrib
    249216       WRITE(lunout,*) 'IN STRATAER : flag_verbose_strataer = ',flag_verbose_strataer
    250217       IF (flag_emit == 1 .OR. flag_emit == 4) THEN
    251           WRITE(lunout,*) 'IN STRATAER : flag_H2O2d_nucleation = ',flag_H2O2d_nucleation
    252218          WRITE(lunout,*) 'IN STRATAER : flag_OH_reduced = ',flag_OH_reduced
    253219          WRITE(lunout,*) 'IN STRATAER : flag_H2SO4_photolysis = ',flag_H2SO4_photolysis
    254           WRITE(lunout,*) 'IN STRATAER : flag_min_rreduce = ',flag_min_rreduce
    255           WRITE(lunout,*) 'IN STRATAER : flag_new_strat_compo = ',flag_new_strat_compo
     220          WRITE(lunout,*) 'IN STRATAER : flag_strat_compo = ',flag_strat_compo
    256221          WRITE(lunout,*) 'IN STRATAER : ok_qemiss = ',ok_qemiss
    257222       ENDIF
  • LMDZ6/trunk/libf/phylmd/StratAer/traccoag_mod.f90

    r5367 r5924  
    121121    WHERE (stratomask.GT.0.5) is_strato=.TRUE.
    122122
    123     IF(flag_new_strat_compo) THEN
    124        IF(debutphy) WRITE(lunout,*) 'traccoag: COMPO/DENSITY (Tabazadeh 97) + H2O kelvin effect', flag_new_strat_compo
     123    IF(flag_strat_compo) THEN
     124       IF(debutphy) WRITE(lunout,*) 'traccoag: COMPO/DENSITY (Tabazadeh 97) + H2O kelvin effect', flag_strat_compo
    125125       ! STRACOMP (H2O, P, t_seri, R -> R2SO4 + Kelvin effect) : Taba97, Socol, etc...
    126126       CALL stracomp_kelvin(sh,t_seri,pplay)
    127127    ELSE
    128        IF(debutphy) WRITE(lunout,*) 'traccoag: COMPO from Bekki 2D model', flag_new_strat_compo
     128       IF(debutphy) WRITE(lunout,*) 'traccoag: COMPO from Bekki 2D model', flag_strat_compo
    129129       ! STRACOMP (H2O, P, t_seri -> aerosol composition (R2SO4))
    130130       ! H2SO4 mass fraction in aerosol (%)
     
    383383                   & *pplay(i,j)/t_seri(i,j)/RD                           ! [air mass concentration in kg air /m3A]
    384384             
    385               IF(flag_new_strat_compo) THEN
     385              IF(flag_strat_compo) THEN
    386386                 !     SAD_sulfate: SAD WET sulfate aerosols (cm2/cm3)
    387387                 SAD_sulfate(i,j) = SAD_sulfate(i,j) + nd_mode(i,j,it) &     ! [DRY part/m3A (in bin it)]
Note: See TracChangeset for help on using the changeset viewer.