source: trunk/MESOSCALE/LMDZ.MARS/libf_gcm/aeronomars/calchim.F @ 932

Last change on this file since 932 was 57, checked in by aslmd, 14 years ago

mineur LMD_MM_MARS: ajout du GCM ancienne physique, systeme maintenant complet sur SVN (ne manque que la base de donnees d'etats initiaux)

File size: 13.1 KB
Line 
1      subroutine calchim(ptimestep,pplay,pplev,pt,pdt,dist_sol,mu0,
2     $                   zzlay,zday,pq,pdq,dqchim,dqschim,dqcloud,
3     $                   dqscloud)
4c
5      implicit none
6c
7c=======================================================================
8c
9c   subject:
10c   --------
11c
12c  Prepare the call for the photochemical module, and send back the
13c  tendencies from photochemistry in the chemical species mass mixing ratios
14c
15c   Author:   Sebastien Lebonnois (08/11/2002)
16c   -------
17c    update 12/06/2003 for water ice clouds and compatibility with dust
18c    update 07/2003 for coupling with thermosphere (Monica Angelats-i-Coll)
19c    update 03/05/2005 cosmetic changes (Franck Lefevre)
20c
21c   Arguments:
22c   ----------
23c
24c  Input:
25c
26c    ptimestep                  timestep (s)
27c    pplay(ngridmx,nlayermx)    Pressure at the middle of the layers (Pa)
28c    pplev(ngridmx,nlayermx+1)  Intermediate pressure levels (Pa)
29c    pt(ngridmx,nlayermx)       Temperature (K)
30c    pdt(ngridmx,nlayermx)      Temperature tendency (K)
31c    dist_sol                   distance of the sun (AU)
32c    mu0(ngridmx)               cos of solar zenith angle (=1 when sun at zenith)
33c    pq(ngridmx,nlayermx,nqmx)  Advected fields, ie chemical species here
34c    pdq(ngridmx,nlayermx,nqmx) Previous tendencies on pq
35c
36c  Output:
37c
38c    dqchim(ngridmx,nlayermx,nqmx) ! tendencies on pq due to chemistry
39c    dqschim(ngridmx,nqmx)         ! tendencies on qsurf
40c
41c=======================================================================
42
43c    Declarations :
44c    --------------
45
46#include "dimensions.h"
47#include "dimphys.h"
48#include "chimiedata.h"
49#include "tracer.h"
50#include "comcstfi.h"
51#include "callkeys.h"
52#include "fisice.h"
53#include "conc.h"
54
55c Arguments :
56c -----------
57
58c   inputs:
59c   -------
60
61      real    ptimestep
62      real    pplay(ngridmx,nlayermx)    ! pressure at the middle of the layers
63      real    zzlay(ngridmx,nlayermx)    ! pressure at the middle of the layers
64      real    pplev(ngridmx,nlayermx+1)  ! intermediate pressure levels
65      real    pt(ngridmx,nlayermx)       ! temperature
66      real    pdt(ngridmx,nlayermx)      ! temperature tendency
67      real    dist_sol                   ! distance of the sun (AU)
68      real    mu0(ngridmx)       ! cos of solar zenith angle (=1 when sun at zenith)
69      real    pq(ngridmx,nlayermx,nqmx)  ! tracers mass mixing ratio
70      real    pdq(ngridmx,nlayermx,nqmx) ! previous tendencies
71      real    zday                       ! date (time since Ls=0, in martian days)
72
73c   outputs:
74c   --------
75
76      real dqchim(ngridmx,nlayermx,nqmx) ! tendencies on pq due to chemistry
77      real dqschim(ngridmx,nqmx)         ! tendencies on qsurf
78      real dqcloud(ngridmx,nlayermx,nqmx)! tendencies on pq due to condensation
79      real dqscloud(ngridmx,nqmx)        ! tendencies on qsurf
80
81c Local variables :
82c -----------------
83
84      character*5 str5
85      integer  ig,l,iq, i_co2, i_o
86      integer  foundswitch, lswitch
87      real zq(ngridmx,nlayermx,nqmx) ! pq+pdq*ptimestep before chemistry
88                                     ! new mole fraction after
89      real colden(ngridmx,nqmx)      ! Column densities (cm-2)
90      real zt(ngridmx,nlayermx)      ! temperature
91c
92c  for each column of atmosphere:
93c
94      real zpress(nlayermx)       !  Pressure (mbar)
95      real zdens(nlayermx)        !  Density  (cm-3)
96      real ztemp(nlayermx)        !  Temperature (K)
97      real zlocal(nlayermx)       !  Altitude (km)
98      real zycol(nlayermx,nqmx)   !  Composition (mole fractions)
99      real szacol                 !  Solar zenith angle
100      real jo3(nlayermx)          !  Photodissociation rate O3->O1D (s-1)
101c
102c for output:
103c
104      real zdens3d(ngridmx,nlayermx) !  Density  (cm-3)
105      real jo3_3d(ngridmx,nlayermx)  !  Photodissociation rate O3->O1D (s-1)
106      real surfice(ngridmx,nlayermx) !  Surface of ice particules (um2/cm3)
107      logical output
108
109      logical firstcall
110      data    firstcall/.true./
111      save    firstcall
112c
113c  scheme A: 1 ; scheme B: 2
114c
115      integer scheme
116      data  scheme/2/
117c
118c=======================================================================
119c     initialization of the chemistry (first call only)
120c=======================================================================
121c
122      if (firstcall) then
123c
124         if (photochem) then
125            print*,'INIT CHEMISTRY'
126            if (scheme  .eq.  1) then
127               print*,'Scheme A : A METTRE A JOUR !!'
128               stop
129c              call init_chimie_A
130            else
131               print*,'Scheme B'
132               call init_chimie_B
133            end if
134         end if
135         firstcall = .false.
136      end if
137c
138c=======================================================================
139c     loop over grid
140c=======================================================================
141c
142      do ig = 1,ngridmx
143c
144c     local updates
145c
146         foundswitch = 0
147         do l = 1,nlayermx
148            do iq = nqchem_min,nqmx
149               zq(ig,l,iq) = pq(ig,l,iq) + pdq(ig,l,iq)*ptimestep
150               zt(ig,l)    = pt(ig,l)    + pdt(ig,l)   *ptimestep
151               zycol(l,iq) = zq(ig,l,iq) * mmean(ig,l)/mmol(iq)
152            enddo
153            zpress(l) = pplay(ig,l)/100.
154            ztemp(l)  = zt(ig,l)
155            zdens(l)  = zpress(l)/(kb*1.e4*ztemp(l))
156            zlocal(l) = zzlay(ig,l)/1000.
157c
158c     search for switch index between regions
159c
160            if (photochem .and. thermochem) then
161               if (foundswitch .eq. 0 .and. pplay(ig,l).lt.1.e-3) then
162                  lswitch = l
163                  foundswitch=1
164               end if
165            end if
166            if ( .not. photochem) then
167               lswitch = 22
168            end if
169            if (.not.  thermochem) then
170               lswitch = min(33,nlayermx+1)
171            end if
172c
173c     ice surface area  in microns^2/cm^3
174c
175c     = 4 pi r^2 * [ zq * mugaz/NA / (rhoice*4/3 pi r^3) ] *zdens
176c     = 3/r * [ zq * mugaz/NA / rhoice ] *zdens
177c     with r in microns, rhoice = 0.92e-12 g microns^-3 and zdens in cm^-3
178c
179            if (iceparty) then
180               zycol(l,nqmx-1) = (3.e-6/rice(ig,l))*zq(ig,l,nqmx-1)
181     $                           *(mugaz/6.022e23)*zdens(l)/0.92e-12
182c              write(*,*) "rice=",rice(ig,l)," m / zdens=",zdens(l),
183c    $        " cm-3 / icesurf=",zycol(l,nqmx-1)," microns^2/cm^3"
184               surfice(ig,l) = zycol(l,nqmx-1)
185            end if
186c
187         end do
188c
189         szacol = acos(mu0(ig))*180./pi
190c
191c=======================================================================
192c     call chemical subroutine
193c=======================================================================
194c
195        if (photochem) then
196           if (scheme .eq. 1) then
197              print*,'Scheme A : A METTRE A JOUR !!'
198c             call photochemist_A(zycol,szacol,ptimestep,
199c    $                            zpress,ztemp,zdens,dist_sol)
200           else
201              call photochemist_B(lswitch,zycol,szacol,ptimestep,
202     $                            zpress,ztemp,zdens,dist_sol,jo3)
203           end if
204        end if
205        if (thermochem) then
206           call chemthermos(ig,lswitch,zycol,ztemp,zdens,zpress,
207     $                      zlocal,szacol,ptimestep,zday)
208        end if
209c
210c=======================================================================
211c     tendencies
212c=======================================================================
213c
214c     must be 0. for water ice:
215c
216         if (iceparty) then
217            do l = 1,nlayermx
218               dqchim(ig,l,nqmx-1) = 0.
219            end do
220         end if
221c
222c     tendency for CO2 = - sum of others for lower atmosphere
223c     tendency for O   = - sum of others for upper atmosphere
224c
225         do l = 1,nlayermx
226            if (l .lt. lswitch) then
227               do iq = nqchem_min,nqmx
228                  if ((noms(iq) .ne. "co2") .and.
229     $                (noms(iq) .ne. "ice")) then
230                     dqchim(ig,l,iq) = (zycol(l,iq)*mmol(iq)/mmean(ig,l)
231     $                                - zq(ig,l,iq))/ptimestep
232                  else if (noms(iq) .eq. "co2") then
233                     i_co2 = iq
234                     dqchim(ig,l,iq) = 0.
235                  end if
236                  dqschim(ig,iq) = 0.
237               end do
238               do iq = nqchem_min,nqmx
239                  if (noms(iq) .ne. "co2") then
240                     dqchim(ig,l,i_co2) = dqchim(ig,l,i_co2)
241     $                                  - dqchim(ig,l,iq)
242                  end if
243                end do
244             else if (l .ge. lswitch) then
245                do iq = nqchem_min,nqmx
246                   if ((noms(iq).ne."o") .and.(noms(iq) .ne."ice")) then
247                      dqchim(ig,l,iq) = (zycol(l,iq)*mmol(iq)
248     $                                  /mmean(ig,l)
249     $                                 - zq(ig,l,iq))/ptimestep
250                   else if (noms(iq) .eq. "o") then
251                      i_o = iq
252                      dqchim(ig,l,iq) = 0.
253                   end if
254                enddo
255                do iq = nqchem_min,nqmx
256                   if (noms(iq) .ne. "o") then
257                      dqchim(ig,l,i_o) = dqchim(ig,l,i_o)
258     $                                 - dqchim(ig,l,iq)
259                   end if
260                end do
261             end if
262          end do
263c
264c     dust
265c
266          if (nqchem_min .gt. 1) then
267             do iq = 1,nqchem_min-1
268                do l = 1,nlayermx
269                   dqchim(ig,l,iq) = 0.
270                end do
271                dqschim(ig,iq) = 0.
272             end do
273          end if
274c
275c     condensation of h2o2
276c
277          call perosat(ig,ptimestep,pplev,pplay,
278     $                 ztemp,zycol,dqcloud,dqscloud)
279c
280c     for outputs
281c
282          do iq = nqchem_min,nqmx
283             colden(ig,iq) = 0.
284             do l = 1,nlayermx
285c
286c     column density converted in cm-2
287c     pplev en pa, mugaz en g.mol-1 et g en m.s-2
288c     not for ice
289c
290                if (noms(iq) .ne. "h2o2") then
291                  colden(ig,iq) = colden(ig,iq) + zycol(l,iq)
292     $                         *6.022e22*(pplev(ig,l)-pplev(ig,l+1))
293     $                         /(mmean(ig,l)*g)
294                else   ! for H2O2, remove condensation from zycol
295                  colden(ig,iq) = colden(ig,iq) + (zycol(l,iq) +
296     $               dqcloud(ig,l,iq)*ptimestep*mmean(ig,l)/mmol(iq))
297     $                         *6.022e22*(pplev(ig,l)-pplev(ig,l+1))
298     $                         /(mmean(ig,l)*g)
299                end if
300c
301c     local densities, for outputs (put in zq)
302c     not for ice
303c
304                zq(ig,l,iq) = zycol(l,iq)*zdens(l)
305c                        for H2O2, remove condensation from zycol
306                if (noms(iq) .eq. "h2o2") then
307                   zq(ig,l,iq) = zdens(l)*(zycol(l,iq) +
308     $               dqcloud(ig,l,iq)*ptimestep*mmean(ig,l)/mmol(iq))
309                end if
310             end do
311          end do
312c
313c     density and j(o3->o1d), for outputs
314c
315          zdens3d(ig,1) = zdens(1)
316          jo3_3d(ig,1) = jo3(1)
317          do l = 2,nlayermx
318             zdens3d(ig,l) = zdens(l)
319             jo3_3d(ig,l) = jo3(l)
320          end do
321c
322c=======================================================================
323c     end of loop over grid
324c=======================================================================
325c
326      end do
327c
328c=======================================================================
329c     write outputs
330c=======================================================================
331c
332      output = .true.
333
334      if (output) then
335         if (ngridmx .gt. 1) then
336c           call writediagfi(ngridmx,'dens','atm dens.','cm-3',3,zdens3d(1,1))
337c           call writediagfi(ngridmx,'jo3','j o3->o1d','s-1',3,jo3_3d(1,1))
338c           call writediagfi(ngridmx,'sice','ice surf.','um2/cm3',3,surfice(1,1))
339            do iq = nqchem_min,nqmx
340               if (noms(iq) .ne. "ice") then
341                  write(str5(1:5),'(a5)') noms(iq)
342                  call writediagfi(ngridmx,'n_'//str5,'density',
343     $                             'cm-3',3,zq(1,1,iq))
344c                 call writediagfi(ngridmx,'dqch_'//str5,'density','cm-3',3,dqchim(1,1,iq))
345c                 if (noms(iq) .eq. "h2o2" .or. noms(iq) .eq. "h2o") then
346c                    call writediagfi(ngridmx,'cl_'//str5,'density','cm-3',3,dqcloud(1,1,iq))
347c                 end if
348                  call writediagfi(ngridmx,'c_'//str5,'col. dens.',
349     $                             'cm-2',2,colden(1,iq))
350               end if
351            end do
352c
353            if (callstats) then
354c
355c              convert to mole.cm-2 for the column densities
356c
357               do iq = nqchem_min,nqmx
358                  do ig = 1,ngridmx
359                     colden(ig,iq) = colden(ig,iq)/6.022e23
360                  end do   
361               end do
362c
363c              call wstats(ngridmx,"jo3","jo3->o1d","s-1",3,jo3_3d)
364c
365               do iq = nqchem_min,nqmx
366                  if (noms(iq) .ne. "ice") then
367                     write(str5(1:5),'(a5)') noms(iq)
368                     call wstats(ngridmx,"n_"//str5,"density",
369     &                           "cm-3",3,zq(1,1,iq))
370                     call wstats(ngridmx,"c_"//str5,"col. dens.",
371     &                           "mol cm-2",2,colden(1,iq))
372                  end if
373               end do
374            end if
375         end if
376c
377      endif
378c
379      end
Note: See TracBrowser for help on using the repository browser.