source: trunk/LMDZ.VENUS/libf/phyvenus/euvheat.F90 @ 3556

Last change on this file since 3556 was 2836, checked in by abierjon, 2 years ago

VENUS GCM:

INCLUDING THE IONOSPHERE CODE IN VENUS GCM


ATTENTION: INCREASED MEMORY DEMAND

NEEDS AT LEAST 135 GB of allocated memory

==============================================================
===> LIST OF APPENDED FILES AND INTERNAL ADDITIONS <==========
==============================================================

NEW MODEL SPECIES

  • deftank/traceur-chemistry-IONOSPHERE.def

Neutrals: 4 Species: N, NO, NO2, N(2D)

Ions: 15 species:

CO2+, CO+, O+, O2+, H+,

N2+, H2O+, OH+, C+, HCO+,

H3O+, HCO2+, N+, NO+, elec

FROM 36 to 55 chemical species

NEW KEYWORD OF PHYSIQ.DEF

  • deftank/physiq-96x96x90-chemistry-IONOSPHERE.def
  • ok_ionchem: keyword supposed to activate ion chemistry.

(be careful that n, no, no2, n2d and the ion species are in the deftank/traceur-chemistry-IONOSPHERE.def)

  • ok_jonline: keyword supposed to activate the online photochemistry

(be careful that n, no, no2 and n2d are in the traceur-chemistry-IONOSPHERE.def)

==============================================================
===> LIST OF MODIFIED PROGRAMS <=========================
==============================================================

nonoro_gwd_ran_mod.F90

  • Change EPFLUXMAX value from 5.E-3 to 1.E-3

photochemistry_venus.F90 (krates; photolysis_online; indices;)

  • Import of keywords: ok_ionchem, tuneupperatm & ok_jonline
  • addition of ion species in order
  • Forcing electroneutrality
  • Update of the reactions a001 and a002 with taking into account the other species
  • Change of formula for a002 with the formulation of Baulch et al., 1976 (confirmed by Smith and Robertson, 2008)

photolysis_mod.F90

  • Modification of the rdsolarflux subroutine to include interpolation with Atlas1 and Atlas3 in connection with E10.7

concentration2.F90

  • Added chemical species n2d, no, no2 and n in the conductivity calculation.

The ions have been excluded because their sum is 105 times less dense than the neutrals and
their thermal conductivity is unknown

iono_h.F90

  • Addition of the phdisrate routine
  • replace the electronic temperature of Mars by that of

origin = 1: Theis et al. 1980 (Venus) with bilinear interpolation altitude/cos(SZA)
origin = 2: Theis et al. 1984 (Venus) with the formula of the electronic temperature at high solar activity

  • addition of an ion temperature model based on VIRA

cleshphys.h

  • added ok_ionchem & ok_jonline in COMMON/clesphys_l/

conf_phys.f90

  • add ok_ionchem & ok_jonline as parameters to read from physiq.def file set to .false. by default

chemparam_mod.F90

  • Add species in M_tr and corresponding i_X. Set all i_X to zero before reading traceur-chemistry-IONOSPHERE.def
  • Added Type_tr table to differentiate species: 1 == neutral, 2 == ION, 3 == liquid, 10 == others


euvheat.F90; hrtherm.F; jthermcalc_e107.F; param_read_e107.F

  • Normalization with Mars

A.M

