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

Last change on this file since 4767 was 4767, checked in by lguez, 6 months ago

Bug fix: do not assign to day_emit_roc

day_emit_roc is never allocated, nor used, in LMDZ.

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