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

Last change on this file was 3466, checked in by emillour, 5 weeks ago

Mars PCM:
More tidying in aeronomars:

  • remove unused "inv.F" and remove "dtridgl.F" which is not used here and is a duplicate of the "dtridgl" routine in phymars/swr_toon.F
  • turn aeronomars routines to modules, for those which aren't in modules yet.

EM

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