source: trunk/mars/libf/aeronomars/calchim.F @ 38

Last change on this file since 38 was 38, checked in by emillour, 14 years ago

Ajout du modè Martien (mon LMDZ.MARS.BETA, du 28/01/2011) dans le rértoire mars, pour pouvoir suivre plus facilement les modifs.
EM

File size: 18.6 KB
Line 
1      subroutine calchim(ptimestep,pplay,pplev,pt,pdt,dist_sol,mu0,
2     $                   zzlay,zday,pq,pdq,rice,
3     &                   dqchim,dqschim,dqcloud,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    update sept. 2008 identify tracers by their names (Ehouarn Millour)
21c
22c   Arguments:
23c   ----------
24c
25c  Input:
26c
27c    ptimestep                  timestep (s)
28c    pplay(ngridmx,nlayermx)    Pressure at the middle of the layers (Pa)
29c    pplev(ngridmx,nlayermx+1)  Intermediate pressure levels (Pa)
30c    pt(ngridmx,nlayermx)       Temperature (K)
31c    pdt(ngridmx,nlayermx)      Temperature tendency (K)
32c    dist_sol                   distance of the sun (AU)
33c    mu0(ngridmx)               cos of solar zenith angle (=1 when sun at zenith)
34c    pq(ngridmx,nlayermx,nqmx)  Advected fields, ie chemical species here
35c    pdq(ngridmx,nlayermx,nqmx) Previous tendencies on pq
36c    rice(ngridmx,nlayermx)     Estimated ice crystal radius (m)
37c
38c  Output:
39c
40c    dqchim(ngridmx,nlayermx,nqmx) ! tendencies on pq due to chemistry
41c    dqschim(ngridmx,nqmx)         ! tendencies on qsurf
42c
43c=======================================================================
44
45c    Declarations :
46c    --------------
47
48#include "dimensions.h"
49#include "dimphys.h"
50#include "chimiedata.h"
51#include "tracer.h"
52#include "comcstfi.h"
53#include "callkeys.h"
54#include "conc.h"
55
56c Arguments :
57c -----------
58
59c   inputs:
60c   -------
61
62      real    ptimestep
63      real    pplay(ngridmx,nlayermx)    ! pressure at the middle of the layers
64      real    zzlay(ngridmx,nlayermx)    ! pressure at the middle of the layers
65      real    pplev(ngridmx,nlayermx+1)  ! intermediate pressure levels
66      real    pt(ngridmx,nlayermx)       ! temperature
67      real    pdt(ngridmx,nlayermx)      ! temperature tendency
68      real    dist_sol                   ! distance of the sun (AU)
69      real    mu0(ngridmx)       ! cos of solar zenith angle (=1 when sun at zenith)
70      real    pq(ngridmx,nlayermx,nqmx)  ! tracers mass mixing ratio
71      real    pdq(ngridmx,nlayermx,nqmx) ! previous tendencies
72      real    zday                       ! date (time since Ls=0, in martian days)
73      real    rice(ngridmx,nlayermx)     ! Estimated ice crystal radius (m)
74
75c   outputs:
76c   --------
77
78      real dqchim(ngridmx,nlayermx,nqmx) ! tendencies on pq due to chemistry
79      real dqschim(ngridmx,nqmx)         ! tendencies on qsurf
80      real dqcloud(ngridmx,nlayermx,nqmx)! tendencies on pq due to condensation
81      real dqscloud(ngridmx,nqmx)        ! tendencies on qsurf
82
83c Local variables :
84c -----------------
85
86      character*20 str20
87      integer  ig,l,i,iq
88      integer  foundswitch, lswitch
89      real zq(ngridmx,nlayermx,nqmx) ! pq+pdq*ptimestep before chemistry
90                                     ! new mole fraction after
91      real colden(ngridmx,nqmx)      ! Column densities (cm-2)
92      real zt(ngridmx,nlayermx)      ! temperature
93c
94c  for each column of atmosphere:
95c
96      real zpress(nlayermx)       !  Pressure (mbar)
97      real zdens(nlayermx)        !  Density  (cm-3)
98      real ztemp(nlayermx)        !  Temperature (K)
99      real zlocal(nlayermx)       !  Altitude (km)
100      real zycol(nlayermx,nqmx)   !  Composition (mole fractions)
101      real szacol                 !  Solar zenith angle
102      real jo3(nlayermx)          !  Photodissociation rate O3->O1D (s-1)
103c
104c for output:
105c
106      real zdens3d(ngridmx,nlayermx) !  Density  (cm-3)
107      real jo3_3d(ngridmx,nlayermx)  !  Photodissociation rate O3->O1D (s-1)
108      real surfice(ngridmx,nlayermx) !  Surface of ice particules (um2/cm3)
109
110      logical output              ! to issue calls to writediagfi and stats
111      parameter (output=.true.)   ! see at end of routine
112
113      logical,save :: firstcall=.true.
114      integer,save :: nbq  ! number of tracers used in the chemistry
115      integer,save :: niq(nqmx) ! array storing the indexes of the tracers
116
117! index of tracers:
118      integer,save :: i_co2=0
119      integer,save :: i_co=0
120      integer,save :: i_o=0
121      integer,save :: i_o1d=0
122      integer,save :: i_o2=0
123      integer,save :: i_o3=0
124      integer,save :: i_h=0
125      integer,save :: i_h2=0
126      integer,save :: i_oh=0
127      integer,save :: i_ho2=0
128      integer,save :: i_h2o2=0
129      integer,save :: i_n2=0
130      integer,save :: i_ar=0
131      integer,save :: i_ice=0 ! water ice
132      integer,save :: i_h2o=0 ! water vapour
133
134c
135c  scheme A: 1 ; scheme B: 2
136c
137      integer,parameter :: scheme=2
138c
139c=======================================================================
140c     initialization of the chemistry (first call only)
141c=======================================================================
142c
143      if (firstcall) then
144c
145         if (photochem) then
146            print*,'calchim: INIT CHEMISTRY'
147            if (scheme  .eq.  1) then
148               print*,'calchim: Scheme A : A METTRE A JOUR !!'
149               stop
150c              call init_chimie_A
151            else
152               print*,'calchim: Scheme B'
153               call init_chimie_B
154            end if
155         end if
156
157         ! find index of chemical tracers to use
158         nbq=0 ! to count number of tracers
159         i_co2=igcm_co2
160         if (i_co2.eq.0) then
161           write(*,*) "calchim: Error; no CO2 tracer !!!"
162           stop
163         else
164           nbq=nbq+1
165           niq(nbq)=i_co2
166         endif
167         i_co=igcm_co
168         if (i_co.eq.0) then
169           write(*,*) "calchim: Error; no CO tracer !!!"
170           stop
171         else
172           nbq=nbq+1
173           niq(nbq)=i_co
174         endif
175         i_o=igcm_o
176         if (i_o.eq.0) then
177           write(*,*) "calchim: Error; no O tracer !!!"
178           stop
179         else
180           nbq=nbq+1
181           niq(nbq)=i_o
182         endif
183         i_o1d=igcm_o1d
184         if (i_o1d.eq.0) then
185           write(*,*) "calchim: Error; no O1D tracer !!!"
186           stop
187         else
188           nbq=nbq+1
189           niq(nbq)=i_o1d
190         endif
191         i_o2=igcm_o2
192         if (i_o2.eq.0) then
193           write(*,*) "calchim: Error; no O2 tracer !!!"
194           stop
195         else
196           nbq=nbq+1
197           niq(nbq)=i_o2
198         endif
199         i_o3=igcm_o3
200         if (i_o3.eq.0) then
201           write(*,*) "calchim: Error; no O3 tracer !!!"
202           stop
203         else
204           nbq=nbq+1
205           niq(nbq)=i_o3
206         endif
207         i_h=igcm_h
208         if (i_h.eq.0) then
209           write(*,*) "calchim: Error; no H tracer !!!"
210           stop
211         else
212           nbq=nbq+1
213           niq(nbq)=i_h
214         endif
215         i_h2=igcm_h2
216         if (i_h2.eq.0) then
217           write(*,*) "calchim: Error; no H2 tracer !!!"
218           stop
219         else
220           nbq=nbq+1
221           niq(nbq)=i_h2
222         endif
223         i_oh=igcm_oh
224         if (i_oh.eq.0) then
225           write(*,*) "calchim: Error; no OH tracer !!!"
226           stop
227         else
228           nbq=nbq+1
229           niq(nbq)=i_oh
230         endif
231         i_ho2=igcm_ho2
232         if (i_ho2.eq.0) then
233           write(*,*) "calchim: Error; no HO2 tracer !!!"
234           stop
235         else
236           nbq=nbq+1
237           niq(nbq)=i_ho2
238         endif
239         i_h2o2=igcm_h2o2
240         if (i_h2o2.eq.0) then
241           write(*,*) "calchim: Error; no H2O2 tracer !!!"
242           stop
243         else
244           nbq=nbq+1
245           niq(nbq)=i_h2o2
246         endif
247         i_n2=igcm_n2
248         if (i_n2.eq.0) then
249           write(*,*) "calchim: Error; no N2 tracer !!!"
250           stop
251         else
252           nbq=nbq+1
253           niq(nbq)=i_n2
254         endif
255         i_ar=igcm_ar
256         if (i_ar.eq.0) then
257           write(*,*) "calchim: Error; no AR tracer !!!"
258           stop
259         else
260           nbq=nbq+1
261           niq(nbq)=i_ar
262         endif
263         i_ice=igcm_h2o_ice
264         if (i_ice.eq.0) then
265           write(*,*) "calchim: Error; no water ice tracer !!!"
266           stop
267         else
268           nbq=nbq+1
269           niq(nbq)=i_ice
270         endif
271         i_h2o=igcm_h2o_vap
272         if (i_h2o.eq.0) then
273           write(*,*) "calchim: Error; no water vapor tracer !!!"
274           stop
275         else
276           nbq=nbq+1
277           niq(nbq)=i_h2o
278         endif
279
280         write(*,*) 'calchim: found nbq=',nbq,' tracers'
281         write(*,*) '         i_co2=',i_co2
282         write(*,*) '         i_co=',i_co
283         write(*,*) '         i_o=',i_o
284         write(*,*) '         i_o1d=',i_o1d
285         write(*,*) '         i_o2=',i_o2
286         write(*,*) '         i_o3=',i_o3
287         write(*,*) '         i_h=',i_h
288         write(*,*) '         i_h2=',i_h2
289         write(*,*) '         i_oh=',i_oh
290         write(*,*) '         i_ho2=',i_ho2
291         write(*,*) '         i_h2o2=',i_h2o2
292         write(*,*) '         i_n2=',i_n2
293         write(*,*) '         i_ar=',i_ar
294         write(*,*) '         i_ice=',i_ice
295         write(*,*) '         i_h2o=',i_h2o
296!         write(*,*) '         niq(:)=',niq
297!         write(*,*) '     nqchem_min,nqmx=',nqchem_min,nqmx
298         
299         firstcall = .false.
300      end if ! if (firstcall)
301
302! Initialize output tendencies to zero (to handle case of tracers which
303! are not used in the chemistry (e.g. dust))
304      dqchim(:,:,:)=0
305      dqschim(:,:)=0
306
307
308c
309c=======================================================================
310c     loop over grid
311c=======================================================================
312c
313      do ig = 1,ngridmx
314c
315c     local updates
316c
317         foundswitch = 0
318         do l = 1,nlayermx
319            zt(ig,l)=pt(ig,l)+pdt(ig,l)*ptimestep
320            do i=1,nbq
321              iq=niq(i) ! get tracer index
322              zq(ig,l,iq) = pq(ig,l,iq) + pdq(ig,l,iq)*ptimestep
323              zycol(l,iq) = zq(ig,l,iq) * mmean(ig,l)/mmol(iq)
324            enddo
325            zpress(l) = pplay(ig,l)/100.
326            ztemp(l)  = zt(ig,l)
327            zdens(l)  = zpress(l)/(kb*1.e4*ztemp(l))
328            zlocal(l) = zzlay(ig,l)/1000.
329c
330c     search for switch index between regions
331c
332            if (photochem .and. thermochem) then
333               if (foundswitch .eq. 0 .and. pplay(ig,l).lt.1.e-3) then
334                  lswitch = l
335                  foundswitch=1
336               end if
337            end if
338            if ( .not. photochem) then
339               lswitch = 22
340            end if
341            if (.not.  thermochem) then
342               lswitch = min(33,nlayermx+1)
343            end if
344c
345c     ice surface area  in microns^2/cm^3
346c
347c     = 4 pi r^2 * [ zq * mugaz/NA / (rhoice*4/3 pi r^3) ] *zdens
348c     = 3/r * [ zq * mugaz/NA / rhoice ] *zdens
349c     with r in microns, rhoice = 0.92e-12 g microns^-3 and zdens in cm^-3
350c
351            if (water) then
352               zycol(l,i_ice) = (3.e-6/rice(ig,l))*zq(ig,l,i_ice)
353     $                           *(mugaz/6.022e23)*zdens(l)/0.92e-12
354c              write(*,*) "rice=",rice(ig,l)," m / zdens=",zdens(l),
355c    $        " cm-3 / icesurf=",zycol(l,nqmx-1)," microns^2/cm^3"
356               surfice(ig,l) = zycol(l,i_ice)
357            end if
358c
359         end do ! of do l=1,nlayermx
360c
361         szacol = acos(mu0(ig))*180./pi
362c
363c=======================================================================
364c     call chemical subroutine
365c=======================================================================
366c
367        if (photochem) then
368           if (scheme .eq. 1) then
369              print*,'Scheme A : A METTRE A JOUR !!'
370c             call photochemist_A(zycol,szacol,ptimestep,
371c    $                            zpress,ztemp,zdens,dist_sol)
372           else
373              call photochemist_B(lswitch,zycol,szacol,ptimestep,
374     $                            zpress,ztemp,zdens,dist_sol,jo3)
375           end if
376        end if
377
378        if (thermochem) then
379           call chemthermos(ig,lswitch,zycol,ztemp,zdens,zpress,
380     $                      zlocal,szacol,ptimestep,zday)
381        end if
382c
383c=======================================================================
384c     tendencies
385c=======================================================================
386c
387c     must be 0. for water ice:
388c
389         if (water) then
390            do l = 1,nlayermx
391!               dqchim(ig,l,nqmx-1) = 0.
392               dqchim(ig,l,i_ice) = 0.
393            end do
394         end if
395c
396c     tendency for CO2 = - sum of others for lower atmosphere
397c     tendency for O   = - sum of others for upper atmosphere
398c
399         do l = 1,nlayermx
400            if (l .lt. lswitch) then
401               do i=1,nbq
402                 iq=niq(i) ! get tracer index
403                  if ((iq.ne.i_co2).and.(iq.ne.i_ice)) then
404                     dqchim(ig,l,iq) = (zycol(l,iq)*mmol(iq)/mmean(ig,l)
405     $                                - zq(ig,l,iq))/ptimestep
406                  else if (iq.eq.i_co2) then
407                     dqchim(ig,l,iq) = 0.
408                  end if
409                  dqschim(ig,iq) = 0.
410               end do ! of do i=1,nbq
411               
412               do i=1,nbq
413                 iq=niq(i) ! get tracer index
414                  if (iq.ne.i_co2) then
415                     dqchim(ig,l,i_co2) = dqchim(ig,l,i_co2)
416     $                                  - dqchim(ig,l,iq)
417                  end if
418               end do
419             else if (l .ge. lswitch) then
420               do i=1,nbq
421                 iq=niq(i) ! get tracer index
422                   if ((iq.ne.i_o).and.(iq.ne.i_ice)) then
423                      dqchim(ig,l,iq) = (zycol(l,iq)*mmol(iq)
424     $                                  /mmean(ig,l)
425     $                                 - zq(ig,l,iq))/ptimestep
426                   else if (iq.eq.i_o) then
427!                      i_o = iq
428                      dqchim(ig,l,iq) = 0.
429                   end if
430               enddo
431               
432               do i=1,nbq
433                 iq=niq(i) ! get tracer index
434                   if (iq.ne.i_o) then
435                      dqchim(ig,l,i_o) = dqchim(ig,l,i_o)
436     $                                 - dqchim(ig,l,iq)
437                   end if
438               end do
439             end if ! of if (l.lt.lswitch) else if (l.ge.lswitch)
440          end do ! of do l = 1,nlayermx
441c
442c     dust: This is now taken care of as a first step at beginning of routine
443c
444!          if (nqchem_min .gt. 1) then
445!             do iq = 1,nqchem_min-1
446!                do l = 1,nlayermx
447!                   dqchim(ig,l,iq) = 0.
448!                end do
449!                dqschim(ig,iq) = 0.
450!             end do
451!          end if
452c
453c     condensation of h2o2
454c
455          call perosat(ig,ptimestep,pplev,pplay,
456     $                 ztemp,zycol,dqcloud,dqscloud)
457c
458c     for outputs
459c
460          do i=1,nbq
461            iq=niq(i) ! get tracer index
462             colden(ig,iq) = 0.
463             do l = 1,nlayermx
464c
465c     column density converted in cm-2
466c     pplev en pa, mugaz en g.mol-1 et g en m.s-2
467c     not for ice
468c
469                if (iq.ne.i_h2o2) then
470                  colden(ig,iq) = colden(ig,iq) + zycol(l,iq)
471     $                         *6.022e22*(pplev(ig,l)-pplev(ig,l+1))
472     $                         /(mmean(ig,l)*g)
473                else   ! for H2O2, remove condensation from zycol
474                  colden(ig,iq) = colden(ig,iq) + (zycol(l,iq) +
475     $               dqcloud(ig,l,iq)*ptimestep*mmean(ig,l)/mmol(iq))
476     $                         *6.022e22*(pplev(ig,l)-pplev(ig,l+1))
477     $                         /(mmean(ig,l)*g)
478                end if
479c
480c     local densities, for outputs (put in zq)
481c     not for ice
482c
483                zq(ig,l,iq) = zycol(l,iq)*zdens(l)
484c                        for H2O2, remove condensation from zycol
485                if (iq.eq.i_h2o2) then
486                   zq(ig,l,iq) = zdens(l)*(zycol(l,iq) +
487     $               dqcloud(ig,l,iq)*ptimestep*mmean(ig,l)/mmol(iq))
488                end if
489             end do
490          end do
491c
492c     density and j(o3->o1d), for outputs
493c
494          zdens3d(ig,1) = zdens(1)
495          jo3_3d(ig,1) = jo3(1)
496          do l = 2,nlayermx
497             zdens3d(ig,l) = zdens(l)
498             jo3_3d(ig,l) = jo3(l)
499          end do
500c
501c=======================================================================
502c     end of loop over grid
503c=======================================================================
504c
505      end do ! of do ig=1,ngridmx
506c
507c=======================================================================
508c     write outputs
509c=======================================================================
510c
511! value of parameter 'output' to trigger writting of outputs
512! is set above at the declaration of the variable.
513
514      if (output) then
515
516         if (ngridmx .gt. 1) then
517c           call writediagfi(ngridmx,'dens','atm dens.','cm-3',3,zdens3d(1,1))
518c           call writediagfi(ngridmx,'jo3','j o3->o1d','s-1',3,jo3_3d(1,1))
519c           call writediagfi(ngridmx,'sice','ice surf.','um2/cm3',3,surfice(1,1))
520            do i=1,nbq
521              iq=niq(i) ! get tracer index
522               if (iq.ne.i_ice) then
523                 write(str20(1:20),'(a20)') noms(iq)
524                 call writediagfi(ngridmx,'n_'//trim(str20),'density',
525     $                             'cm-3',3,zq(1,1,iq))
526c                 call writediagfi(ngridmx,'dqch_'//str5,'density','cm-3',3,dqchim(1,1,iq))
527c                 if (noms(iq) .eq. "h2o2" .or. noms(iq) .eq. "h2o") then
528c                    call writediagfi(ngridmx,'cl_'//str5,'density','cm-3',3,dqcloud(1,1,iq))
529c                 end if
530                 call writediagfi(ngridmx,'c_'//trim(str20),
531     $                            'col. dens.','cm-2',2,colden(1,iq))
532               end if
533            end do
534c
535            if (callstats) then
536c
537c              convert to mole.cm-2 for the column densities
538c
539               do i=1,nbq
540                 iq=niq(i) ! get tracer index
541                  do ig = 1,ngridmx
542                     colden(ig,iq) = colden(ig,iq)/6.022e23
543                  end do   
544               end do
545c
546c              call wstats(ngridmx,"jo3","jo3->o1d","s-1",3,jo3_3d)
547c
548               do i=1,nbq
549                 iq=niq(i) ! get tracer index
550                  if (iq.ne.i_ice) then
551                     write(str20(1:20),'(a20)') noms(iq)
552                     call wstats(ngridmx,"n_"//trim(str20),"density",
553     &                           "cm-3",3,zq(1,1,iq))
554                     call wstats(ngridmx,"c_"//trim(str20),"col. dens.",
555     &                           "mol cm-2",2,colden(1,iq))
556                  end if
557               end do ! of i=1,nbq
558            end if ! of if (callstats)
559         end if ! of if (ngridmx.gt.1)
560c
561      endif ! of if (output)
562c
563      end
Note: See TracBrowser for help on using the repository browser.