File size: 14.3 KB
Line 
1      SUBROUTINE euvheat(nlon, nlev,nqmx, pt,pplev,pplay,zzlay, &
2                   mu0,ptimestep,ptime,pq, pdq, pdteuv)
3
4        use chemparam_mod
5        use dimphy
6        use conc, only:  rnew, cpnew
7
8      IMPLICIT NONE
9!=======================================================================
10!   subject:
11!   --------
12!   Computing heating rate due to EUV absorption
13!
14!   author:  MAC 2002
15!   ------
16!
17!   input:
18!   -----
19!   mu0(klon)           
20!   pplay(ngrid,nlayer)   pressure at middle of layers (Pa)
21!   zzlay                 ! altitude at the middle of the layers (m)
22!
23!   output:
24!   -------
25!
26!   pdteuv(ngrid,nlayer)      Heating rate (K/s)
27!
28!=======================================================================
29!
30!    0.  Declarations :
31!    ------------------
32!
33#include "YOMCST.h"
34#include "clesphys.h"
35#include "mmol.h"
36!-----------------------------------------------------------------------
37!    Input/Output
38!    ------------
39
40
41      integer :: nlon
42      integer :: nlev
43      integer :: nqmx
44
45      real :: pt(nlon,nlev)
46      real :: pplev(nlon,nlev+1)
47      real :: pplay(nlon,nlev)
48      real :: zzlay(nlon,nlev)
49      real :: mu0(nlon)
50
51      real :: ptimestep,ptime
52      real :: pq(nlon,nlev,nqmx)
53      real :: pdq(nlon,nlev,nqmx)
54      real :: pdteuv(nlon,nlev)
55!
56!    Local variables :
57!    -----------------
58
59      integer,save :: nespeuv=17    ! Number of species considered (11, 12 or 17 (with nitrogen))
60      integer,save :: nspeuv_vgcm    ! Number of species considered currently considered into VGCM
61
62
63      INTEGER :: l,ig,n
64      integer,save :: euvmod = 0     !0: 4 (main) species  1: O3 chemistry 2: N chemistry, 3: C/O/H
65      real, allocatable, save :: rm(:,:)   !  number density (cm-3)
66      real :: zq(nlon,nlev,nqmx) ! local updated tracer quantity
67      real :: zt(nlon,nlev)      ! local updated atmospheric temperature
68      real :: zlocal(nlev)
69      real :: zenit
70      real :: jtot(nlev)
71      real :: dens              ! Total number density (cm-3)
72      real :: tx(nlev)
73       
74! tracer indexes for the EUV heating:
75!!! ATTENTION. These values have to be identical to those in hrterm.F90
76!!! If the values are changed there, the same has to be done here  !!!
77     
78!      integer,parameter :: ix_co2=1
79!      integer,parameter :: ix_o=3
80!      integer,parameter :: ix_co=4
81!      integer,parameter :: ix_n2=13
82
83      integer,parameter :: ix_co2  =  1
84      integer,parameter :: ix_co   =  2
85      integer,parameter :: ix_o    =  3
86      integer,parameter :: ix_o1d  =  4
87      integer,parameter :: ix_o2   =  5
88      integer,parameter :: ix_o3   =  6
89      integer,parameter :: ix_h    =  7
90      integer,parameter :: ix_h2   =  8
91      integer,parameter :: ix_oh   =  9
92      integer,parameter :: ix_ho2  = 10
93      integer,parameter :: ix_h2o2 = 11
94      integer,parameter :: ix_h2o  = 12
95      integer,parameter :: ix_n    = 13
96      integer,parameter :: ix_n2d  = 14
97      integer,parameter :: ix_no   = 15
98      integer,parameter :: ix_no2  = 16
99      integer,parameter :: ix_n2   = 17
100
101! Tracer indexes in the GCM:
102      integer,save :: g_co2=0
103      integer,save :: g_o=0
104      integer,save :: g_o2=0
105      integer,save :: g_h2=0
106      integer,save :: g_h2o2=0
107      integer,save :: g_h2o=0
108      integer,save :: g_o3=0
109      integer,save :: g_n2=0
110      integer,save :: g_n=0
111      integer,save :: g_no=0
112      integer,save :: g_co=0
113      integer,save :: g_h=0
114      integer,save :: g_no2=0
115      integer,save :: g_oh=0
116      integer,save :: g_ho2=0
117      integer,save :: g_o1d=0
118      integer,save :: g_n2d=0
119     
120      logical,save :: firstcall=.true.
121
122! Initializations and sanity checks:
123
124
125      if (firstcall) then
126         nspeuv_vgcm=0
127!        ! identify the indexes of the tracers we'll need
128         g_co2=i_co2
129         if (g_co2.eq.0) then
130            write(*,*) "euvheat: Error; no CO2 tracer !!!"
131            write(*,*) "CO2 is always needed if calleuv=.true."
132            stop
133         else
134            nspeuv_vgcm=nspeuv_vgcm+1
135         endif
136         g_o=i_o
137         if (g_o.eq.0) then
138            write(*,*) "euvheat: Error; no O tracer !!!"
139!            write(*,*) "O is always needed if calleuv=.true."
140            stop
141         else
142            nspeuv_vgcm=nspeuv_vgcm+1
143         endif
144         g_co=i_co
145         if (g_co.eq.0) then
146            write(*,*) "euvheat: Error; no CO tracer !!!"
147!            write(*,*) "CO is always needed if calleuv=.true."
148            stop
149         else
150            nspeuv_vgcm=nspeuv_vgcm+1
151         endif
152         ! n2
153         g_n2=i_n2
154         if (g_n2.eq.0) then
155            write(*,*) "euvheat: Error; no N2 tracer !!!"
156!                write(*,*) "N2 needed if NO is in traceur.def"
157            stop
158         else
159            nspeuv_vgcm=nspeuv_vgcm+1
160         endif
161         g_o2=i_o2
162         if (g_o2.eq.0) then
163            write(*,*) "euvheat: Error; no O2 tracer !!!"
164!            write(*,*) "O2 is always needed if calleuv=.true."
165            stop
166         else
167            nspeuv_vgcm=nspeuv_vgcm+1
168         endif
169         g_h2=i_h2
170         if (g_h2.eq.0) then
171            write(*,*) "euvheat: Error; no H2 tracer !!!"
172!            write(*,*) "H2 is always needed if calleuv=.true."
173            stop
174         else
175            nspeuv_vgcm=nspeuv_vgcm+1
176         endif
177         g_oh=i_oh
178         if (g_oh.eq.0) then
179            write(*,*) "euvheat: Error; no OH tracer !!!"
180!            write(*,*) "OH must always be present if thermochem=T"
181            stop
182         else
183            nspeuv_vgcm=nspeuv_vgcm+1 
184         endif
185         g_ho2=i_ho2
186         if (g_ho2.eq.0) then
187            write(*,*) "euvheat: Error; no HO2 tracer !!!"
188!            write(*,*) "HO2 must always be present if thermochem=T"
189            stop
190         else
191            nspeuv_vgcm=nspeuv_vgcm+1 
192         endif
193         g_h2o2=i_h2o2
194         if (g_h2o2.eq.0) then
195            write(*,*) "euvheat: Error; no H2O2 tracer !!!"
196!            write(*,*) "H2O2 is always needed if calleuv=.true."
197            stop
198         else
199            nspeuv_vgcm=nspeuv_vgcm+1
200         endif
201         g_h2o=i_h2o
202         if (g_h2o.eq.0) then
203            write(*,*) "euvheat: Error; no water vapor tracer !!!"
204!            write(*,*) "H2O is always needed if calleuv=.true."
205            stop
206         else
207            nspeuv_vgcm=nspeuv_vgcm+1
208         endif
209         g_o1d=i_o1d
210         if (g_o1d.eq.0) then
211            write(*,*) "euvheat: Error; no O1D tracer !!!"
212!            write(*,*) "O1D must always be present if thermochem=T"
213            stop
214         else
215            nspeuv_vgcm=nspeuv_vgcm+1 
216         endif
217         g_h=i_h
218         if (g_h.eq.0) then
219            write(*,*) "euvheat: Error; no H tracer !!!"
220!            write(*,*) "H is always needed if calleuv=.true."
221            stop
222         else
223            nspeuv_vgcm=nspeuv_vgcm+1
224         endif
225         
226!         euvmod = 1            !Default: C/O/H chemistry
227!         !Check if O3 is present
228         g_o3=i_o3
229         if (g_o3.eq.0) then
230            write(*,*) "euvheat: Error; no O3 tracer !!!"
231            write(*,*) "O3 must be present if calleuv=.true."
232            stop
233         else
234            nspeuv_vgcm=nspeuv_vgcm+1
235            euvmod=1
236         endif
237
238         !Nitrogen species
239         !NO is used to determine if N chemistry is wanted
240         !euvmod=2 -> N chemistry
241         g_no=i_no
242         if (g_no.eq.0) then
243            write(*,*) "euvheat: no NO tracer"
244            write(*,*) "No N species in UV heating"
245         else if(g_no.ne.0) then
246            nspeuv_vgcm=nspeuv_vgcm+1
247            euvmod=2
248         endif
249         ! N
250         g_n=i_n
251         if(euvmod == 2) then
252            if (g_n.eq.0) then
253               write(*,*) "euvheat: Error; no N tracer !!!"
254               write(*,*) "N needed if NO is in traceur.def"
255               stop
256            else if(g_n.ne.0) then
257               nspeuv_vgcm=nspeuv_vgcm+1
258            endif
259         else
260            if(g_n /= 0) then
261               write(*,*) "euvheat: Error: N present, but NO not!!!"
262               write(*,*) "Both must be in traceur.def"
263               stop
264            endif
265         endif   !Of if(euvmod==2)
266         !NO2
267         g_no2=i_no2
268         if(euvmod == 2) then
269            if (g_no2.eq.0) then
270               write(*,*) "euvheat: Error; no NO2 tracer !!!"
271               write(*,*) "NO2 needed if NO is in traceur.def"
272               stop
273            else if(g_no2.ne.0) then
274               nspeuv_vgcm=nspeuv_vgcm+1
275            endif
276         else
277            if(g_no2 /= 0) then
278               write(*,*) "euvheat: Error: NO2 present, but NO not!!!"
279               write(*,*) "Both must be in traceur.def"
280               stop
281            endif
282         endif   !Of if(euvmod==2)
283         !N2D
284         g_n2d=i_n2d
285         if(euvmod == 2) then
286            if (g_n2d.eq.0) then
287               write(*,*) "euvheat: Error; no N2D tracer !!!"
288               write(*,*) "N2D needed if NO is in traceur.def"
289               stop
290            else
291               nspeuv_vgcm=nspeuv_vgcm+1 
292            endif
293         else
294            if(g_n2d /= 0) then
295               write(*,*) "euvheat: Error: N2D present, but NO not!!!"
296               write(*,*) "Both must be in traceur.def"
297               stop
298            endif
299         endif   !Of if(euvmod==2)
300
301         !Check if nespeuv is appropriate for the value of euvmod
302!         select case(euvmod)
303!         case(0)
304!            if(nespeuv.ne.11) then
305!               write(*,*)'euvheat: Wrong number of tracers!'
306!               stop
307!            else
308!               write(*,*)'euvheat: Computing absorption by',nespeuv, &
309!                    ' species'
310!            endif
311!         case(1)
312!            if(nespeuv.ne.12) then
313!               write(*,*)'euvheat: Wrong number of tracers!',nespeuv
314!               stop
315!            else
316!               write(*,*)'euvheat: Computing absorption by',nespeuv,  &
317!                    ' species'
318!            endif
319!         case(2)
320!            if(nespeuv.ne.17) then
321!               write(*,*)'euvheat: Wrong number of tracers!'
322!               stop
323!            else
324!               write(*,*)'euvheat: Computing absorption by',nespeuv,  &
325!                    ' species'
326!            endif
327!         end select
328
329
330         !Allocate density vector
331         allocate(rm(nlev,nespeuv))
332
333         firstcall= .false.
334      endif                     ! of if (firstcall)
335
336!      write(*,*),  "CHECK n species currently used into VGCM",  nspeuv_vgcm
337
338
339!cccccccccccccccccccccccccccccccccccccccccccccccccccccccc
340
341      ! euvmod selection security
342      if(euvmod.gt.2.or.euvmod.lt.0) then
343         write(*,*)'euvheat: bad value for euvmod. Stop'
344         stop
345      endif
346
347      ! build local updated values of tracers (if any) and temperature
348      do l=1,nlev
349        do ig=1,nlon
350          ! chemical species
351          zq(ig,l,g_co2)=pq(ig,l,g_co2)     ! CO2 
352          zq(ig,l,g_o2)=pq(ig,l,g_o2)       ! O2
353          zq(ig,l,g_o)=pq(ig,l,g_o)         ! O(3P)
354          zq(ig,l,g_h2)=pq(ig,l,g_h2)       ! H2
355          zq(ig,l,g_h2o2)=pq(ig,l,g_h2o2)   ! H2O2
356          zq(ig,l,g_h2o)=pq(ig,l,g_h2o)     ! H2O
357          zq(ig,l,g_n2)=pq(ig,l,g_n2)       ! N2   
358          zq(ig,l,g_co)=pq(ig,l,g_co)       ! CO
359          zq(ig,l,g_h)=pq(ig,l,g_h)         ! H
360
361          !Only if O3, N or ion chemistry requested
362          if(euvmod.ge.1) then
363             zq(ig,l,g_o3)=pq(ig,l,g_o3)    ! 03
364          endif
365          !Only if N or ion chemistry requested
366          if(euvmod.ge.2) then
367             zq(ig,l,g_n)=pq(ig,l,g_n)      ! N
368             zq(ig,l,g_no)=pq(ig,l,g_no)    ! NO
369             zq(ig,l,g_no2)=pq(ig,l,g_no2)  ! NO2
370          endif
371          ! atmospheric temperature
372          zt(ig,l)=pt(ig,l)
373!      write(*,*),  "CHECK update densities L332 euv",   zq(ig,l,g_co2)
374        enddo
375      enddo
376     
377      !Solar flux calculation     
378      do ig=1,nlon
379         zenit=acos(mu0(ig))*180./acos(-1.)  !convers from rad to deg
380         
381         do l=1,nlev         
382            !Conversion to number density   
383            !!!  use R specific = R/MolarMass
384            dens=pplay(ig,l)/(rnew(ig,l)*zt(ig,l)) / 1.66e-21   ! [g mol-1] [cm-3]         
385
386            rm(l,ix_co2)  = zq(ig,l,g_co2) * dens / M_tr(g_co2) ! [cm-3]
387            rm(l,ix_o2)   = zq(ig,l,g_o2)  * dens / M_tr(g_o2)
388            rm(l,ix_o)    = zq(ig,l,g_o)   * dens / M_tr(g_o)
389            rm(l,ix_h2)   = zq(ig,l,g_h2)  * dens / M_tr(g_h2)
390            rm(l,ix_h2o)  = zq(ig,l,g_h2o) * dens / M_tr(g_h2o)
391            rm(l,ix_h2o2) = zq(ig,l,g_h2o2)* dens / M_tr(g_h2o2)
392            rm(l,ix_co)   = zq(ig,l,g_co)  * dens / M_tr(g_co)
393            rm(l,ix_n2)   = zq(ig,l,g_n2)  * dens / M_tr(g_n2)
394            rm(l,ix_h)    = zq(ig,l,g_h)   * dens / M_tr(g_h)
395
396            !Only if O3, N or ion chemistry requested
397            if(euvmod.ge.1) then
398               rm(l,ix_o3)   = zq(ig,l,g_o3) * dens / M_tr(g_o3)
399            endif
400            !Only if N or ion chemistry requested
401            if(euvmod.ge.2) then
402               rm(l,ix_n)    = zq(ig,l,g_n)    * dens / M_tr(g_n)
403               rm(l,ix_no)   = zq(ig,l,g_no)   * dens / M_tr(g_no)
404               rm(l,ix_no2)  = zq(ig,l,g_no2)  * dens / M_tr(g_no2)
405            endif
406
407!           write(*,*),  "CHECK n density", l, rm(l,ix_co2)
408         enddo
409
410!        zlocal(1)=-log(pplay(ig,1)/pplev(ig,1))
411!     &            *Rnew(ig,1)*zt(ig,1)/g
412         zlocal(1)=zzlay(ig,1)
413         zlocal(1)=zlocal(1)/1000.    ! conversion m ---> km
414         tx(1)=zt(ig,1)
415         
416         do l=2,nlev
417            tx(l)=zt(ig,l)
418            zlocal(l)=zzlay(ig,l)/1000.
419         enddo
420
421        !Routine to calculate the UV heating
422         call hrtherm (ig,euvmod,rm,nespeuv,tx,zlocal,zenit,jtot)
423         
424
425                       !euveff: UV heating efficiency. Following Fox et al. ASR 1996
426                       !should vary between 19% and 23%. Lower values
427                       !(i.e. 16%) can be used to compensate
428                       !underestimation
429                       !of 15-um cooling (see Forget et al. JGR 2009 and
430                       !Gonzalez-Galindo et al. JGR 2009) for details
431
432        !Calculates the UV heating from the total photoabsorption coefficient
433        do l=1,nlev
434!       jtot conversion from erg/(s*cm3) ---> J/(s*m3)
435          pdteuv(ig,l)=euveff*jtot(l)/10.                  &
436               /(cpnew(ig,l)*pplay(ig,l)/(rnew(ig,l)*zt(ig,l)))
437
438        enddo   
439      enddo  ! of do ig=1,nlon
440
441      !Deallocations
442      !deallocate(rm)
443
444      return
445      end
Note: See TracBrowser for help on using the repository browser.