source: LMDZ6/trunk/libf/phylmd/StratAer/strataer_local_var_mod.F90 @ 4601

Last change on this file since 4601 was 4601, checked in by dcugnet, 11 months ago

StratAer? commit, N. Lebas

File size: 11.7 KB
Line 
1! $Id: strataer_local_var_mod.F90 2022-10-17 19:39:09Z nlebas $
2MODULE strataer_local_var_mod
3! This module contains strato microphysic model parameters & variables
4 
5  IMPLICIT NONE
6 
7  !============= GENERAL PARAMS =============
8  !flag for type emission scenario: (0) background aer ; (1) volcanic eruption with Sulfur ;
9  !(2,3) strato aer injections (SAI) ; (4) volcanic eruption chimistry; (5) rocket
10  INTEGER,SAVE :: flag_emit
11  !$OMP THREADPRIVATE(flag_emit)
12 
13  ! flag for emission altitude distribution: (0) gaussian; (1) uniform
14  INTEGER,SAVE :: flag_emit_distrib
15  !$OMP THREADPRIVATE(flag_emit_distrib)
16 
17  ! flag to choose nucleation nucleation method
18  LOGICAL,SAVE :: flag_new_nucl   ! T=new routine from A. Maattanen (LATMOS), F=older routine from H. Vehkamäki (FMI)
19  !$OMP THREADPRIVATE(flag_new_nucl)
20 
21  ! Use relative humidity from 2D model stratospheric H2O because LMDz is too dry in the stratosphere
22  ! (no CH4 oxidation)
23  LOGICAL,SAVE :: flag_H2O2d_nucleation
24  !$OMP THREADPRIVATE(flag_H2O2d_nucleation)
25 
26  ! OH reduction from SO2. OH is reduced when its reaction with SO2 competes sufficiently with its reaction
27  ! with O3 (Bekki, 1995). As a result, SO2 lifetime is extended. 2D model O3 climatologies are needed.
28  LOGICAL,SAVE :: flag_OH_reduced
29  !$OMP THREADPRIVATE(flag_OH_reduced)
30 
31  ! H2SO4 photolysis: H2SO4 is converted into SO2 by complex photolytic processes. Here simplified approach
32  ! by setting H2SO4 cross-sections = 0.3*HCl cross-sections (Rinsland et al., 1995)
33  LOGICAL,SAVE :: flag_H2SO4_photolysis
34  !$OMP THREADPRIVATE(flag_H2SO4_photolysis)
35 
36  ! flag for minimum lifetime (=1.5 pdt phys)
37  LOGICAL,SAVE :: flag_min_rreduce
38  !$OMP THREADPRIVATE(flag_min_rreduce)
39 
40  ! flag to read new climato (O3, H2O & H2SO4_LIFET)
41  LOGICAL,SAVE :: flag_newclim_file
42  !$OMP THREADPRIVATE(flag_newclim_file)
43 
44  ! Verbose mode to get more print info
45  LOGICAL, SAVE :: flag_verbose_strataer
46  !$OMP THREADPRIVATE(flag_verbose_strataer)
47 
48 
49  !============= NUCLEATION VARS =============
50  ! flag to constraint nucleation rate in a lat/pres box
51  LOGICAL,SAVE :: flag_nuc_rate_box      ! Nucleation rate limit or not to a lat/pres
52  !$OMP THREADPRIVATE(flag_nuc_rate_box)
53  REAL,SAVE    :: nuclat_min             ! min lat to activate nuc rate
54  REAL,SAVE    :: nuclat_max             ! max lat to activate nuc rate
55  REAL,SAVE    :: nucpres_min            ! min pres to activate nuc rate
56  REAL,SAVE    :: nucpres_max            ! max pres to activate nuc rate
57  !$OMP THREADPRIVATE(nuclat_min, nuclat_max, nucpres_min, nucpres_max)
58
59  LOGICAL,SAVE :: ok_qemiss
60  !$OMP THREADPRIVATE(ok_qemiss)
61  INTEGER,SAVE :: flh2o  ! ds stratemit : flh2o =0 (tr_seri), flh2o=1 (dq)
62  !$OMP THREADPRIVATE(flh2o)
63!  REAL,ALLOCATABLE,SAVE    :: d_q_emiss(:,:)
64!  !$OMP THREADPRIVATE(d_q_emiss)
65 
66  REAL,ALLOCATABLE,SAVE    :: budg_emi(:,:)            !DIMENSION(klon,n)
67  !$OMP THREADPRIVATE(budg_emi)
68 
69 
70  !============= EMISSION VARS =============
71  !--flag_emit=1 OR == 4 -- Volcanic eruption(s)
72  INTEGER,SAVE             :: nErupt                    ! number of eruptions specs
73  REAL,SAVE                :: injdur                    ! volcanic injection duration
74  !$OMP THREADPRIVATE(nErupt, injdur)
75  INTEGER,ALLOCATABLE,SAVE :: year_emit_vol(:)          ! year of emission date
76  INTEGER,ALLOCATABLE,SAVE :: mth_emit_vol(:)           ! month of emission date
77  INTEGER,ALLOCATABLE,SAVE :: day_emit_vol(:)           ! day of emission date
78  !$OMP THREADPRIVATE(year_emit_vol, mth_emit_vol, day_emit_vol)
79  REAL,ALLOCATABLE,SAVE    :: altemiss_vol(:)           ! emission altitude in m
80  REAL,ALLOCATABLE,SAVE    :: sigma_alt_vol(:)          ! standard deviation of emission altitude in m
81  !$OMP THREADPRIVATE(altemiss_vol, sigma_alt_vol)
82  INTEGER,ALLOCATABLE,SAVE :: ponde_lonlat_vol(:)       ! lon/lat ponderation factor
83  REAL,ALLOCATABLE,SAVE    :: xlat_min_vol(:)           ! min latitude of volcano in degree
84  REAL,ALLOCATABLE,SAVE    :: xlat_max_vol(:)           ! max latitude of volcano in degree
85  REAL,ALLOCATABLE,SAVE    :: xlon_min_vol(:)           ! min longitude of volcano in degree
86  REAL,ALLOCATABLE,SAVE    :: xlon_max_vol(:)           ! max longitude of volcano in degree
87  !$OMP THREADPRIVATE(ponde_lonlat_vol, xlat_min_vol, xlat_max_vol, xlon_min_vol, xlon_max_vol)
88 
89  !--flag_emit=1
90  INTEGER,SAVE             :: nAerErupt                 ! number Aerosol
91  !$OMP THREADPRIVATE(nAerErupt)
92  REAL,ALLOCATABLE,SAVE    :: m_sulf_emiss_vol(:)        ! emitted sulfur mass in kgS, e.g. 7Tg(S)=14Tg(SO2)
93  REAL,ALLOCATABLE,SAVE    :: m_aer_emiss_vol(:,:)
94  !$OMP THREADPRIVATE(m_sulf_emiss_vol,m_aer_emiss_vol)
95 
96  !--flag_emit=2 --SAI
97  REAL,SAVE    :: m_aer_emiss_sai        ! emitted sulfur mass in kgS, eg 1e9=1TgS, 1e10=10TgS
98  REAL,SAVE    :: altemiss_sai           ! emission altitude in m
99  REAL,SAVE    :: sigma_alt_sai          ! standard deviation of emission altitude in m
100  !$OMP THREADPRIVATE(m_aer_emiss_sai, altemiss_sai, sigma_alt_sai)
101  REAL,SAVE    :: xlat_sai               ! latitude of SAI in degree
102  REAL,SAVE    :: xlon_sai               ! longitude of SAI in degree
103  !$OMP THREADPRIVATE(xlat_sai, xlon_sai)
104 
105  !--flag_emit=3 -- SAI
106  REAL,SAVE    :: xlat_max_sai           ! maximum latitude of SAI in degrees
107  REAL,SAVE    :: xlat_min_sai           ! minimum latitude of SAI in degrees
108  !$OMP THREADPRIVATE(xlat_min_sai,xlat_max_sai)
109 
110  !--flag_emit=4 -- volc species
111  INTEGER,SAVE             :: nSpeciesErupt            ! number of species Repr
112  INTEGER,ALLOCATABLE,SAVE :: id_species(:)            ! indice species Repr
113  REAL,ALLOCATABLE,SAVE    :: m_species_emiss_vol(:,:) ! emitted species
114  !$OMP THREADPRIVATE(nSpeciesErupt,id_species,m_species_emiss_vol)
115  INTEGER,ALLOCATABLE,SAVE :: id_HCl
116  INTEGER,ALLOCATABLE,SAVE :: id_HBr
117  INTEGER,ALLOCATABLE,SAVE :: id_NOx
118  INTEGER,ALLOCATABLE,SAVE :: id_H2O
119  !$OMP THREADPRIVATE(id_HCl,id_HBr,id_NOx,id_H2O)
120  REAL,ALLOCATABLE,SAVE    :: m_Chlore_emiss_vol(:)   ! emitted Chlore mass
121  REAL,ALLOCATABLE,SAVE    :: m_Brome_emiss_vol(:)    ! emitted Brome mass
122  REAL,ALLOCATABLE,SAVE    :: m_NOx_emiss_vol(:)      ! emitted NOx mass
123  REAL,ALLOCATABLE,SAVE    :: m_H2O_emiss_vol(:)      ! emitted H2O mass
124  REAL,ALLOCATABLE,SAVE    :: m_H2O_emiss_vol_daily(:)
125  !$OMP THREADPRIVATE(m_Chlore_emiss_vol,m_Brome_emiss_vol,m_NOx_emiss_vol,m_H2O_emiss_vol)
126  !$OMP THREADPRIVATE(m_H2O_emiss_vol_daily)
127 
128  !--flag_emit=5 -- Rockets Emitted
129  INTEGER, SAVE            :: ifreqroc        ! frequence (=2 ex: tous les 2 mois)
130  !$OMP THREADPRIVATE(ifreqroc)
131  INTEGER,ALLOCATABLE,SAVE :: day_emit_roc(:) ! day of emission date
132  !$OMP THREADPRIVATE(day_emit_roc)
133 
134  REAL,SAVE    :: dlat, dlon             ! delta latitude and d longitude of grid in degree
135  !$OMP THREADPRIVATE(dlat, dlon)
136 
137CONTAINS
138   
139  SUBROUTINE strataer_init()
140    USE ioipsl_getin_p_mod, ONLY : getin_p
141    USE print_control_mod, ONLY : lunout
142    USE mod_phys_lmdz_para, ONLY : is_master
143    USE infotrac_phy, ONLY: id_OCS_strat,id_SO2_strat,id_H2SO4_strat,nbtr_sulgas
144   
145    WRITE(lunout,*) 'IN STRATAER_LOCAL_VAR INIT WELCOME!'
146   
147    !============= Check Sulfur aerosols ID =============
148    WRITE(lunout,*) 'STRATAER_LOCAL_VAR INIT: id_OCS_strat=',id_OCS_strat,' id_SO2_strat=',id_SO2_strat,' id_H2SO4_strat=',id_H2SO4_strat
149   
150    IF(id_OCS_strat < 0 .OR. id_OCS_strat > nbtr_sulgas) THEN
151       WRITE(lunout,*) 'ERROR : OCS index id_OCS_strat=',id_OCS_strat,' is negative or superior than the total sulfur gases !'
152       CALL abort_physic('strataer_local_var_mod','Wrong OCS index, check your tracer.def file.',1)
153    ELSEIF(id_SO2_strat < 0 .OR. id_SO2_strat > nbtr_sulgas) THEN
154       WRITE(lunout,*) 'ERROR : SO2 index id_SO2_strat=',id_SO2_strat,' is negative or superior than the total sulfur gases !'
155       CALL abort_physic('strataer_local_var_mod','Wrong SO2 index, check your tracer.def file.',1)
156    ELSEIF(id_H2SO4_strat < 0 .OR. id_H2SO4_strat > nbtr_sulgas) THEN
157       WRITE(lunout,*) 'ERROR : H2SO4 index id_H2SO4_strat=',id_H2SO4_strat,' is negative or superior than the total sulfur gases !'
158       CALL abort_physic('strataer_local_var_mod','Wrong H2SO4 index, check your tracer.def file.',1)
159    ENDIF
160   
161    !============= Init params =============
162    flag_emit = 0                   ! Background (default)
163    flag_emit_distrib = 0           ! Gaussian (default)
164    flag_new_nucl = .TRUE.          ! Define nucleation routine (default: A. Maattanen - LATMOS)
165    flag_verbose_strataer = .FALSE. ! verbose mode
166    flag_newclim_file = .TRUE.      ! Define input climato file (default: all climato)
167    flag_H2O2d_nucleation = .FALSE. ! Use H2O 2D climato (default: No)
168    flag_OH_reduced = .FALSE.       ! OH reduce (default: No)
169    flag_H2SO4_photolysis = .FALSE. ! H2SO4 photolysis (default: No)
170    flag_min_rreduce = .TRUE.       ! Minimum lifetime=1.5 pdt phys (default: Yes)
171    ok_qemiss = .FALSE.             ! H2O emission flag
172   
173    ! nuc init
174    flag_nuc_rate_box = .FALSE.
175    nuclat_min=0  ; nuclat_max=0
176    nucpres_min=0 ; nucpres_max=0
177   
178    ! emiss init
179    nErupt = 0 ! eruption number
180    injdur = 0 ! init injection duration
181    nAerErupt = 1 ; nSpeciesErupt = 1 ; id_species = 3
182    year_emit_vol=0 ; mth_emit_vol=0 ; day_emit_vol=0
183    m_species_emiss_vol=0. ; m_aer_emiss_vol=0. ; m_sulf_emiss_vol=0.
184    altemiss_vol=0. ; sigma_alt_vol=0.
185    xlon_min_vol=0. ; xlon_max_vol=0.
186    xlat_min_vol=0. ; xlat_max_vol=0.
187    m_Chlore_emiss_vol=0. ; m_Brome_emiss_vol=0.
188    m_NOx_emiss_vol=0. ; m_H2O_emiss_vol=0.
189    day_emit_roc=0 ; ifreqroc=2 ; flh2o=0
190   
191    !============= Read params =============
192    CALL getin_p('flag_emit',flag_emit)
193    CALL getin_p('flag_emit_distrib',flag_emit_distrib)
194    CALL getin_p('flag_verbose_strataer',flag_verbose_strataer)
195    CALL getin_p('flag_new_nucl',flag_new_nucl)
196    CALL getin_p('flag_newclim_file',flag_newclim_file)
197    CALL getin_p('flag_H2O2d_nucleation',flag_H2O2d_nucleation)
198    CALL getin_p('flag_OH_reduced',flag_OH_reduced)
199    CALL getin_p('flag_H2SO4_photolysis',flag_H2SO4_photolysis)
200    CALL getin_p('flag_min_rreduce',flag_min_rreduce)
201    CALL getin_p('ok_qemiss',ok_qemiss)
202   
203    !============= Test flag coherence =============
204    IF (.NOT. flag_newclim_file) THEN
205       IF (flag_H2SO4_photolysis .OR. flag_OH_reduced .OR. flag_H2O2d_nucleation) THEN
206          WRITE(lunout,*) 'ERROR : flag_newclim_file=',flag_newclim_file, &
207               ' whereas flag_H2SO4_photolysis=',flag_H2SO4_photolysis,', flag_OH_reduced=',flag_OH_reduced, &
208               ' and flag_H2O2d_nucleation=',flag_H2O2d_nucleation
209          CALL abort_physic('strataer_local_var_mod','Incompatible options in physiq_def file !',1)
210       ENDIF
211       IF(flag_min_rreduce) THEN
212          WRITE(lunout,*) 'Warning : flag_min_rreduce will be ignored with old climato file !'
213       ENDIF
214    ENDIF
215   
216    !============= Print params =============
217    IF (is_master) THEN
218       WRITE(lunout,*) 'flag_emit = ',flag_emit
219       WRITE(lunout,*) 'IN STRATAER : flag_new_nucl = ',flag_new_nucl
220       WRITE(lunout,*) 'IN STRATAER : flag_newclim_file = ',flag_newclim_file
221       WRITE(lunout,*) 'IN STRATAER : flag_emit_distrib = ',flag_emit_distrib
222       WRITE(lunout,*) 'IN STRATAER : flag_verbose_strataer = ',flag_verbose_strataer
223       IF (flag_emit == 1 .OR. flag_emit == 4) THEN
224          WRITE(lunout,*) 'IN STRATAER : flag_H2O2d_nucleation = ',flag_H2O2d_nucleation
225          WRITE(lunout,*) 'IN STRATAER : flag_OH_reduced = ',flag_OH_reduced
226          WRITE(lunout,*) 'IN STRATAER : flag_H2SO4_photolysis = ',flag_H2SO4_photolysis
227          WRITE(lunout,*) 'IN STRATAER : flag_min_rreduce = ',flag_min_rreduce
228          WRITE(lunout,*) 'IN STRATAER : ok_qemiss = ',ok_qemiss
229       ENDIF
230    ENDIF ! if master
231   
232    WRITE(lunout,*) 'IN STRATAER INIT END'
233   
234  END SUBROUTINE strataer_init
235 
236END MODULE strataer_local_var_mod
Note: See TracBrowser for help on using the repository browser.