source: trunk/LMDZ.MARS/libf/aeronomars/photolysis.F90 @ 2024

Last change on this file since 2024 was 2024, checked in by flefevre, 6 years ago

Préparation de la fusion des modèles chimiques basse/haute atmosphère:

  • ajout de la chimie de N(2D) dans la basse atmosphère
  • ajout des photodissociations de H2 et N2 dans la basse atmosphère (non actives pour l'instant)
File size: 14.3 KB
Line 
1!==========================================================================
2
3      subroutine photolysis(nlayer,                              &
4                            lswitch, press, temp, sza, tauref,   &
5                            zmmean, dist_sol, rmco2, rmo3, v_phot)
6
7!==========================================================================
8
9      use comcstfi_h
10
11      implicit none
12
13#include "chimiedata.h"
14
15!==========================================================================
16!     input:
17!==========================================================================
18       
19      integer, intent(in) :: nlayer ! number of atmospheric layers
20      integer :: lswitch            ! interface level between chemistries
21      real :: press(nlayer)         ! pressure (hPa)
22      real :: temp(nlayer)          ! temperature (K)
23      real :: sza                   ! solar zenith angle (deg)
24      real :: tauref                ! optical depth at 7 hpa
25      real :: zmmean(nlayer)        ! mean molecular mass (g)
26      real :: dist_sol              ! sun distance (AU)
27      real :: rmco2(nlayer)         ! co2 mixing ratio
28      real :: rmo3(nlayer)          ! ozone mixing ratio
29
30!==========================================================================
31!     output: interpolated photodissociation rates (s-1)
32!==========================================================================
33
34      real (kind = 8), dimension(nlayer,nb_phot_max) :: v_phot
35
36!==========================================================================
37!     local:
38!==========================================================================
39
40      integer :: icol, ij, indsza, indtau, indcol, indozo, indtemp,     &
41                 iozo, isza, itau, it, l
42
43      integer :: j_o2_o, j_o2_o1d, j_co2_o, j_co2_o1d, j_o3_o1d,        &
44                 j_o3_o, j_h2o, j_hdo, j_h2o2, j_ho2, j_no, j_no2,      &
45                 j_hno3, j_hno4
46
47      real :: col(nlayer)                 ! overhead air column   (molecule cm-2)
48      real :: colo3(nlayer)               ! overhead ozone column (molecule cm-2)
49      real :: poids(2,2,2,2,2)            ! 5D interpolation weights
50      real :: tref                        ! temperature  at 1.9 hPa in the gcm (K)
51      real :: table_temp(ntemp)           ! temperatures at 1.9 hPa in jmars   (K)
52      real :: cinf, csup, cicol, ciozo, cisza, citemp, citau
53      real :: colo3min, dp, coef
54      real :: ratio_o3(nlayer)
55      real :: tau
56      real :: j(nlayer,nd)
57
58!==========================================================================
59!     day/night criterion
60!==========================================================================
61
62      if (sza <= 95.) then
63
64!==========================================================================
65!     temperatures at 1.9 hPa in lookup table
66!==========================================================================
67     
68      table_temp(1) = 226.2
69      table_temp(2) = 206.2
70      table_temp(3) = 186.2
71      table_temp(4) = 169.8
72
73!==========================================================================
74!     interpolation in solar zenith angle
75!==========================================================================
76 
77      indsza = nsza - 1
78      do isza = 1,nsza
79         if (szatab(isza) >= sza) then
80            indsza = isza - 1
81            indsza = max(indsza, 1)
82            exit
83         end if
84      end do
85      cisza = (sza - szatab(indsza))  &
86             /(szatab(indsza + 1) - szatab(indsza))
87
88!==========================================================================
89!     interpolation in dust (tau)
90!==========================================================================
91
92      tau = min(tauref, tautab(ntau))
93      tau = max(tau, tautab(1))
94
95      indtau = ntau - 1
96      do itau = 1,ntau
97         if (tautab(itau) >= tau) then
98            indtau = itau - 1
99            indtau = max(indtau, 1)
100            exit
101         end if
102      end do
103      citau = (tau - tautab(indtau))     &
104             /(tautab(indtau + 1) - tautab(indtau))
105
106!==========================================================================
107!     co2 and ozone columns
108!==========================================================================
109
110!     co2 column at model top (molecule.cm-2)
111
112      col(lswitch-1) = 6.022e22*rmco2(lswitch-1)*press(lswitch-1)*100.  &
113                       /(zmmean(lswitch-1)*g)
114
115!     ozone column at model top
116
117      colo3(lswitch-1) = 0.
118
119!     co2 and ozone columns for other levels (molecule.cm-2)
120
121      do l = lswitch-2,1,-1
122         dp = (press(l) - press(l+1))*100.
123         col(l) = col(l+1) + (rmco2(l+1) + rmco2(l))*0.5   &
124                             *6.022e22*dp/(zmmean(l)*g)
125         col(l) = min(col(l), colairtab(1))
126         colo3(l) = colo3(l+1) + (rmo3(l+1) + rmo3(l))*0.5 &
127                                 *6.022e22*dp/(zmmean(l)*g)
128      end do
129
130!     ratio ozone column/minimal theoretical column (0.1 micron-atm)
131
132!     ro3 = 7.171e-10 is the o3 mixing ratio for a uniform
133!     profile giving a column 0.1 micron-atmosphere at
134!     a surface pressure of 10 hpa.
135
136      do l = 1,lswitch-1
137         colo3min    = col(l)*7.171e-10
138         ratio_o3(l) = colo3(l)/colo3min
139         ratio_o3(l) = min(ratio_o3(l), table_ozo(nozo)*10.)
140         ratio_o3(l) = max(ratio_o3(l), 1.)
141      end do
142
143!==========================================================================
144!     temperature dependence
145!==========================================================================
146
147!     1) search for temperature at 1.9 hPa (tref): vertical interpolation
148
149      tref = temp(1)
150      do l = (lswitch-1)-1,1,-1
151         if (press(l) > 1.9) then
152            cinf = (press(l) - 1.9)/(press(l) - press(l+1))
153            csup = 1. - cinf
154            tref = cinf*temp(l+1) + csup*temp(l)
155            exit
156         end if
157      end do
158
159!     2) interpolation in temperature
160
161      tref = min(tref,table_temp(1))
162      tref = max(tref,table_temp(ntemp))
163
164      do it = 2, ntemp
165         if (table_temp(it) <= tref) then
166            citemp = (log(tref) - log(table_temp(it)))              &
167                    /(log(table_temp(it-1)) - log(table_temp(it)))
168            indtemp = it - 1
169            exit
170         end if
171      end do
172
173!==========================================================================
174!     loop over vertical levels
175!==========================================================================
176
177      do l = 1,lswitch-1
178
179!     interpolation in air column
180
181         indcol = nz - 1
182         do icol = 1,nz
183            if (colairtab(icol) < col(l)) then
184               indcol = icol - 1
185               exit
186            end if
187         end do
188         cicol = (log(col(l)) - log(colairtab(indcol + 1)))              &
189                /(log(colairtab(indcol)) - log(colairtab(indcol + 1)))
190
191!     interpolation in ozone column
192
193         indozo = nozo - 1
194         do iozo = 1,nozo
195            if (table_ozo(iozo)*10. >= ratio_o3(l)) then
196               indozo = iozo - 1
197               indozo = max(indozo, 1)
198               exit
199            end if
200         end do
201         ciozo = (ratio_o3(l) - table_ozo(indozo)*10.)             &
202                /(table_ozo(indozo + 1)*10. - table_ozo(indozo)*10.)
203
204!     4-dimensional interpolation weights
205
206!     poids(temp,sza,co2,o3,tau)
207
208         poids(1,1,1,1,1) = citemp*(1.-cisza)*cicol*(1.-ciozo)*(1.-citau)
209         poids(1,1,1,2,1) = citemp*(1.-cisza)*cicol*ciozo*(1.-citau)
210         poids(1,1,2,1,1) = citemp*(1.-cisza)*(1.-cicol)*(1.-ciozo)*(1.-citau)
211         poids(1,1,2,2,1) = citemp*(1.-cisza)*(1.-cicol)*ciozo*(1.-citau)
212         poids(1,2,1,1,1) = citemp*cisza*cicol*(1.-ciozo)*(1.-citau)
213         poids(1,2,1,2,1) = citemp*cisza*cicol*ciozo*(1.-citau)
214         poids(1,2,2,1,1) = citemp*cisza*(1.-cicol)*(1.-ciozo)*(1.-citau)
215         poids(1,2,2,2,1) = citemp*cisza*(1.-cicol)*ciozo*(1.-citau)
216         poids(2,1,1,1,1) = (1.-citemp)*(1.-cisza)*cicol*(1.-ciozo)*(1.-citau)
217         poids(2,1,1,2,1) = (1.-citemp)*(1.-cisza)*cicol*ciozo*(1.-citau)
218         poids(2,1,2,1,1) = (1.-citemp)*(1.-cisza)*(1.-cicol)*(1.-ciozo)*(1.-citau)
219         poids(2,1,2,2,1) = (1.-citemp)*(1.-cisza)*(1.-cicol)*ciozo*(1.-citau)
220         poids(2,2,1,1,1) = (1.-citemp)*cisza*cicol*(1.-ciozo)*(1.-citau)
221         poids(2,2,1,2,1) = (1.-citemp)*cisza*cicol*ciozo*(1.-citau)
222         poids(2,2,2,1,1) = (1.-citemp)*cisza*(1.-cicol)*(1.-ciozo)*(1.-citau)
223         poids(2,2,2,2,1) = (1.-citemp)*cisza*(1.-cicol)*ciozo*(1.-citau)
224!
225         poids(1,1,1,1,2) = citemp*(1.-cisza)*cicol*(1.-ciozo)*citau
226         poids(1,1,1,2,2) = citemp*(1.-cisza)*cicol*ciozo*citau
227         poids(1,1,2,1,2) = citemp*(1.-cisza)*(1.-cicol)*(1.-ciozo)*citau
228         poids(1,1,2,2,2) = citemp*(1.-cisza)*(1.-cicol)*ciozo*citau
229         poids(1,2,1,1,2) = citemp*cisza*cicol*(1.-ciozo)*citau
230         poids(1,2,1,2,2) = citemp*cisza*cicol*ciozo*citau
231         poids(1,2,2,1,2) = citemp*cisza*(1.-cicol)*(1.-ciozo)*citau
232         poids(1,2,2,2,2) = citemp*cisza*(1.-cicol)*ciozo*citau
233         poids(2,1,1,1,2) = (1.-citemp)*(1.-cisza)*cicol*(1.-ciozo)*citau
234         poids(2,1,1,2,2) = (1.-citemp)*(1.-cisza)*cicol*ciozo*citau
235         poids(2,1,2,1,2) = (1.-citemp)*(1.-cisza)*(1.-cicol)*(1.-ciozo)*citau
236         poids(2,1,2,2,2) = (1.-citemp)*(1.-cisza)*(1.-cicol)*ciozo*citau
237         poids(2,2,1,1,2) = (1.-citemp)*cisza*cicol*(1.-ciozo)*citau
238         poids(2,2,1,2,2) = (1.-citemp)*cisza*cicol*ciozo*citau
239         poids(2,2,2,1,2) = (1.-citemp)*cisza*(1.-cicol)*(1.-ciozo)*citau
240         poids(2,2,2,2,2) = (1.-citemp)*cisza*(1.-cicol)*ciozo*citau
241
242!     4-dimensional interpolation in the lookup table
243
244         do ij = 1,nd
245            j(l,ij) =                                                                &
246            poids(1,1,1,1,1)*jphot(indtemp,indsza,indcol,indozo,indtau,ij)           &
247          + poids(1,1,1,2,1)*jphot(indtemp,indsza,indcol,indozo+1,indtau,ij)         &
248          + poids(1,1,2,1,1)*jphot(indtemp,indsza,indcol+1,indozo,indtau,ij)         &
249          + poids(1,1,2,2,1)*jphot(indtemp,indsza,indcol+1,indozo+1,indtau,ij)       &
250          + poids(1,2,1,1,1)*jphot(indtemp,indsza+1,indcol,indozo,indtau,ij)         &
251          + poids(1,2,1,2,1)*jphot(indtemp,indsza+1,indcol,indozo+1,indtau,ij)       &
252          + poids(1,2,2,1,1)*jphot(indtemp,indsza+1,indcol+1,indozo,indtau,ij)       &
253          + poids(1,2,2,2,1)*jphot(indtemp,indsza+1,indcol+1,indozo+1,indtau,ij)     &
254          + poids(2,1,1,1,1)*jphot(indtemp+1,indsza,indcol,indozo,indtau,ij)         &
255          + poids(2,1,1,2,1)*jphot(indtemp+1,indsza,indcol,indozo+1,indtau,ij)       &
256          + poids(2,1,2,1,1)*jphot(indtemp+1,indsza,indcol+1,indozo,indtau,ij)       &
257          + poids(2,1,2,2,1)*jphot(indtemp+1,indsza,indcol+1,indozo+1,indtau,ij)     &
258          + poids(2,2,1,1,1)*jphot(indtemp+1,indsza+1,indcol,indozo,indtau,ij)       &
259          + poids(2,2,1,2,1)*jphot(indtemp+1,indsza+1,indcol,indozo+1,indtau,ij)     &
260          + poids(2,2,2,1,1)*jphot(indtemp+1,indsza+1,indcol+1,indozo,indtau,ij)     &
261          + poids(2,2,2,2,1)*jphot(indtemp+1,indsza+1,indcol+1,indozo+1,indtau,ij)   &
262!
263          + poids(1,1,1,1,2)*jphot(indtemp,indsza,indcol,indozo,indtau+1,ij)         &
264          + poids(1,1,1,2,2)*jphot(indtemp,indsza,indcol,indozo+1,indtau+1,ij)       &
265          + poids(1,1,2,1,2)*jphot(indtemp,indsza,indcol+1,indozo,indtau+1,ij)       &
266          + poids(1,1,2,2,2)*jphot(indtemp,indsza,indcol+1,indozo+1,indtau+1,ij)     &
267          + poids(1,2,1,1,2)*jphot(indtemp,indsza+1,indcol,indozo,indtau+1,ij)       &
268          + poids(1,2,1,2,2)*jphot(indtemp,indsza+1,indcol,indozo+1,indtau+1,ij)     &
269          + poids(1,2,2,1,2)*jphot(indtemp,indsza+1,indcol+1,indozo,indtau+1,ij)     &
270          + poids(1,2,2,2,2)*jphot(indtemp,indsza+1,indcol+1,indozo+1,indtau+1,ij)   &
271          + poids(2,1,1,1,2)*jphot(indtemp+1,indsza,indcol,indozo,indtau+1,ij)       &
272          + poids(2,1,1,2,2)*jphot(indtemp+1,indsza,indcol,indozo+1,indtau+1,ij)     &
273          + poids(2,1,2,1,2)*jphot(indtemp+1,indsza,indcol+1,indozo,indtau+1,ij)     &
274          + poids(2,1,2,2,2)*jphot(indtemp+1,indsza,indcol+1,indozo+1,indtau+1,ij)   &
275          + poids(2,2,1,1,2)*jphot(indtemp+1,indsza+1,indcol,indozo,indtau+1,ij)     &
276          + poids(2,2,1,2,2)*jphot(indtemp+1,indsza+1,indcol,indozo+1,indtau+1,ij)   &
277          + poids(2,2,2,1,2)*jphot(indtemp+1,indsza+1,indcol+1,indozo,indtau+1,ij)   &
278          + poids(2,2,2,2,2)*jphot(indtemp+1,indsza+1,indcol+1,indozo+1,indtau+1,ij)
279         end do
280
281!     correction for sun distance
282
283         do ij = 1,nd
284            j(l,ij) = j(l,ij)*(1.52/dist_sol)**2.
285         end do
286
287!==========================================================================
288!     end of loop over vertical levels
289!==========================================================================
290
291      end do
292
293      else
294
295!==========================================================================
296!     night
297!==========================================================================
298
299         j(:,:) = 0.
300
301      end if
302
303! photodissociation rates numbering in the lookup table
304
305! jmars.20140930
306
307      j_o2_o         =  1      ! o2 + hv     -> o + o
308      j_o2_o1d       =  2      ! o2 + hv     -> o + o(1d)
309      j_co2_o        =  3      ! co2 + hv    -> co + o
310      j_co2_o1d      =  4      ! co2 + hv    -> co + o(1d)
311      j_o3_o1d       =  5      ! o3 + hv     -> o2 + o(1d)
312      j_o3_o         =  6      ! o3 + hv     -> o2 + o
313      j_h2o          =  7      ! h2o + hv    -> h + oh
314      j_h2o2         =  8      ! h2o2 + hv   -> oh + oh
315      j_ho2          =  9      ! ho2 + hv    -> oh + o
316      j_no           =  10     ! no + hv     -> n + o
317      j_no2          =  11     ! no2 + hv    -> no + o
318      j_hno3         =  12     ! hno3 + hv   -> no2 + oh
319      j_hno4         =  13     ! hno4 + hv   -> no2 + ho2
320
321! fill v_phot array
322
323      v_phot(:,:) = 0.
324
325      do l = 1,lswitch-1
326         v_phot(l, 1) = j(l,j_o2_o)
327         v_phot(l, 2) = j(l,j_o2_o1d)
328         v_phot(l, 3) = j(l,j_co2_o)
329         v_phot(l, 4) = j(l,j_co2_o1d)
330         v_phot(l, 5) = j(l,j_o3_o1d)
331         v_phot(l, 6) = j(l,j_o3_o)
332         v_phot(l, 7) = j(l,j_h2o)
333         v_phot(l, 8) = j(l,j_h2o2)
334         v_phot(l, 9) = j(l,j_ho2)
335         v_phot(l,10) = 0.         ! h2
336         v_phot(l,11) = j(l,j_no)
337         v_phot(l,12) = j(l,j_no2)
338         v_phot(l,13) = 0.         ! n2
339      end do
340
341      return
342      end
343
344!*****************************************************************
Note: See TracBrowser for help on using the repository browser.