source: trunk/LMDZ.MARS/libf/aeronomars/chemthermos.F90 @ 2007

Last change on this file since 2007 was 1888, checked in by emillour, 7 years ago

Mars GCM:
Updated the calculation of the dissociation and ionization
branching ratios, using the values in the Schunk and Nagy book.
New datafiles *branchingratio_schunkandnagy2000_param.dat must be loaded
for the "EUVDAT" subdirectory of the standard "datadir" directory.
Main changes are:

  • param_v4_h.F90 -> New definition for the O2 ionization branching ratio
  • param_read_e107.F -> Read the new files containing the S&N branching ratios
  • paramfoto_compact.F -> Mainly cleaning of the code and the comments.

Also correction of a bug affecting the calculation of CO losses

  • chemthermos.F90 -> Small modification to add the possibility of including

NO and O2 nightglow rates to the outputs

  • calchim.F90 and calchim_asis.F90 -> account for change in arguments in

calls to chemthermos
FGG

File size: 19.5 KB
Line 
1      SUBROUTINE chemthermos(ig,nlayer,lswitch,chemthermod,zycol,ztemp, &
2           zdens,zpress,zlocal,zenit,ptimestep,zday,em_no,em_o2)
3
4      use tracer_mod, only: nqmx, igcm_co2, igcm_co, igcm_o, igcm_o1d,  &
5                            igcm_o2, igcm_h, igcm_h2, igcm_oh, igcm_ho2,&
6                            igcm_h2o2, igcm_h2o_vap, igcm_o3, igcm_n2,  &
7                            igcm_n, igcm_no, igcm_no2, igcm_n2d,        &
8                            igcm_co2plus, igcm_o2plus, igcm_coplus,     &
9                            igcm_cplus, igcm_nplus, igcm_noplus,        &
10                            igcm_n2plus, igcm_hplus, igcm_hco2plus,     &
11                            igcm_elec, igcm_oplus
12
13      use param_v4_h, only: Pno, Po2
14      USE comcstfi_h
15      IMPLICIT NONE
16!=======================================================================
17!   subject:
18!   --------
19!   Computing chemical variations in the thermosphere
20!
21!   author:  MAC July 2003
22!   ------
23!   modifications:
24!   -------------
25!     Ehouarn Sept 2008: added handling of tracers by their names
26!     Francisco Sept 2009: added ionosphere and N chemistry
27!     Francisco Mar 2012: Different chemical schemes possible according to
28!                         traceur.def
29!=======================================================================
30!
31!    0.  Declarations :
32!    ------------------
33!
34#include "callkeys.h"
35!-----------------------------------------------------------------------
36!    Input/Output
37!    ------------
38      integer :: lswitch,ig,chemthermod,nlayer
39      real :: zycol(nlayer,nqmx)
40      real :: ztemp(nlayer)
41      real :: zdens(nlayer)
42      real :: zpress(nlayer)                    ! in mbar
43      real :: zlocal(nlayer)
44      real :: zenit
45      real :: ptimestep
46      real :: zday
47      real :: em_no(nlayer)
48      real :: em_o2(nlayer)
49!
50!    Local variables :
51!    -----------------
52      integer :: l
53      integer,save :: nesptherm
54      real,allocatable :: rm(:,:)               !number density (cm-3)
55      logical,save :: firstcall=.true.
56
57! Tracer indexes in the GCM:
58      integer,save :: g_co2=0
59      integer,save :: g_co=0
60      integer,save :: g_o=0
61      integer,save :: g_o1d=0
62      integer,save :: g_o2=0
63      integer,save :: g_o3=0
64      integer,save :: g_h=0
65      integer,save :: g_h2=0
66      integer,save :: g_oh=0
67      integer,save :: g_ho2=0
68      integer,save :: g_h2o2=0
69      integer,save :: g_n2=0
70      integer,save :: g_h2o_vap=0
71      integer,save :: g_n=0
72      integer,save :: g_no=0
73      integer,save :: g_no2=0
74      integer,save :: g_n2d=0
75      integer,save :: g_co2plus=0
76      integer,save :: g_oplus=0
77      integer,save :: g_o2plus=0
78      integer,save :: g_coplus=0
79      integer,save :: g_cplus=0
80      integer,save :: g_nplus=0
81      integer,save :: g_noplus=0
82      integer,save :: g_n2plus=0
83      integer,save :: g_hplus=0
84      integer,save :: g_hco2plus=0
85      integer,save :: g_elec=0
86     
87! Tracer indexes in the thermospheric chemistry:
88!!! IMPORTANT. These values have to be the same than in
89!!! jthermcal.F, column.F, paramfoto_compact.F, euvheat.F
90!!! and hrtherm.F
91!!! If some value is changed here, the same change has to
92!!! be made into the other subroutines
93      integer,parameter :: i_co2=1
94      integer,parameter :: i_o2=2
95      integer,parameter :: i_o=3
96      integer,parameter :: i_co=4
97      integer,parameter :: i_h=5
98      integer,parameter :: i_oh=6
99      integer,parameter :: i_ho2=7
100      integer,parameter :: i_h2=8
101      integer,parameter :: i_h2o=9
102      integer,parameter :: i_h2o2=10
103      integer,parameter :: i_o1d=11
104      integer,parameter :: i_o3=12
105      integer,parameter :: i_n2=13
106      integer,parameter :: i_n=14
107      integer,parameter :: i_no=15
108      integer,parameter :: i_n2d=16
109      integer,parameter :: i_no2=17
110      integer,parameter :: i_co2plus=18
111      integer,parameter :: i_oplus=19
112      integer,parameter :: i_o2plus=20
113      integer,parameter :: i_coplus=21
114      integer,parameter :: i_cplus=22
115      integer,parameter :: i_nplus=23
116      integer,parameter :: i_noplus=24
117      integer,parameter :: i_n2plus=25
118      integer,parameter :: i_hplus=26
119      integer,parameter :: i_hco2plus=27
120      integer,parameter :: i_elec=28
121
122     
123! Initializations at first call
124      if (firstcall) then
125         !Number of species to consider
126         nesptherm=0
127         ! get the indexes of the tracers we'll need
128         ! It is not really necessary to check if the species are present,
129         ! as it is already done in calchim.F90. But we include it to double-check
130
131         ! Species always included if photochemistry
132         g_co2=igcm_co2
133         if (g_co2.eq.0) then
134            write(*,*) "chemthermos: Error; no CO2 tracer !!!"
135            write(*,*) "CO2 must always be present if thermochem=T"
136            stop
137         else
138            nesptherm=nesptherm+1 
139         endif
140         g_co=igcm_co
141         if (g_co.eq.0) then
142            write(*,*) "chemthermos: Error; no CO tracer !!!"
143            write(*,*) "CO must always be present if thermochem=T"
144            stop
145         else
146            nesptherm=nesptherm+1 
147         endif
148         g_o=igcm_o
149         if (g_o.eq.0) then
150            write(*,*) "chemthermos: Error; no O tracer !!!"
151            write(*,*) "O must always be present if thermochem=T"
152            stop
153         else
154            nesptherm=nesptherm+1 
155         endif
156         g_o1d=igcm_o1d
157         if (g_o1d.eq.0) then
158            write(*,*) "chemthermos: Error; no O1D tracer !!!"
159            write(*,*) "O1D must always be present if thermochem=T"
160            stop
161         else
162            nesptherm=nesptherm+1 
163         endif
164         g_o2=igcm_o2
165         if (g_o2.eq.0) then
166            write(*,*) "chemthermos: Error; no O2 tracer !!!"
167            write(*,*) "O2 must always be present if thermochem=T"
168            stop
169         else
170            nesptherm=nesptherm+1 
171         endif
172         g_h=igcm_h
173         if (g_h.eq.0) then
174            write(*,*) "chemthermos: Error; no H tracer !!!"
175            write(*,*) "H must always be present if thermochem=T"
176            stop
177         else
178            nesptherm=nesptherm+1 
179         endif
180         g_h2=igcm_h2
181         if (g_h2.eq.0) then
182            write(*,*) "chemthermos: Error; no H2 tracer !!!"
183            write(*,*) "H2 must always be present if thermochem=T"
184            stop
185         else
186            nesptherm=nesptherm+1 
187         endif
188         g_oh=igcm_oh
189         if (g_oh.eq.0) then
190            write(*,*) "chemthermos: Error; no OH tracer !!!"
191            write(*,*) "OH must always be present if thermochem=T"
192            stop
193         else
194            nesptherm=nesptherm+1 
195         endif
196         g_ho2=igcm_ho2
197         if (g_ho2.eq.0) then
198            write(*,*) "chemthermos: Error; no HO2 tracer !!!"
199            write(*,*) "HO2 must always be present if thermochem=T"
200            stop
201         else
202            nesptherm=nesptherm+1 
203         endif
204         g_h2o2=igcm_h2o2
205         if (g_h2o2.eq.0) then
206            write(*,*) "chemthermos: Error; no H2O2 tracer !!!"
207            write(*,*) "H2O2 must always be present if thermochem=T"
208            stop
209         else
210            nesptherm=nesptherm+1 
211         endif
212         g_h2o_vap=igcm_h2o_vap
213         if (g_h2o_vap.eq.0) then
214            write(*,*) "chemthermos: Error; no water vapor tracer !!!"
215            write(*,*) "H2O must always be present if thermochem=T"
216            stop
217         else
218            nesptherm=nesptherm+1 
219         endif
220         !Verify if O3 chemistry wanted
221         g_o3=igcm_o3
222         if(chemthermod.ge.1) then
223            if (g_o3.eq.0) then
224               write(*,*) "chemthermos: Error; no O3 tracer !!!"
225               write(*,*) "O3 must be present if NO is in traceur.def"
226               stop
227            else
228               nesptherm=nesptherm+1
229            endif
230         else
231            if(g_o3 == 0) then
232               write(*,*) "chemthermos: No O3 chemistry"
233            else               
234               write(*,*) "chemthermos: O3 chemistry included"
235               nesptherm=nesptherm+1 
236               chemthermod=1
237            endif
238         endif    ! Of if(chemthermod.ge.1)
239           
240         ! N chemistry
241         if(chemthermod.ge.2) then
242            g_n2=igcm_n2
243            if (g_n2.eq.0) then
244               write(*,*) "chemthermos: Error; no N2 tracer !!!"
245               write(*,*) "N2 must be present if NO is in traceur.def"
246               stop
247            else
248               nesptherm=nesptherm+1 
249            endif
250            g_n=igcm_n
251            if (g_n.eq.0) then
252               write(*,*) "chemthermos: Error; no N tracer !!!"
253               write(*,*) "N must be present if NO is in traceur.def"
254               stop
255            else
256               nesptherm=nesptherm+1 
257            endif
258            g_no=igcm_no
259            if (g_no.eq.0) then
260               write(*,*) "chemthermos: Error; no NO tracer !!!"
261               write(*,*) "NO must be present if N chemistry wanted"
262               stop
263            else
264               nesptherm=nesptherm+1 
265            endif
266            g_no2=igcm_no2
267            if (g_no2.eq.0) then
268               write(*,*) "chemthermos: Error; no NO2 tracer !!!"
269               write(*,*) "NO must be present if NO is in traceur.def"
270               stop
271            else
272               nesptherm=nesptherm+1 
273            endif
274            g_n2d=igcm_n2d
275            if (g_n2d.eq.0) then
276               write(*,*) "chemthermos: Error; no N2D tracer !!!"
277               write(*,*) "NO must be present if NO is in traceur.def"
278               stop
279            else
280               nesptherm=nesptherm+1 
281            endif
282         endif   ! Of if(chemthermod.ge.2)
283         
284         !Ion chemistry
285         if(chemthermod.eq.3) then
286            g_co2plus=igcm_co2plus
287            if (g_co2plus.eq.0 .and. chemthermod.ge.3) then
288               write(*,*) "chemthermos: Error; no CO2+ tracer !!!"
289               write(*,*) "CO2+ must be present if chemthermod=3"
290               stop
291            else
292               nesptherm=nesptherm+1 
293            endif
294            g_oplus=igcm_oplus
295            if (g_oplus.eq.0 .and. chemthermod.ge.3) then
296               write(*,*) "chemthermos: Error; no O+ tracer !!!"
297               write(*,*) "O+ must be present if chemthermod=3"
298               stop
299            else
300               nesptherm=nesptherm+1 
301            endif
302            g_o2plus=igcm_o2plus
303            if (g_o2plus.eq.0 .and. chemthermod.ge.3) then
304               write(*,*) "chemthermos: Error; no O2+ tracer !!!"
305               write(*,*) "O2+ must be present if chemthermod=3"
306               stop
307            else
308               nesptherm=nesptherm+1 
309            endif
310            g_coplus=igcm_coplus
311            if (g_coplus.eq.0) then
312               write(*,*) "chemthermos: Error; no CO+ tracer !!!"
313               write(*,*) "CO+ must be present if chemthermod=3"
314               stop
315            else
316               nesptherm=nesptherm+1 
317            endif
318            g_cplus=igcm_cplus
319            if (g_cplus.eq.0) then
320               write(*,*) "chemthermos: Error; no C+ tracer !!!"
321               write(*,*) "C+ must be present if chemthermod=3"
322               stop
323            else
324               nesptherm=nesptherm+1 
325            endif
326            g_nplus=igcm_nplus
327            if (g_nplus.eq.0) then
328               write(*,*) "chemthermos: Error; no N+ tracer !!!"
329               write(*,*) "N+ must be present if chemthermod=3"
330               stop
331            else
332               nesptherm=nesptherm+1 
333            endif
334            g_noplus=igcm_noplus
335            if (g_noplus.eq.0) then
336               write(*,*) "chemthermos: Error; no NO+ tracer !!!"
337               write(*,*) "NO+ must be present if chemthermod=3"
338               stop
339            else
340               nesptherm=nesptherm+1 
341            endif
342            g_n2plus=igcm_n2plus
343            if (g_n2plus.eq.0) then
344               write(*,*) "chemthermos: Error; no N2+ tracer !!!"
345               write(*,*) "N2+ must be present if chemthermod=3"
346               stop
347            else
348               nesptherm=nesptherm+1 
349            endif
350            g_hplus=igcm_hplus
351            if (g_hplus.eq.0) then
352               write(*,*) "chemthermos: Error; no H+ tracer !!!"
353               write(*,*) "H+ must be present if chemthermod=3"
354               stop
355            else
356               nesptherm=nesptherm+1 
357            endif
358            g_hco2plus=igcm_hco2plus
359            if (g_hco2plus.eq.0 .and. chemthermod.ge.3) then
360               write(*,*) "chemthermos: Error; no HCO2+ tracer !!!"
361               write(*,*) "HCO2+ must be present if chemthermod=3"
362               stop
363            else
364               nesptherm=nesptherm+1 
365            endif
366            g_elec=igcm_elec
367            if (g_elec.eq.0) then
368               write(*,*) "chemthermos: Error; no e- tracer !!!"
369               write(*,*) "e- must be present if chemthermod=3"
370               stop
371            else
372               nesptherm=nesptherm+1 
373            endif
374         endif
375
376         !Check if number of species is as expected
377         select case(chemthermod)
378         case(0)
379            if(nesptherm.ne.11) then
380               write(*,*)"chemthermos: Error:"
381               write(*,*)"Number of tracers not correct"
382               write(*,*)"There are",nesptherm," tracers"
383               write(*,*)"There should be 11 tracers"
384               stop
385            else
386               write(*,*)"chemthermos:",nesptherm," species"
387            endif
388         case(1)           
389            if(nesptherm.ne.12) then
390               write(*,*)"chemthermos: Error:"
391               write(*,*)"Number of tracers not correct"
392               write(*,*)"There are",nesptherm," tracers"
393               write(*,*)"There should be 12 tracers"
394               stop
395            else
396               write(*,*)"chemthermos:",nesptherm," species"
397            endif
398         case(2)
399            if(nesptherm.ne.17) then
400               write(*,*)"chemthermos: Error:"
401               write(*,*)"Number of tracers not correct"
402               write(*,*)"There are",nesptherm," tracers"
403               write(*,*)"There should be 17 tracers"
404               stop
405            else
406               write(*,*)"chemthermos:",nesptherm," species"
407            endif
408         case(3)
409            if(nesptherm.ne.28) then
410               write(*,*)"chemthermos: Error:"
411               write(*,*)"Number of tracers not correct"
412               write(*,*)"There are",nesptherm," tracers"
413               write(*,*)"There should be 28 tracers"
414               stop
415            else
416               write(*,*)"chemthermos:",nesptherm," species"
417            endif
418         end select
419         firstcall= .false.
420         write(*,*)'chemthermos: chemthermod=',chemthermod
421      endif                     ! of if (firstcall)
422     
423!cccccccccccccccccccccccccccccccccccccccccccccccccccccccc
424
425      !Allocate density vector
426      allocate(rm(nlayer,nesptherm))
427
428      do l=1,nlayer
429        rm(l,i_co2)     = max(zycol(l,g_co2)*zdens(l),1.e-30)
430        rm(l,i_co)      = max(zycol(l,g_co)*zdens(l),1.e-30)
431        rm(l,i_o)       = max(zycol(l,g_o)*zdens(l),1.e-30)
432        rm(l,i_o1d)     = max(zycol(l,g_o1d)*zdens(l),1.e-30)
433        rm(l,i_o2)      = max(zycol(l,g_o2)*zdens(l),1.e-30)
434        rm(l,i_h)       = max(zycol(l,g_h)*zdens(l),1.e-30)
435        rm(l,i_h2)      = max(zycol(l,g_h2)*zdens(l),1.e-30)
436        rm(l,i_oh)      = max(zycol(l,g_oh)*zdens(l),1.e-30)
437        rm(l,i_ho2)     = max(zycol(l,g_ho2)*zdens(l),1.e-30)
438        rm(l,i_h2o2)    = max(zycol(l,g_h2o2)*zdens(l),1.e-30)
439        rm(l,i_h2o)     = max(zycol(l,g_h2o_vap)*zdens(l),1.e-30)
440        if(chemthermod.ge.1)  &
441             rm(l,i_o3)      = max(zycol(l,g_o3)*zdens(l),1.e-30)
442        if(chemthermod.ge.2) then
443           rm(l,i_n2)      = max(zycol(l,g_n2)*zdens(l),1.e-30)
444           rm(l,i_n)       = max(zycol(l,g_n)*zdens(l),1.e-30)
445           rm(l,i_no)      = max(zycol(l,g_no)*zdens(l),1.e-30)
446           rm(l,i_co)      = max(zycol(l,g_co)*zdens(l),1.e-30)
447           rm(l,i_n2d)     = max(zycol(l,g_n2d)*zdens(l),1.e-30)
448           rm(l,i_no2)     = max(zycol(l,g_no2)*zdens(l),1.e-30)
449        endif
450        if(chemthermod.eq.3) then
451           rm(l,i_co2plus) = max(zycol(l,g_co2plus)*zdens(l),1.e-30)
452           rm(l,i_oplus)   = max(zycol(l,g_oplus)*zdens(l),1.e-30)
453           rm(l,i_o2plus)  = max(zycol(l,g_o2plus)*zdens(l),1.e-30)
454           rm(l,i_coplus)  = max(zycol(l,g_coplus)*zdens(l),1.e-30)
455           rm(l,i_cplus)   = max(zycol(l,g_cplus)*zdens(l),1.e-30)
456           rm(l,i_nplus)   = max(zycol(l,g_nplus)*zdens(l),1.e-30)
457           rm(l,i_noplus)  = max(zycol(l,g_noplus)*zdens(l),1.e-30)
458           rm(l,i_n2plus)  = max(zycol(l,g_n2plus)*zdens(l),1.e-30)
459           rm(l,i_hplus)   = max(zycol(l,g_hplus)*zdens(l),1.e-30)
460           rm(l,i_hco2plus)= max(zycol(l,g_hco2plus)*zdens(l),1.e-30)
461           rm(l,i_elec)    = max(zycol(l,g_elec)*zdens(l),1.e-30)
462        endif
463        if(chemthermod.gt.3.or.chemthermod.lt.0) then
464           write(*,*)'chemthermos: bad value for chemthermod. Stop'
465           stop
466        endif
467      enddo
468
469      !Solar flux calculation
470
471      !Photoabsorption coefficients
472      call jthermcalc_e107(ig,nlayer,chemthermod,rm,nesptherm,ztemp,zlocal,zenit,zday)
473         
474
475      !Chemistry
476      call paramfoto_compact  &
477           (ig,nlayer,chemthermod,lswitch,ztemp,ptimestep,zenit,zlocal,rm,nesptherm)
478
479      !Concentrations back to GCM
480      do l=lswitch,nlayer
481        zycol(l,g_co2)     = max(rm(l,i_co2)     / zdens(l) , 1.e-30)
482        zycol(l,g_co)      = max(rm(l,i_co)      / zdens(l) , 1.e-30)
483        zycol(l,g_o2)      = max(rm(l,i_o2)      / zdens(l) , 1.e-30)
484        zycol(l,g_h2)      = max(rm(l,i_h2)      / zdens(l) , 1.e-30)
485        zycol(l,g_h)       = max(rm(l,i_h)       / zdens(l) , 1.e-30)
486        zycol(l,g_oh)      = max(rm(l,i_oh)      / zdens(l) , 1.e-30)
487        zycol(l,g_ho2)     = max(rm(l,i_ho2)     / zdens(l) , 1.e-30)
488        zycol(l,g_h2o_vap) = max(rm(l,i_h2o)     / zdens(l) , 1.e-30)
489        zycol(l,g_h2o2)    = max(rm(l,i_h2o2)    / zdens(l) , 1.e-30)
490        zycol(l,g_o1d)     = max(rm(l,i_o1d)     / zdens(l) , 1.e-30)
491        zycol(l,g_o)       = max(rm(l,i_o)       / zdens(l) , 1.e-30)
492        if(chemthermod.ge.1) &
493             zycol(l,g_o3) = max(rm(l,i_o3)      / zdens(l) , 1.e-30)
494        if(chemthermod.ge.2) then
495           zycol(l,g_n2)      = max(rm(l,i_n2)      / zdens(l) , 1.e-30)
496           zycol(l,g_n)       = max(rm(l,i_n)       / zdens(l) , 1.e-30)
497           zycol(l,g_no)      = max(rm(l,i_no)      / zdens(l) , 1.e-30)
498           zycol(l,g_no2)     = max(rm(l,i_no2)     / zdens(l) , 1.e-30)
499           zycol(l,g_n2d)     = max(rm(l,i_n2d)     / zdens(l) , 1.e-30)
500        endif
501        if(chemthermod.ge.3) then
502           zycol(l,g_co2plus) = max(rm(l,i_co2plus) / zdens(l) , 1.e-30)
503           zycol(l,g_oplus)   = max(rm(l,i_oplus)   / zdens(l) , 1.e-30)
504           zycol(l,g_o2plus)  = max(rm(l,i_o2plus)  / zdens(l) , 1.e-30)
505           zycol(l,g_coplus)  = max(rm(l,i_coplus)  / zdens(l) , 1.e-30)
506           zycol(l,g_cplus)   = max(rm(l,i_cplus)   / zdens(l) , 1.e-30)
507           zycol(l,g_nplus)   = max(rm(l,i_nplus)   / zdens(l) , 1.e-30)
508           zycol(l,g_noplus)  = max(rm(l,i_noplus)  / zdens(l) , 1.e-30)
509           zycol(l,g_n2plus)  = max(rm(l,i_n2plus)  / zdens(l) , 1.e-30)
510           zycol(l,g_hplus)   = max(rm(l,i_hplus)   / zdens(l) , 1.e-30)
511           zycol(l,g_hco2plus)= max(rm(l,i_hco2plus)/ zdens(l) , 1.e-30)
512           zycol(l,g_elec)    = max(rm(l,i_elec)    / zdens(l) , 1.e-30)
513        endif
514        em_no(l)=Pno(l,45)
515        em_o2(l)=Po2(l,10)*0.75
516      enddo                     !nlayer
517
518      !Deallocations
519      deallocate(rm)
520
521      return
522      end
523
524
525
526
Note: See TracBrowser for help on using the repository browser.