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

Last change on this file since 2883 was 2615, checked in by romain.vande, 3 years ago

LMDZ_MARS RV : Open_MP;
Put all the "save" variables as "!$OMP THREADPRIVATE" in aeronomars

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