source: trunk/LMDZ.VENUS/libf/phyvenus/phytrac_chimie.F @ 3764

Last change on this file since 3764 was 3764, checked in by flefevre, 6 weeks ago

Implementation of ClSO2 + Cl -> Cl2SO2

  • Property svn:executable set to *
File size: 18.7 KB
Line 
1      subroutine phytrac_chimie (
2     $                    debutphy,
3     $                    gmtime,
4     $                    nqmax,
5     $                    nlon,
6     $                    lat,
7     $                    lon,
8     $                    zzlay,
9     $                    nlev,
10     $                    pdtphys,
11     $                    temp,
12     $                    pplay,
13     $                    trac,
14     $                    d_tr_chem,
15     $                    iter,
16     $                    prod_tr,
17     $                    loss_tr,
18     $                    no_emi,
19     $                    o2_emi)
20
21      use chemparam_mod
22      use conc, only: mmean,rnew
23      use photolysis_mod, only: init_photolysis, nphot
24      use iono_h, only: temp_elect
25#ifdef CPP_XIOS     
26      use xios_output_mod, only: send_xios_field
27#endif
28
29      implicit none
30     
31#include "clesphys.h"
32#include "YOMCST.h"
33
34!===================================================================
35!     input
36!===================================================================
37
38      integer :: nlon, nlev                     ! number of gridpoints and levels
39      integer :: nqmax                          ! number of tracers
40
41      real :: gmtime                            ! day fraction
42      real :: pdtphys                           ! phytrac_chimie timestep (s)
43      real, dimension(nlon,nlev) :: temp        ! temperature (k)
44      real, dimension(nlon,nlev) :: pplay       ! pressure (pa)
45      real, dimension(nlon,nlev) :: zzlay       ! altitude (m)
46      real, dimension(nlon,nlev,nqmax) :: trac  ! tracer mass mixing ratio
47
48      logical :: debutphy                       ! first call flag
49
50!===================================================================
51!     output
52!===================================================================
53
54      integer, dimension(nlon,nlev) :: iter                 ! chemical iterations
55      real, dimension(nlon,nlev,nqmax) :: d_tr_chem         ! chemical tendency for each tracer
56      real, dimension(nlon,nlev,nqmax) :: prod_tr, loss_tr  ! production and loss terms (for info)
57      real, dimension(nlon,nlev)    :: no_emi               ! no emission
58      real, dimension(nlon,nlev)    :: o2_emi               ! o2 emission
59
60!===================================================================
61!     local
62!===================================================================
63
64      real :: sza_local     ! solar zenith angle (deg)
65      real :: lon_sun
66      real :: zlocal(nlev)  ! altitude for photochem (km)
67      real :: t_elec(nlev)  ! electron temperature [K]
68     
69      integer, parameter :: t_elec_origin=2
70      !Electronic temperature. Index 1 -> Theis et al. 1980 - model data ; Index 2-> Theis et al. 1984 - model data
71     
72      integer :: i, iq
73      integer :: ilon, ilev
74
75      real  lat(nlon), lat_local(nlon)
76      real  lon(nlon), lon_local(nlon)
77
78      real, dimension(nlon,nlev) :: mrtwv, mrtsa ! total water and total sulfuric acid
79      real, dimension(nlon,nlev) :: mrwv, mrsa   ! gas-phase water and gas-phase sulfuric acid
80      real, dimension(nlon,nlev) :: trac_sum
81      real, dimension(nlon,nlev,nqmax) :: ztrac  ! local tracer mixing ratio
82      real, dimension(nlev) :: no_em
83      real, dimension(nlev) :: o2_em
84
85      integer, save :: nb_reaction_3_max     ! number of quadratic reactions
86      integer, save :: nb_reaction_4_max     ! number of bimolecular reactions
87      integer, save :: nquench               ! number of quenching + heterogeneous reactions
88      integer, save :: nphotion              ! number of photoionizations
89      integer, save :: nb_reaction_4_ion     ! quadratic reactions for ionosphere
90!      integer, save :: nb_reaction_4_deut    ! quadratic reactions for deuterium chem
91      integer, save :: nb_phot_max           ! total number of photolysis+photoionizations+quenching reactions
92
93      ! tracer indexes for the EUV heating:
94!!! ATTENTION. These values have to be identical to those in euvheat.F90
95!!! If the values are changed there, the same has to be done here  !!!
96
97      integer,parameter :: ix_co2  =  1
98      integer,parameter :: ix_co   =  2
99      integer,parameter :: ix_o    =  3
100      integer,parameter :: ix_o1d  =  4
101      integer,parameter :: ix_o2   =  5
102      integer,parameter :: ix_o3   =  6
103      integer,parameter :: ix_h    =  7
104      integer,parameter :: ix_h2   =  8
105      integer,parameter :: ix_oh   =  9
106      integer,parameter :: ix_ho2  = 10
107      integer,parameter :: ix_h2o2 = 11
108      integer,parameter :: ix_h2o  = 12
109      integer,parameter :: ix_n    = 13
110      integer,parameter :: ix_n2d  = 14
111      integer,parameter :: ix_no   = 15
112      integer,parameter :: ix_no2  = 16
113      integer,parameter :: ix_n2   = 17
114
115      ! NEED TO BE THE SAME AS IN EUVHEAT.F90
116      integer,parameter :: nespeuv = 17    ! Number of species considered (11, 12 or 17 (with nitrogen))
117
118      real :: vmr_dens_euv(nlon,nlev,nespeuv) ! local species density for EUV heating
119         
120!===================================================================
121!     first call : initialisations
122!===================================================================
123
124      if (debutphy) then
125     
126!--- Adjustment of Helium amount
127!       if (i_he/=0) then
128!          trac(:,:,i_he)=trac(:,:,i_he)/2.
129!       endif
130!---
131
132!-------------------------------------------------------------------
133!        Determination of chemistry reaction number
134!-------------------------------------------------------------------
135
136         if (ok_chem) then
137
138           ! set number of reactions, depending on ion chemistry or not
139
140           nb_reaction_4_ion  = 64
141           !nb_reaction_4_deut = 35
142   
143           ! default numbers if no ion and no deuterium chemistry
144   
145           nb_reaction_4_max = 99     ! set number of bimolecular reactions
146           nb_reaction_3_max = 14     ! set number of quadratic reactions
147           nquench           = 15     ! set number of first-order reactions:
148                                      !               quenching
149                                      !               thermal dissociation
150                                      !               heterogeneous
151           nphotion          = 0      ! set number of photoionizations
152   
153           if (ok_ionchem) then
154              nb_reaction_4_max = nb_reaction_4_max + nb_reaction_4_ion
155              nphotion       = 18     ! set number of photoionizations
156           endif
157
158           !if(deutchem) then
159           !   nb_reaction_4_max = nb_reaction_4_max + nb_reaction_4_deut 
160           !end if
161   
162           ! nb_phot_max is the total number of processes that are treated
163           ! numerically as a photolysis (first-order reaction):
164   
165           nb_phot_max = nphot + nphotion + nquench
166   
167!-------------------------------------------------------------------
168!        case of tracers re-initialisation with chemistry
169!-------------------------------------------------------------------
170 
171           if (reinit_trac .and. ok_chem) then
172 
173!             convert mass to volume mixing ratio
174              do iq = 1,nqmax - nmicro
175                 trac(:,:,iq) = trac(:,:,iq)*mmean(:,:)/m_tr(iq)
176              end do
177
178              print*, "SO2 is re-initialised"
179
180              if (i_so2 /= 0) then
181                 trac(:,25:,i_so2)  = 100.e-9
182                 trac(:,1:24,i_so2) = 10.e-6
183                 trac(:,25:,i_h2o)  = 1.e-6
184                 trac(:,1:24,i_h2o) = 30.e-6
185
186                 trac(:,:,i_osso_cis)   = 0.
187                 trac(:,:,i_osso_trans) = 0.
188                 trac(:,:,i_s2o2_cyc)   = 0.
189 
190! AL TRACERS!!!!!!!!!!!!!!!!!!!!!!!!!!!!
191!           print*, "Tracers are re-initialised"
192!           trac(:,:,:) = 1.0e-30
193 
194!             if ((i_ocs /= 0) .and. (i_co /= 0) .and. (i_hcl /= 0)
195!     $          .and. (i_so2 /= 0) .and. (i_h2o /= 0)
196!     $          .and. (i_n2 /= 0)  .and. (i_co2 /= 0)) then
197 
198!                trac(:,1:22,i_ocs) = 3.e-6
199!                trac(:,1:22,i_co)  = 25.e-6
200!                trac(:,:,i_hcl)    = 0.4e-6
201!                trac(:,1:22,i_so2) = 7.e-6
202!                trac(:,1:22,i_h2o) = 30.e-6
203!                trac(:,:,i_n2)     = 0.35e-1
204! !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
205     
206!                ensure that sum of mixing ratios = 1
207 
208                 trac_sum(:,:) = 0.
209 
210                 do iq = 1,nqmax - nmicro
211                    if (iq /= i_co2) then
212                       trac_sum(:,:) = trac_sum(:,:) + trac(:,:,iq)
213                    end if
214                 end do
215 
216!                initialise co2
217 
218                 trac(:,:,i_co2) = 1. - trac_sum(:,:)
219 
220              else
221                 write(*,*) "at least one tracer is missing : stop"
222                 stop
223              end if
224         
225!             update mmean
226 
227              mmean(:,:) = 0.
228              do iq = 1,nqmax - nmicro
229                 mmean(:,:) = mmean(:,:)+trac(:,:,iq)*m_tr(iq)
230              enddo
231              rnew(:,:) = 8.314/mmean(:,:)*1.e3     ! J/kg K
232 
233!             convert volume to mass mixing ratio
234 
235              do iq = 1,nqmax - nmicro
236                 trac(:,:,iq) = trac(:,:,iq)*m_tr(iq)/mmean(:,:)
237              end do
238   
239           end if  ! reinit_trac
240
241         end if  ! ok_chem
242
243!-------------------------------------------------------------------
244!        case of detailed microphysics without chemistry
245!-------------------------------------------------------------------
246
247         if (.not. ok_chem .and. ok_cloud .and. cl_scheme == 2) then
248
249!           convert mass to volume mixing ratio
250
251            do iq = 1,nqmax - nmicro
252               ztrac(:,:,iq) = trac(:,:,iq)*mmean(:,:)/m_tr(iq)
253            end do
254         
255!           initialise microphysics
256 
257            call vapors4muphy_ini(nlon,nlev,ztrac)
258
259!           convert volume to mass mixing ratio
260
261            do iq = 1,nqmax - nmicro
262               trac(:,:,iq) = ztrac(:,:,iq)*m_tr(iq)/mmean(:,:)
263            end do
264   
265         end if
266
267      end if  ! debutphy
268
269!===================================================================
270!     convert mass to volume mixing ratio : gas phase
271!===================================================================
272
273      do iq = 1,nqmax - nmicro
274         ztrac(:,:,iq) = max(trac(:,:,iq)*mmean(:,:)/m_tr(iq), 1.e-30)
275      end do
276
277!===================================================================
278!     microphysics: simplified scheme (phd aurelien stolzenbach)
279!===================================================================
280
281      if (ok_cloud .and. cl_scheme == 1) then
282
283!     convert mass to volume mixing ratio : liquid phase
284
285         ztrac(:,:,i_h2so4liq) = max(trac(:,:,i_h2so4liq)
286     $                             *mmean(:,:)/m_tr(i_h2so4liq), 1.e-30)
287         ztrac(:,:,i_h2oliq) = max(trac(:,:,i_h2oliq)
288     $                             *mmean(:,:)/m_tr(i_h2oliq), 1.e-30)
289             
290!     total water and sulfuric acid (gas + liquid)
291
292         mrtwv(:,:) = ztrac(:,:,i_h2o) + ztrac(:,:,i_h2oliq)
293         mrtsa(:,:) = ztrac(:,:,i_h2so4) + ztrac(:,:,i_h2so4liq)
294
295!     all water and sulfuric acid is put in the gas-phase
296
297         mrwv(:,:) = mrtwv(:,:)
298         mrsa(:,:) = mrtsa(:,:)
299
300!     call microphysics
301
302         call new_cloud_venus(nb_mode, nlev, nlon, temp, pplay,
303     $                        mrtwv, mrtsa, mrwv, mrsa)
304
305!     update water vapour and sulfuric acid
306
307         ztrac(:,:,i_h2o) = mrwv(:,:)
308         ztrac(:,:,i_h2oliq) = mrtwv(:,:) - ztrac(:,:,i_h2o)
309     
310         ztrac(:,:,i_h2so4) = mrsa(:,:)
311         ztrac(:,:,i_h2so4liq) = mrtsa(:,:) - ztrac(:,:,i_h2so4)
312
313      end if  ! simplified scheme
314
315!===================================================================
316!     microphysics: detailed scheme (phd sabrina guilbon)
317!     !!! to be confirmed whether mad_muphy expects mmr or vmr for h2o and h2so4
318!===================================================================
319
320      if (ok_cloud .and. cl_scheme == 2) then
321
322         do iq = nqmax-nmicro+1,nqmax
323            ztrac(:,:,iq) = trac(:,:,iq)
324         end do
325
326         do ilon = 1,nlon       
327            do ilev = 1, nlev
328               if (temp(ilon,ilev) < 500.) then
329                  call mad_muphy(pdtphys,                               ! timestep
330     $                           temp(ilon,ilev),pplay(ilon,ilev),      ! temperature and pressure
331     $                           ztrac(ilon,ilev,i_h2o),
332     $                           ztrac(ilon,ilev,i_h2so4),     
333     $                           ztrac(ilon,ilev,i_m0_aer),
334     $                           ztrac(ilon,ilev,i_m3_aer),   
335     $                           ztrac(ilon,ilev,i_m0_mode1drop),
336     $                           ztrac(ilon,ilev,i_m0_mode1ccn),
337     $                           ztrac(ilon,ilev,i_m3_mode1sa),
338     $                           ztrac(ilon,ilev,i_m3_mode1w),   
339     $                           ztrac(ilon,ilev,i_m3_mode1ccn),   
340     $                           ztrac(ilon,ilev,i_m0_mode2drop),
341     $                           ztrac(ilon,ilev,i_m0_mode2ccn),
342     $                           ztrac(ilon,ilev,i_m3_mode2sa),
343     $                           ztrac(ilon,ilev,i_m3_mode2w),
344     $                           ztrac(ilon,ilev,i_m3_mode2ccn))
345               else
346                  ztrac(ilon,ilev,i_m0_aer)       = 0.
347                  ztrac(ilon,ilev,i_m3_aer)       = 0.
348                  ztrac(ilon,ilev,i_m0_mode1drop) = 0.
349                  ztrac(ilon,ilev,i_m0_mode1ccn)  = 0.
350                  ztrac(ilon,ilev,i_m3_mode1sa)   = 0.
351                  ztrac(ilon,ilev,i_m3_mode1w)    = 0.
352                  ztrac(ilon,ilev,i_m3_mode1ccn)  = 0.
353                  ztrac(ilon,ilev,i_m0_mode2drop) = 0.
354                  ztrac(ilon,ilev,i_m0_mode2ccn)  = 0.
355                  ztrac(ilon,ilev,i_m3_mode2sa)   = 0.
356                  ztrac(ilon,ilev,i_m3_mode2w)    = 0.
357                  ztrac(ilon,ilev,i_m3_mode2ccn)  = 0.
358               end if
359            end do
360         end do
361
362      end if  ! detailed scheme
363           
364!===================================================================
365!     photochemistry
366!===================================================================
367
368      if (ok_chem) then
369
370         lon_sun = (0.5 - gmtime)*2.*rpi
371         lon_local(:) = lon(:)*rpi/180.
372         lat_local(:) = lat(:)*rpi/180.
373         
374         if (ok_ionchem) then
375       
376           vmr_dens_euv(:,:,ix_co2) = ztrac(:,:,i_co2)  ! CO2
377           vmr_dens_euv(:,:,ix_co)  = ztrac(:,:,i_co)   ! CO
378           vmr_dens_euv(:,:,ix_o)   = ztrac(:,:,i_o)    ! O
379           vmr_dens_euv(:,:,ix_o1d) = ztrac(:,:,i_o1d)  ! O(1D)
380           vmr_dens_euv(:,:,ix_o2)  = ztrac(:,:,i_o2)   ! O2
381           vmr_dens_euv(:,:,ix_o3)  = ztrac(:,:,i_o3)   ! O3
382           vmr_dens_euv(:,:,ix_h)   = ztrac(:,:,i_h)    ! H
383           vmr_dens_euv(:,:,ix_h2)  = ztrac(:,:,i_h2)   ! H2
384           vmr_dens_euv(:,:,ix_oh)  = ztrac(:,:,i_oh)   ! OH
385           vmr_dens_euv(:,:,ix_ho2) = ztrac(:,:,i_ho2)  ! HO2
386           vmr_dens_euv(:,:,ix_h2o2)= ztrac(:,:,i_h2o2) ! H2O2
387           vmr_dens_euv(:,:,ix_h2o) = ztrac(:,:,i_h2o)  ! H2O
388           vmr_dens_euv(:,:,ix_n)   = ztrac(:,:,i_n)    ! N
389           vmr_dens_euv(:,:,ix_n2d) = ztrac(:,:,i_n2d)  ! N(2D)
390           vmr_dens_euv(:,:,ix_no)  = ztrac(:,:,i_no)   ! NO
391           vmr_dens_euv(:,:,ix_no2) = ztrac(:,:,i_no2)  ! NO2
392           vmr_dens_euv(:,:,ix_n2)  = ztrac(:,:,i_n2)   ! N2
393           
394         end if
395         
396         do ilon = 1,nlon
397            zlocal(:)=zzlay(ilon,:)/1000.
398                       
399!           solar zenith angle
400!            sza_local = acos(cos(lat_local(ilon))*cos(lon_local(ilon))
401!     $                 *cos(lon_sun) + cos(lat_local(ilon))
402!     $                 *sin(lon_local(ilon))*sin(lon_sun))*180./rpi
403
404            sza_local = cos(lat_local(ilon))*cos(lon_local(ilon))
405     $                 *cos(lon_sun) + cos(lat_local(ilon))
406     $                 *sin(lon_local(ilon))*sin(lon_sun)
407
408            ! Security - Handle rare cases where |sza_local| > 1
409            sza_local = min(sza_local,1.)
410            sza_local = max(-1.,sza_local)
411            sza_local = acos(sza_local)*180./rpi
412
413!           electron temperature
414
415            do ilev = 1, nlev
416               t_elec(ilev) = temp_elect(zlocal(ilev),temp(ilon,ilev),
417     $                                   sza_local,t_elec_origin) 
418            end do
419
420            call photochemistry_venus(nlev, nlon, zlocal, pdtphys,
421     $                           ok_jonline,ok_ionchem,tuneupperatm,
422     $                           nb_reaction_3_max,nb_reaction_4_max,
423     $                           nb_phot_max,nphotion,ilon,         
424     $                           pplay(ilon,:)/100.,
425     $                           temp(ilon,:), t_elec(:),
426     $                           ztrac(ilon,:,:),vmr_dens_euv(ilon,:,:),
427     $                           mmean(ilon,:),
428     $                           sza_local,
429     $                           lon(ilon), lat(ilon),
430     $                           nqmax, nespeuv, iter(ilon,:),
431     $                           prod_tr(ilon,:,:),
432     $                           loss_tr(ilon,:,:),
433     $                           no_em, o2_em)
434
435             no_emi(ilon,:) = no_em(:)
436             o2_emi(ilon,:) = o2_em(:)
437
438         end do         
439      end if  ! ok_chem
440
441!===================================================================
442!     compute tendencies
443!===================================================================
444
445!     update mmean
446
447      mmean(:,:) = 0.
448      do iq = 1,nqmax - nmicro
449         mmean(:,:) = mmean(:,:)+ztrac(:,:,iq)*m_tr(iq)
450      end do
451      rnew(:,:) = 8.314/mmean(:,:)*1.e3     ! J/kg K
452
453!===================================================================
454!     convert volume to mass mixing ratio / then tendencies in mmr
455!===================================================================
456
457!     gas phase
458
459      do iq = 1,nqmax - nmicro
460         ztrac(:,:,iq) = max(ztrac(:,:,iq)*m_tr(iq)/mmean(:,:),
461     $                       1.e-30)
462         d_tr_chem(:,:,iq) = (ztrac(:,:,iq) - trac(:,:,iq))/pdtphys
463      end do
464
465!     liquid phase or moments
466
467      if (ok_cloud .and. cl_scheme == 1) then
468         ztrac(:,:,i_h2so4liq) = max(ztrac(:,:,i_h2so4liq)
469     $                               *m_tr(i_h2so4liq)/mmean(:,:),
470     $                               1.e-30)
471         ztrac(:,:,i_h2oliq)   = max(ztrac(:,:,i_h2oliq)
472     $                               *m_tr(i_h2oliq)/mmean(:,:),
473     $                               1.e-30)
474         d_tr_chem(:,:,i_h2so4liq) = (ztrac(:,:,i_h2so4liq)
475     $                              - trac(:,:,i_h2so4liq))/pdtphys
476         d_tr_chem(:,:,i_h2oliq) = (ztrac(:,:,i_h2oliq)
477     $                            - trac(:,:,i_h2oliq))/pdtphys
478      end if
479
480
481      if (ok_cloud .and. cl_scheme == 2) then
482         do iq = nqmax-nmicro+1,nqmax
483            d_tr_chem(:,:,iq) = (ztrac(:,:,iq) - trac(:,:,iq))/pdtphys
484         end do
485      end if
486
487      end subroutine phytrac_chimie
Note: See TracBrowser for help on using the repository browser.