| 1 | MODULE strataer_local_var_mod |
|---|
| 2 | ! This module contains strato microphysic model parameters & variables |
|---|
| 3 | |
|---|
| 4 | IMPLICIT NONE |
|---|
| 5 | |
|---|
| 6 | !============= GENERAL PARAMS ============= |
|---|
| 7 | !flag for type emission scenario: (0) background aer ; (1) volcanic eruption with Sulfur ; |
|---|
| 8 | !(2,3) strato aer injections (SAI) ; (4) volcanic eruption chimistry; (5) rocket |
|---|
| 9 | INTEGER,SAVE :: flag_emit |
|---|
| 10 | !$OMP THREADPRIVATE(flag_emit) |
|---|
| 11 | |
|---|
| 12 | ! flag for emission altitude distribution: (0) gaussian; (1) uniform |
|---|
| 13 | INTEGER,SAVE :: flag_emit_distrib |
|---|
| 14 | !$OMP THREADPRIVATE(flag_emit_distrib) |
|---|
| 15 | |
|---|
| 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) |
|---|
| 19 | |
|---|
| 20 | ! OH reduction from SO2. OH is reduced when its reaction with SO2 competes sufficiently with its reaction |
|---|
| 21 | ! with O3 (Bekki, 1995). As a result, SO2 lifetime is extended. 2D model O3 climatologies are needed. |
|---|
| 22 | LOGICAL,SAVE :: flag_OH_reduced |
|---|
| 23 | !$OMP THREADPRIVATE(flag_OH_reduced) |
|---|
| 24 | |
|---|
| 25 | ! H2SO4 photolysis: H2SO4 is converted into SO2 by complex photolytic processes. Here simplified approach |
|---|
| 26 | ! by setting H2SO4 cross-sections = 0.3*HCl cross-sections (Rinsland et al., 1995) |
|---|
| 27 | LOGICAL,SAVE :: flag_H2SO4_photolysis |
|---|
| 28 | !$OMP THREADPRIVATE(flag_H2SO4_photolysis) |
|---|
| 29 | |
|---|
| 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) |
|---|
| 33 | |
|---|
| 34 | ! Verbose mode to get more print info |
|---|
| 35 | LOGICAL, SAVE :: flag_verbose_strataer |
|---|
| 36 | !$OMP THREADPRIVATE(flag_verbose_strataer) |
|---|
| 37 | |
|---|
| 38 | |
|---|
| 39 | !============= NUCLEATION VARS ============= |
|---|
| 40 | ! MOLECULAR ACCOMODATION OF H2SO4 (Raes and Van Dingen) |
|---|
| 41 | REAL,SAVE :: ALPH2SO4 ! H2SO4 accommodation coefficient [condensation/evaporation] |
|---|
| 42 | !$OMP THREADPRIVATE(ALPH2SO4) |
|---|
| 43 | |
|---|
| 44 | ! flag to constraint nucleation rate in a lat/pres box |
|---|
| 45 | LOGICAL,SAVE :: flag_nuc_rate_box ! Nucleation rate limit or not to a lat/pres |
|---|
| 46 | !$OMP THREADPRIVATE(flag_nuc_rate_box) |
|---|
| 47 | REAL,SAVE :: nuclat_min ! min lat to activate nuc rate |
|---|
| 48 | REAL,SAVE :: nuclat_max ! max lat to activate nuc rate |
|---|
| 49 | REAL,SAVE :: nucpres_min ! min pres to activate nuc rate |
|---|
| 50 | REAL,SAVE :: nucpres_max ! max pres to activate nuc rate |
|---|
| 51 | !$OMP THREADPRIVATE(nuclat_min, nuclat_max, nucpres_min, nucpres_max) |
|---|
| 52 | |
|---|
| 53 | LOGICAL,SAVE :: ok_qemiss |
|---|
| 54 | !$OMP THREADPRIVATE(ok_qemiss) |
|---|
| 55 | INTEGER,SAVE :: flh2o ! ds stratemit : flh2o =0 (tr_seri), flh2o=1 (dq) |
|---|
| 56 | !$OMP THREADPRIVATE(flh2o) |
|---|
| 57 | |
|---|
| 58 | REAL,ALLOCATABLE,SAVE :: budg_emi(:,:) !DIMENSION(klon,n) |
|---|
| 59 | !$OMP THREADPRIVATE(budg_emi) |
|---|
| 60 | |
|---|
| 61 | |
|---|
| 62 | !============= EMISSION VARS ============= |
|---|
| 63 | !--flag_emit=1 OR == 4 -- Volcanic eruption(s) |
|---|
| 64 | INTEGER,SAVE :: nErupt ! number of eruptions specs |
|---|
| 65 | REAL,SAVE :: injdur ! volcanic injection duration |
|---|
| 66 | !$OMP THREADPRIVATE(nErupt, injdur) |
|---|
| 67 | INTEGER,ALLOCATABLE,SAVE :: year_emit_vol(:) ! year of emission date |
|---|
| 68 | INTEGER,ALLOCATABLE,SAVE :: mth_emit_vol(:) ! month of emission date |
|---|
| 69 | INTEGER,ALLOCATABLE,SAVE :: day_emit_vol(:) ! day of emission date |
|---|
| 70 | !$OMP THREADPRIVATE(year_emit_vol, mth_emit_vol, day_emit_vol) |
|---|
| 71 | REAL,ALLOCATABLE,SAVE :: altemiss_vol(:) ! emission altitude in m |
|---|
| 72 | REAL,ALLOCATABLE,SAVE :: sigma_alt_vol(:) ! standard deviation of emission altitude in m |
|---|
| 73 | !$OMP THREADPRIVATE(altemiss_vol, sigma_alt_vol) |
|---|
| 74 | INTEGER,ALLOCATABLE,SAVE :: ponde_lonlat_vol(:) ! lon/lat ponderation factor |
|---|
| 75 | REAL,ALLOCATABLE,SAVE :: xlat_min_vol(:) ! min latitude of volcano in degree |
|---|
| 76 | REAL,ALLOCATABLE,SAVE :: xlat_max_vol(:) ! max latitude of volcano in degree |
|---|
| 77 | REAL,ALLOCATABLE,SAVE :: xlon_min_vol(:) ! min longitude of volcano in degree |
|---|
| 78 | REAL,ALLOCATABLE,SAVE :: xlon_max_vol(:) ! max longitude of volcano in degree |
|---|
| 79 | !$OMP THREADPRIVATE(ponde_lonlat_vol, xlat_min_vol, xlat_max_vol, xlon_min_vol, xlon_max_vol) |
|---|
| 80 | |
|---|
| 81 | !--flag_emit=1 |
|---|
| 82 | INTEGER,SAVE :: nAerErupt ! number Aerosol |
|---|
| 83 | !$OMP THREADPRIVATE(nAerErupt) |
|---|
| 84 | REAL,ALLOCATABLE,SAVE :: m_sulf_emiss_vol(:) ! emitted sulfur mass in kgS, e.g. 7Tg(S)=14Tg(SO2) |
|---|
| 85 | REAL,ALLOCATABLE,SAVE :: m_aer_emiss_vol(:,:) |
|---|
| 86 | !$OMP THREADPRIVATE(m_sulf_emiss_vol,m_aer_emiss_vol) |
|---|
| 87 | |
|---|
| 88 | !--flag_emit=2 --SAI |
|---|
| 89 | REAL,SAVE :: m_aer_emiss_sai ! emitted sulfur mass in kgS, eg 1e9=1TgS, 1e10=10TgS |
|---|
| 90 | REAL,SAVE :: altemiss_sai ! emission altitude in m |
|---|
| 91 | REAL,SAVE :: sigma_alt_sai ! standard deviation of emission altitude in m |
|---|
| 92 | !$OMP THREADPRIVATE(m_aer_emiss_sai, altemiss_sai, sigma_alt_sai) |
|---|
| 93 | INTEGER,SAVE :: year_emit_sai_start |
|---|
| 94 | INTEGER,SAVE :: year_emit_sai_end |
|---|
| 95 | INTEGER,SAVE :: mth_emit_sai_start |
|---|
| 96 | INTEGER,SAVE :: mth_emit_sai_end |
|---|
| 97 | INTEGER,SAVE :: day_emit_sai_start |
|---|
| 98 | INTEGER,SAVE :: day_emit_sai_end |
|---|
| 99 | !$OMP THREADPRIVATE(year_emit_sai_start, year_emit_sai_end) |
|---|
| 100 | !$OMP THREADPRIVATE(mth_emit_sai_start, mth_emit_sai_end) |
|---|
| 101 | !$OMP THREADPRIVATE(day_emit_sai_start, day_emit_sai_end) |
|---|
| 102 | REAL,SAVE :: xlat_sai ! latitude of SAI in degree |
|---|
| 103 | REAL,SAVE :: xlon_sai ! longitude of SAI in degree |
|---|
| 104 | !$OMP THREADPRIVATE(xlat_sai, xlon_sai) |
|---|
| 105 | |
|---|
| 106 | !--flag_emit=3 -- SAI |
|---|
| 107 | REAL,SAVE :: xlat_max_sai ! maximum latitude of SAI in degrees |
|---|
| 108 | REAL,SAVE :: xlat_min_sai ! minimum latitude of SAI in degrees |
|---|
| 109 | !$OMP THREADPRIVATE(xlat_min_sai,xlat_max_sai) |
|---|
| 110 | |
|---|
| 111 | !--flag_emit=4 -- volc species |
|---|
| 112 | INTEGER,SAVE :: nSpeciesErupt ! number of species Repr |
|---|
| 113 | INTEGER,ALLOCATABLE,SAVE :: id_species(:) ! indice species Repr |
|---|
| 114 | REAL,ALLOCATABLE,SAVE :: m_species_emiss_vol(:,:) ! emitted species |
|---|
| 115 | !$OMP THREADPRIVATE(nSpeciesErupt,id_species,m_species_emiss_vol) |
|---|
| 116 | INTEGER,ALLOCATABLE,SAVE :: id_HCl |
|---|
| 117 | INTEGER,ALLOCATABLE,SAVE :: id_HBr |
|---|
| 118 | INTEGER,ALLOCATABLE,SAVE :: id_NOx |
|---|
| 119 | INTEGER,ALLOCATABLE,SAVE :: id_H2O |
|---|
| 120 | !$OMP THREADPRIVATE(id_HCl,id_HBr,id_NOx,id_H2O) |
|---|
| 121 | REAL,ALLOCATABLE,SAVE :: m_Chlore_emiss_vol(:) ! emitted Chlore mass |
|---|
| 122 | REAL,ALLOCATABLE,SAVE :: m_Brome_emiss_vol(:) ! emitted Brome mass |
|---|
| 123 | REAL,ALLOCATABLE,SAVE :: m_NOx_emiss_vol(:) ! emitted NOx mass |
|---|
| 124 | REAL,ALLOCATABLE,SAVE :: m_H2O_emiss_vol(:) ! emitted H2O mass |
|---|
| 125 | REAL,ALLOCATABLE,SAVE :: m_H2O_emiss_vol_daily(:) |
|---|
| 126 | !$OMP THREADPRIVATE(m_Chlore_emiss_vol,m_Brome_emiss_vol,m_NOx_emiss_vol,m_H2O_emiss_vol) |
|---|
| 127 | !$OMP THREADPRIVATE(m_H2O_emiss_vol_daily) |
|---|
| 128 | |
|---|
| 129 | !--flag_emit=5 -- Rockets Emitted |
|---|
| 130 | INTEGER, SAVE :: ifreqroc ! frequence (=2 ex: tous les 2 mois) |
|---|
| 131 | !$OMP THREADPRIVATE(ifreqroc) |
|---|
| 132 | INTEGER,ALLOCATABLE,SAVE :: day_emit_roc(:) ! day of emission date |
|---|
| 133 | !$OMP THREADPRIVATE(day_emit_roc) |
|---|
| 134 | |
|---|
| 135 | REAL,ALLOCATABLE,SAVE :: RRSI(:) ! radius [cm] for each aerosol size |
|---|
| 136 | REAL,ALLOCATABLE,SAVE :: Vbin(:) ! volume [m3] for each aerosol size |
|---|
| 137 | !$OMP THREADPRIVATE(RRSI, Vbin) |
|---|
| 138 | REAL,SAVE :: dlat, dlon ! delta latitude and d longitude of grid in degree |
|---|
| 139 | !$OMP THREADPRIVATE(dlat, dlon) |
|---|
| 140 | |
|---|
| 141 | CONTAINS |
|---|
| 142 | |
|---|
| 143 | SUBROUTINE strataer_init() |
|---|
| 144 | USE ioipsl_getin_p_mod, ONLY : getin_p |
|---|
| 145 | USE print_control_mod, ONLY : lunout |
|---|
| 146 | USE mod_phys_lmdz_para, ONLY : is_master |
|---|
| 147 | USE infotrac_phy, ONLY: id_OCS_strat,id_SO2_strat,id_H2SO4_strat,nbtr_sulgas,nbtr_bin |
|---|
| 148 | USE phys_local_var_mod, ONLY : mdw,R2SO4,R2SO4B,DENSO4,DENSO4B,f_r_wet,f_r_wetB |
|---|
| 149 | USE aerophys, ONLY: mdwmin, V_rat |
|---|
| 150 | USE yomcst_mod_h , ONLY : RPI |
|---|
| 151 | |
|---|
| 152 | INTEGER :: it |
|---|
| 153 | |
|---|
| 154 | WRITE(lunout,*) 'IN STRATAER_LOCAL_VAR INIT WELCOME!' |
|---|
| 155 | |
|---|
| 156 | !============= Check Sulfur aerosols ID ============= |
|---|
| 157 | WRITE(lunout,*) 'STRATAER_LOCAL_VAR INIT: id_OCS_strat=',id_OCS_strat,' id_SO2_strat=',id_SO2_strat,' id_H2SO4_strat=',id_H2SO4_strat |
|---|
| 158 | |
|---|
| 159 | IF(id_OCS_strat < 0 .OR. id_OCS_strat > nbtr_sulgas) THEN |
|---|
| 160 | WRITE(lunout,*) 'ERROR : OCS index id_OCS_strat=',id_OCS_strat,' is negative or superior than the total sulfur gases !' |
|---|
| 161 | CALL abort_physic('strataer_local_var_mod','Wrong OCS index, check your tracer.def file.',1) |
|---|
| 162 | ELSEIF(id_SO2_strat < 0 .OR. id_SO2_strat > nbtr_sulgas) THEN |
|---|
| 163 | WRITE(lunout,*) 'ERROR : SO2 index id_SO2_strat=',id_SO2_strat,' is negative or superior than the total sulfur gases !' |
|---|
| 164 | CALL abort_physic('strataer_local_var_mod','Wrong SO2 index, check your tracer.def file.',1) |
|---|
| 165 | ELSEIF(id_H2SO4_strat < 0 .OR. id_H2SO4_strat > nbtr_sulgas) THEN |
|---|
| 166 | WRITE(lunout,*) 'ERROR : H2SO4 index id_H2SO4_strat=',id_H2SO4_strat,' is negative or superior than the total sulfur gases !' |
|---|
| 167 | CALL abort_physic('strataer_local_var_mod','Wrong H2SO4 index, check your tracer.def file.',1) |
|---|
| 168 | ENDIF |
|---|
| 169 | |
|---|
| 170 | !============= Init params ============= |
|---|
| 171 | flag_emit = 0 ! Background (default) |
|---|
| 172 | flag_emit_distrib = 0 ! Gaussian (default) |
|---|
| 173 | flag_nucl = 2 ! Define nucleation routine (default: A. Maattanen - LATMOS) |
|---|
| 174 | flag_verbose_strataer = .FALSE. ! verbose mode |
|---|
| 175 | flag_OH_reduced = .FALSE. ! OH reduce (default: No) |
|---|
| 176 | flag_H2SO4_photolysis = .FALSE. ! H2SO4 photolysis (default: No) |
|---|
| 177 | flag_strat_compo = 2 ! H2SO4/H2O composition routine (default: Tabazadeh et al. 1997) |
|---|
| 178 | ok_qemiss = .FALSE. ! H2O emission flag |
|---|
| 179 | |
|---|
| 180 | ! nuc init |
|---|
| 181 | ALPH2SO4 = 0.1 |
|---|
| 182 | flag_nuc_rate_box = .FALSE. |
|---|
| 183 | nuclat_min=0 ; nuclat_max=0 |
|---|
| 184 | nucpres_min=0 ; nucpres_max=0 |
|---|
| 185 | |
|---|
| 186 | ! emiss init |
|---|
| 187 | nErupt = 0 ! eruption number |
|---|
| 188 | injdur = 0 ! init injection duration |
|---|
| 189 | nAerErupt = 1 ; nSpeciesErupt = 1 |
|---|
| 190 | ifreqroc=2 ; flh2o=0 |
|---|
| 191 | |
|---|
| 192 | ! array init |
|---|
| 193 | mdw(:)=0. |
|---|
| 194 | R2SO4(:,:)=0. |
|---|
| 195 | R2SO4B(:,:,:)=0. |
|---|
| 196 | DENSO4(:,:)=0. |
|---|
| 197 | DENSO4B(:,:,:)=0. |
|---|
| 198 | f_r_wet(:,:)=0. |
|---|
| 199 | f_r_wetB(:,:,:)=0. |
|---|
| 200 | |
|---|
| 201 | !============= Read params ============= |
|---|
| 202 | CALL getin_p('flag_emit',flag_emit) |
|---|
| 203 | CALL getin_p('flag_emit_distrib',flag_emit_distrib) |
|---|
| 204 | CALL getin_p('flag_verbose_strataer',flag_verbose_strataer) |
|---|
| 205 | CALL getin_p('flag_nucl',flag_nucl) |
|---|
| 206 | CALL getin_p('flag_OH_reduced',flag_OH_reduced) |
|---|
| 207 | CALL getin_p('flag_H2SO4_photolysis',flag_H2SO4_photolysis) |
|---|
| 208 | CALL getin_p('flag_strat_compo',flag_strat_compo) |
|---|
| 209 | CALL getin_p('ok_qemiss',ok_qemiss) |
|---|
| 210 | |
|---|
| 211 | !============= Print params ============= |
|---|
| 212 | IF (is_master) THEN |
|---|
| 213 | WRITE(lunout,*) 'flag_emit = ',flag_emit |
|---|
| 214 | WRITE(lunout,*) 'IN STRATAER : flag_nucl = ',flag_nucl |
|---|
| 215 | WRITE(lunout,*) 'IN STRATAER : flag_emit_distrib = ',flag_emit_distrib |
|---|
| 216 | WRITE(lunout,*) 'IN STRATAER : flag_verbose_strataer = ',flag_verbose_strataer |
|---|
| 217 | IF (flag_emit == 1 .OR. flag_emit == 4) THEN |
|---|
| 218 | WRITE(lunout,*) 'IN STRATAER : flag_OH_reduced = ',flag_OH_reduced |
|---|
| 219 | WRITE(lunout,*) 'IN STRATAER : flag_H2SO4_photolysis = ',flag_H2SO4_photolysis |
|---|
| 220 | WRITE(lunout,*) 'IN STRATAER : flag_strat_compo = ',flag_strat_compo |
|---|
| 221 | WRITE(lunout,*) 'IN STRATAER : ok_qemiss = ',ok_qemiss |
|---|
| 222 | ENDIF |
|---|
| 223 | ENDIF ! if master |
|---|
| 224 | |
|---|
| 225 | !--initialising dry diameters to geometrically spaced mass/volume (see Jacobson 1994) |
|---|
| 226 | IF(nbtr_bin < 3) THEN |
|---|
| 227 | WRITE(lunout,*) 'WARNING: There are less than 3 sulfur aerosol class, it could be a problem for StratAer usage !' |
|---|
| 228 | WRITE(lunout,*) 'NBTR_BIN=',nbtr_bin |
|---|
| 229 | ELSE |
|---|
| 230 | mdw(1)=mdwmin |
|---|
| 231 | IF (V_rat.LT.1.62) THEN ! compensate for dip in second bin for lower volume ratio |
|---|
| 232 | mdw(2)=mdw(1)*2.**(1./3.) |
|---|
| 233 | DO it=3, nbtr_bin |
|---|
| 234 | mdw(it)=mdw(it-1)*V_rat**(1./3.) |
|---|
| 235 | ENDDO |
|---|
| 236 | ELSE |
|---|
| 237 | DO it=2, nbtr_bin |
|---|
| 238 | mdw(it)=mdw(it-1)*V_rat**(1./3.) |
|---|
| 239 | ENDDO |
|---|
| 240 | ENDIF |
|---|
| 241 | IF (is_master) WRITE(lunout,*) 'init mdw=', mdw |
|---|
| 242 | ENDIF |
|---|
| 243 | |
|---|
| 244 | ! compute particle radius RRSI [cm] and volume Vbin [m3] from diameter mdw [m] |
|---|
| 245 | ALLOCATE(RRSI(nbtr_bin), Vbin(nbtr_bin)) |
|---|
| 246 | |
|---|
| 247 | DO it=1,nbtr_bin |
|---|
| 248 | ! [cm] |
|---|
| 249 | RRSI(it)=mdw(it)/2.*100. |
|---|
| 250 | ! [m3] |
|---|
| 251 | Vbin(it)=4.0*RPI*((mdw(it)/2.)**3)/3.0 |
|---|
| 252 | ENDDO |
|---|
| 253 | |
|---|
| 254 | IF (is_master) THEN |
|---|
| 255 | WRITE(lunout,*) 'init RRSI=', RRSI |
|---|
| 256 | WRITE(lunout,*) 'init Vbin=', Vbin |
|---|
| 257 | ENDIF |
|---|
| 258 | |
|---|
| 259 | WRITE(lunout,*) 'IN STRATAER INIT END' |
|---|
| 260 | |
|---|
| 261 | END SUBROUTINE strataer_init |
|---|
| 262 | |
|---|
| 263 | END MODULE strataer_local_var_mod |
|---|