Ignore:
Timestamp:
Oct 25, 2024, 3:41:23 PM (39 hours ago)
Author:
abarral
Message:

Replace yomcst.h by existing module

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

Legend:

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

    r5268 r5274  
    2323  !     -----------------------------------------------------------------------
    2424
     25  USE yomcst_mod_h, ONLY: RPI, RCLUM, RHPLA, RKBOL, RNAVO                   &
     26          , RDAY, REA, REPSM, RSIYEA, RSIDAY, ROMEGA                  &
     27          , R_ecc, R_peri, R_incl                                      &
     28          , RA, RG, R1SA                                         &
     29          , RSIGMA                                                     &
     30          , R, RMD, RMV, RD, RV, RCPD                    &
     31          , RMO3, RMCO2, RMC, RMCH4, RMN2O, RMCFC11, RMCFC12        &
     32          , RCPV, RCVD, RCVV, RKAPPA, RETV, eps_w                    &
     33          , RCW, RCS                                                 &
     34          , RLVTT, RLSTT, RLMLT, RTT, RATM                           &
     35          , RESTT, RALPW, RBETW, RGAMW, RALPS, RBETS, RGAMS            &
     36          , RALPD, RBETD, RGAMD
    2537  USE dimphy, ONLY : klon,klev
    2638  USE aerophys
     
    2840  USE phys_local_var_mod, ONLY: DENSO4, DENSO4B, f_r_wet, f_r_wetB
    2941  USE strataer_local_var_mod, ONLY: flag_new_strat_compo
    30  
     42
    3143  IMPLICIT NONE
    3244
     
    6981
    7082  ! Additional variables for coagulation enhancement factor due to van der Waals forces
    71   ! Taken from Chan and Mozurkewich, Measurement of the coagulation rate constant for sulfuric acid 
     83  ! Taken from Chan and Mozurkewich, Measurement of the coagulation rate constant for sulfuric acid
    7284  ! particles as a function of particle size using TDMA, Aerosol Science, 32, 321-339, 2001.
    7385  !--ok_vdw is 0 for no vdW forces, 1 for E(0), 2 for E(infinity)
     
    8395  REAL                                          :: EvdW
    8496
    85   include "YOMCST.h"
    8697
    8798! ff(i,j,k): Volume fraction of Vi,j that is partitioned to each model bin k
  • LMDZ6/trunk/libf/phylmd/StratAer/nucleation_tstep_mod.f90

    r5268 r5274  
    88SUBROUTINE nucleation_rate(rhoa,t_seri,pplay,rh,a_xm,b_xm,c_xm,nucl_rate,ntot_n,x_n)
    99
     10  USE yomcst_mod_h, ONLY: RPI, RCLUM, RHPLA, RKBOL, RNAVO                   &
     11          , RDAY, REA, REPSM, RSIYEA, RSIDAY, ROMEGA                  &
     12          , R_ecc, R_peri, R_incl                                      &
     13          , RA, RG, R1SA                                         &
     14          , RSIGMA                                                     &
     15          , R, RMD, RMV, RD, RV, RCPD                    &
     16          , RMO3, RMCO2, RMC, RMCH4, RMN2O, RMCFC11, RMCFC12        &
     17          , RCPV, RCVD, RCVV, RKAPPA, RETV, eps_w                    &
     18          , RCW, RCS                                                 &
     19          , RLVTT, RLSTT, RLMLT, RTT, RATM                           &
     20          , RESTT, RALPW, RBETW, RGAMW, RALPS, RBETS, RGAMS            &
     21          , RALPD, RBETD, RGAMD
    1022  USE aerophys
    1123  USE infotrac_phy
    1224  USE strataer_local_var_mod, ONLY : flag_new_nucl
    13  
     25
    1426  IMPLICIT NONE
    1527
     
    3850  REAL ipr     ! Ion pair production rate (cm-3 s-1) NOT IN USE
    3951
    40   include "YOMCST.h"
    4152
    4253  ! call nucleation routine
     
    331342  !
    332343
     344  USE yomcst_mod_h, ONLY: RPI, RCLUM, RHPLA, RKBOL, RNAVO                   &
     345          , RDAY, REA, REPSM, RSIYEA, RSIDAY, ROMEGA                  &
     346          , R_ecc, R_peri, R_incl                                      &
     347          , RA, RG, R1SA                                         &
     348          , RSIGMA                                                     &
     349          , R, RMD, RMV, RD, RV, RCPD                    &
     350          , RMO3, RMCO2, RMC, RMCH4, RMN2O, RMCFC11, RMCFC12        &
     351          , RCPV, RCVD, RCVV, RKAPPA, RETV, eps_w                    &
     352          , RCW, RCS                                                 &
     353          , RLVTT, RLSTT, RLMLT, RTT, RATM                           &
     354          , RESTT, RALPW, RBETW, RGAMW, RALPS, RBETS, RGAMS            &
     355          , RALPD, RBETD, RGAMD
    333356  USE aerophys
    334357
    335   IMPLICIT NONE 
     358  IMPLICIT NONE
    336359
    337360  !----------------------------------------------------
    338  
     361
    339362  !Global intent in
    340   REAL,INTENT(IN) :: t         ! temperature in K 
     363  REAL,INTENT(IN) :: t         ! temperature in K
    341364  REAL,INTENT(IN) :: satrat    ! saturatio ratio of water (between zero and 1)
    342365  REAL,INTENT(IN) :: rhoa      ! sulfuric acid concentration in 1/cm3
     
    349372  REAL,INTENT(OUT) :: jnuc_i_real   ! Charged nucleation rate in 1/cm3s (J>10^-7 1/cm3s)
    350373  REAL,INTENT(OUT) :: ntot_i_real   ! total number of molecules in the charged critical cluster
    351   REAL,INTENT(OUT) :: x_n_real      ! mole fraction of H2SO4 in the neutral critical cluster 
    352   REAL,INTENT(OUT) :: x_i_real      ! mole fraction of H2SO4 in the charged critical cluster 
    353                                            ! (note that x_n=x_i in nucleation regime) 
     374  REAL,INTENT(OUT) :: x_n_real      ! mole fraction of H2SO4 in the neutral critical cluster
     375  REAL,INTENT(OUT) :: x_i_real      ! mole fraction of H2SO4 in the charged critical cluster
     376                                           ! (note that x_n=x_i in nucleation regime)
    354377  REAL,INTENT(OUT) :: na_n_real     ! sulfuric acid molecules in the neutral critical cluster
    355378  REAL,INTENT(OUT) :: na_i_real     ! sulfuric molecules in the charged critical cluster
    356   REAL,INTENT(OUT) :: rc_n_real     ! radius of the charged critical cluster in nm 
    357   REAL,INTENT(OUT) :: rc_i_real     ! radius of the charged critical cluster in nm 
    358   REAL,INTENT(OUT) :: n_i_real      ! number of ion pairs in air (cm-3) 
     379  REAL,INTENT(OUT) :: rc_n_real     ! radius of the charged critical cluster in nm
     380  REAL,INTENT(OUT) :: rc_i_real     ! radius of the charged critical cluster in nm
     381  REAL,INTENT(OUT) :: n_i_real      ! number of ion pairs in air (cm-3)
    359382  LOGICAL,INTENT(OUT)  :: kinetic_n        ! true if kinetic neutral nucleation
    360383  LOGICAL,INTENT(OUT)  :: kinetic_i        ! true if kinetic ion-induced nucleation
     
    365388  DOUBLE PRECISION :: jnuc_i      ! Charged nucleation rate in 1/cm3s (J>10^-7 1/cm3s)
    366389  DOUBLE PRECISION :: ntot_i      ! total number of molecules in the charged critical cluster
    367   DOUBLE PRECISION :: x_n         ! mole fraction of H2SO4 in the neutral critical cluster 
    368   DOUBLE PRECISION :: x_i         ! mole fraction of H2SO4 in the charged critical cluster 
    369                                               ! (note that x_n=x_i in nucleation regime) 
     390  DOUBLE PRECISION :: x_n         ! mole fraction of H2SO4 in the neutral critical cluster
     391  DOUBLE PRECISION :: x_i         ! mole fraction of H2SO4 in the charged critical cluster
     392                                              ! (note that x_n=x_i in nucleation regime)
    370393  DOUBLE PRECISION :: na_n        ! sulfuric acid molecules in the neutral critical cluster
    371394  DOUBLE PRECISION :: na_i        ! sulfuric molecules in the charged critical cluster
    372   DOUBLE PRECISION :: rc_n        ! radius of the charged critical cluster in nm 
    373   DOUBLE PRECISION :: rc_i        ! radius of the charged critical cluster in nm 
    374   DOUBLE PRECISION :: n_i         ! number of ion pairs in air (cm-3) 
    375   DOUBLE PRECISION :: x           ! mole fraction of H2SO4 in the critical cluster 
     395  DOUBLE PRECISION :: rc_n        ! radius of the charged critical cluster in nm
     396  DOUBLE PRECISION :: rc_i        ! radius of the charged critical cluster in nm
     397  DOUBLE PRECISION :: n_i         ! number of ion pairs in air (cm-3)
     398  DOUBLE PRECISION :: x           ! mole fraction of H2SO4 in the critical cluster
    376399  DOUBLE PRECISION :: satratln    ! bounded water saturation ratio for neutral case (between 5.E-6 - 1.0)
    377400  DOUBLE PRECISION :: satratli    ! bounded water saturation ratio for ion-induced case (between 1.E-7 - 0.95)
     
    380403  DOUBLE PRECISION :: tln         ! bounded temperature for neutral case (between 165-400 K)
    381404  DOUBLE PRECISION :: tli         ! bounded temperature for ion-induced case (195-400 K)
    382   DOUBLE PRECISION :: kinrhotresn ! threshold sulfuric acid for neutral kinetic nucleation   
    383   DOUBLE PRECISION :: kinrhotresi ! threshold sulfuric acid for ion-induced kinetic nucleation
    384   DOUBLE PRECISION :: jnuc_i1     ! Ion-induced rate for n_i=1 cm-3
    385   DOUBLE PRECISION :: xloss       ! Ion loss rate
    386   DOUBLE PRECISION :: recomb      ! Ion-ion recombination rate
    387 
    388   include "YOMCST.h"
     405  DOUBLE PRECISION :: kinrhotresn ! threshold sulfuric acid for neutral kinetic nucleation
     406  DOUBLE PRECISION :: kinrhotresi ! threshold sulfuric acid for ion-induced kinetic nucleation
     407  DOUBLE PRECISION :: jnuc_i1     ! Ion-induced rate for n_i=1 cm-3
     408  DOUBLE PRECISION :: xloss       ! Ion loss rate
     409  DOUBLE PRECISION :: recomb      ! Ion-ion recombination rate
     410
    389411
    390412  !--- 0) Initializations:
  • LMDZ6/trunk/libf/phylmd/StratAer/strataer_emiss_mod.f90

    r5268 r5274  
    214214  SUBROUTINE strataer_ponde_init()
    215215
    216     USE regular_lonlat_mod, ONLY: lon_reg, lat_reg
     216    USE yomcst_mod_h, ONLY: RPI, RCLUM, RHPLA, RKBOL, RNAVO                   &
     217          , RDAY, REA, REPSM, RSIYEA, RSIDAY, ROMEGA                  &
     218          , R_ecc, R_peri, R_incl                                      &
     219          , RA, RG, R1SA                                         &
     220          , RSIGMA                                                     &
     221          , R, RMD, RMV, RD, RV, RCPD                    &
     222          , RMO3, RMCO2, RMC, RMCH4, RMN2O, RMCFC11, RMCFC12        &
     223          , RCPV, RCVD, RCVV, RKAPPA, RETV, eps_w                    &
     224          , RCW, RCS                                                 &
     225          , RLVTT, RLSTT, RLMLT, RTT, RATM                           &
     226          , RESTT, RALPW, RBETW, RGAMW, RALPS, RBETS, RGAMS            &
     227          , RALPD, RBETD, RGAMD
     228USE regular_lonlat_mod, ONLY: lon_reg, lat_reg
    217229    USE dimphy, ONLY: klon
    218230    USE mod_grid_phy_lmdz, ONLY: nbp_lat, nbp_lon
     
    220232    USE strataer_local_var_mod
    221233
    222     INCLUDE "YOMCST.h"  !--RPI
     234      !--RPI
    223235
    224236    ! local var
Note: See TracChangeset for help on using the changeset viewer.