source: trunk/libf/phytitan/calchim.F @ 102

Last change on this file since 102 was 102, checked in by slebonnois, 14 years ago

SL : corrections et modifications dans phytitan correspondant a celles
faites apres compilation Venus. Titan pas encore compile.

File size: 16.9 KB
Line 
1      SUBROUTINE calchim(ny,qy_c,nomqy_c,declin_rad,ls_rad,dtchim,
2     .                   ctemp,cplay,cplev,
3     .                   dqyc)
4     
5c-------------------------------------------------
6
7c     Introduction d une routine chimique
8c
9c     Auteur: S. Lebonnois,  01/2000 | 09/2003
10c            adaptation pour Titan 3D: 02/2009
11c
12c-------------------------------------------------
13c
14      use dimphy
15      implicit none
16#include "dimensions.h"
17#include "clesphys.h"
18#include "paramet.h"
19#include "YOMCST.h"
20
21#include "titan_for.h" 
22!!!  doit etre en accord avec titan.h
23#include "aerprod.h"
24
25c    Arguments
26c    ---------
27
28      INTEGER      ny                     ! nb de composes (nqmax-nmicro)
29      REAL         qy_c(jjm+1,klev,NC)    ! Especes chimiques apres adv.+diss.
30      character*10 nomqy_c(NC+1)          ! Noms des especes chimiques
31      REAL         declin_rad,ls_rad      ! declinaison et long solaire en radians
32      REAL         dtchim                 ! pas de temps chimie
33      REAL         ctemp(jjm+1,klev)      ! Temperature
34      REAL         cplay(jjm+1,klev)      ! pression (Pa)
35      REAL         cplev(jjm+1,klev)      ! pression intercouches (Pa)
36     
37      REAL         dqyc(jjm+1,klev,nqtot)  ! Tendances especes chimiques (nqtot, mais en fait NC...)
38     
39c    Local variables :
40c    -----------------
41c variables envoyees dans la chimie: double precision
42
43      integer i,j,l,ic
44      REAL  temp_c(klev),press_c(klev)     ! T,p(mbar) a 1 lat donnee
45      REAL  declin_c                       ! declinaison en degres
46      REAL  cqy(klev,NC)                   ! frac mol qui seront modifiees
47      REAL  surfhaze(klev)
48      REAL  cprodaer(klev,4),cmaer(klev,4),ccsn(klev,4),ccsh(klev,4)
49      REAL  rinter(klev),nb(klev)
50      REAL  a,b
51      character str1*1,str2*2
52      integer ntotftop
53      parameter (ntotftop=50)
54      integer nftop(ntotftop),isaisonflux
55      REAL  fluxtop(NC),latit,tabletmp(ntotftop),factflux
56      character*10 nomsftop(ntotftop+1)
57      character*20 formt1,formt2,formt3
58     
59c     variables locales initialisees au premier appel
60
61      LOGICAL firstcal
62      DATA    firstcal/.true./
63      SAVE    firstcal
64     
65      REAL  mass(NC),duree
66      REAL  tablefluxtop(NC,jjm+1,5)
67      REAL  botCH4
68      DATA  botCH4/0.05/
69      REAL  krpd(15,ND+1,klev,jjm+1),krate(klev,NR)
70      integer reactif(5,NR),nom_prod(NC),nom_perte(NC)
71      integer prod(200,NC),perte(2,200,NC)
72      SAVE    mass,tablefluxtop,botCH4
73      SAVE    krpd,krate
74      SAVE    reactif,nom_prod,nom_perte,prod,perte
75     
76c-----------------------------------------------------------------------
77c***********************************************************************
78c
79c    Initialisations :
80c    ----------------
81
82      duree = dtchim  ! passage en real*4 pour appel a routines C
83
84      IF (firstcal) THEN
85           
86        print*,'CHIMIE, premier appel'
87       
88c ************************************
89c Au premier appel, initialisation de toutes les variables
90c pour les routines de la chimie.
91c ************************************
92
93c Verification dimension verticale: coherence titan_for.h et klev
94c --------------------------------
95
96        if (klev.ne.NLEV) then
97           print*,'PROBLEME de coherence dans la dimension verticale:'
98     .           ,klev,NLEV
99           STOP
100        endif
101
102c Verification du nombre de composes: coherence titan_for.h et nqmax-nmicro
103c ----------------------------------
104
105        if (ny.ne.NC) then
106           print*,'PROBLEME de coherence dans le nombre de composes:'
107     .           ,ny,NC
108           STOP
109        endif
110
111c calcul de temp_c, densites et press_c a l'equateur:
112c --------------------------------------------------
113
114        print*,'pression, densites et temp a l equateur (chimie):'
115        print*,'level, press_c, nb, temp_c'
116        DO l=1,klev
117c     temp_c (K):
118         temp_c(l)  = ctemp(jjm/2+1,l)
119c     press_c (mbar):
120         press_c(l) = cplay(jjm/2+1,l)/100.
121c     nb (cm-3):
122         nb(l) = 1.e-4*press_c(l) / (RKBOL*temp_c(l))
123         print*,l,press_c(l),nb(l),temp_c(l)
124        ENDDO
125       
126c caracteristiques des composes:       
127c -----------------------------
128        mass = 0.0
129        call comp(nomqy_c,mass)
130        print*,'           Mass'
131        do ic=1,NC
132          print*,nomqy_c(ic),mass(ic)
133        enddo
134       
135
136c FLUX AU SOMMET: DEPENDANT DE LA LATITUDE ET DE LA SAISON...
137
138c flux dans la derniere couche:(issu du modele 1D, a 500 km)
139c -----------------------------
140c       !!  en cm-2.s-1 !!
141c  ces valeurs sont converties en cm-3.s-1 (dni/dt) dans a couche 54
142c
143c Lecture des tables de flux en fonction lat et saison
144c ----------------------------------------------------
145
146        WRITE(str2(1:2),'(i2.2)') ntotftop
147        formt1 = '(A10,'//str2//'(3X,A10))'
148        formt2 = '(F12.6,'//str2//'(2X,F13.6))'
149        formt3 = '(F13.6,'//str2//'(2X,F13.6))'
150       
151        do j=1,jjp1
152          do ic=1,NC
153            do l=1,5
154             tablefluxtop(ic,j,l) = 0.
155            enddo
156          enddo
157        enddo
158       
159        do l=1,4
160          WRITE(str1(1:1),'(i1.1)') l
161c hx1 -> Ls=RPI/2 / hx4 -> Ls=0
162          open(10,file="../../INPUT/FLUXTOP/flux500.hs"//str1)
163c         open(10,file="FLUXTOP/flux500.hs"//str1)
164c on remet l=1 et 5 -> Ls=0 / l=2 -> Ls=RPI/2 ...
165
166          read(10,formt1) nomsftop
167          do j=1,ntotftop
168           do i=1,10   !justification a gauche...
169             if (nomsftop(j+1)(i:i).ne.' ') then
170                nomsftop(j) = nomsftop(j+1)(i:)
171                goto 100
172             endif
173           enddo
174100        continue
175c         print*,nomsftop(j)
176           nftop(j) = 0
177           do i=1,NC
178            if (nomqy_c(i).eq.nomsftop(j)) then
179             nftop(j) = i
180            endif
181           enddo
182c          if (nftop(j).ne.0) print*,nomsftop(j),nomqy_c(nftop(j))
183          enddo
184
185         
186c lecture des flux. Les formats sont un peu alambiques...
187c     a revoir eventuellement
188          do j=1,jjp1/2+1
189            read(10,formt2) latit,tabletmp
190            do i=1,ntotftop
191              if (nftop(i).ne.0) then
192               tablefluxtop(nftop(i),j,l+1) = tabletmp(i)
193              endif
194            enddo
195          enddo
196          do j=jjp1/2+2,jjp1
197            read(10,formt3) latit,tabletmp
198            do i=1,ntotftop
199              if (nftop(i).ne.0) then
200               tablefluxtop(nftop(i),j,l+1) = tabletmp(i)
201              endif
202            enddo
203          enddo
204
205          close(10)
206        enddo  ! l
207       
208        do j=1,jjp1
209          do ic=1,NC
210             tablefluxtop(ic,j,1) = tablefluxtop(ic,j,5)
211          enddo
212        enddo
213       
214c  Stockage des composes utilises dans la prod d'aerosols
215c     (aerprod=1) et dans H-> H2 (htoh2=1): utilaer
216c     ! decalage de 1 car utilise dans le c !
217c ------------------------------------------
218c + modifs du flux en fonction des obs UVIS et CIRS: C2H2,C2H6,HCN
219c + modifs des flux qui presentent un probleme evident: C3H8 et C4H10
220c ------------------------------------------
221
222        do ic=1,NC
223
224c!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
225c!!!remise de CH4 a 1.5%!!!!!!!!!!!!!!!!!!!!!!
226c!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
227c         if (nomqy_c(ic).eq."CH4") then
228c           do l=1,llm
229c            do j=1,ip1jmp1
230c              if (qy_c(j,l,ic).le.0.015) qy_c(j,l,ic) = 0.015
231c            enddo
232c           enddo
233c         endif
234c!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
235         
236          if (nomqy_c(ic).eq."C4H2") then
237            utilaer(10) = ic-1
238          endif
239          if (nomqy_c(ic).eq."HCN") then
240            utilaer(6)  = ic-1
241            do j=1,jjp1
242              do i=1,5
243             tablefluxtop(ic,j,i) = tablefluxtop(ic,j,i) * 6.
244              enddo
245            enddo
246          endif
247          if (nomqy_c(ic).eq."HC3N") then
248            utilaer(7)  = ic-1
249          endif
250          if (nomqy_c(ic).eq."NCCN") then
251            utilaer(14) = ic-1
252          endif
253          if (nomqy_c(ic).eq."CH3CN") then
254            utilaer(15) = ic-1
255            utilaer(16) = ic-1 ! si pas C2H3CN, CH3CN utilise, mais reac. nulle
256          endif
257          if (nomqy_c(ic).eq."H") then
258            utilaer(1)  = ic-1
259          endif
260          if (nomqy_c(ic).eq."H2") then
261            utilaer(2)  = ic-1
262          endif
263          if (nomqy_c(ic).eq."C2H2") then
264            utilaer(3)  = ic-1
265            do j=1,jjp1
266              do i=1,5
267c             tablefluxtop(ic,j,i) = tablefluxtop(ic,j,i) * 7.3
268             tablefluxtop(ic,j,i) = tablefluxtop(ic,j,i) * 10.
269              enddo
270            enddo
271          endif
272          if (nomqy_c(ic).eq."AC6H6") then
273            utilaer(13) = ic-1
274          endif
275          if (nomqy_c(ic).eq."C2H3CN") then
276            utilaer(16) = ic-1
277          endif
278          if (nomqy_c(ic).eq."C2") then
279            utilaer(4)  = ic-1
280          endif
281          if (nomqy_c(ic).eq."C2H") then
282            utilaer(5)  = ic-1
283          endif
284          if (nomqy_c(ic).eq."C3N") then
285            utilaer(8)  = ic-1
286          endif
287          if (nomqy_c(ic).eq."H2CN") then
288            utilaer(9)  = ic-1
289          endif
290          if (nomqy_c(ic).eq."C4H3") then
291            utilaer(11) = ic-1
292          endif
293          if (nomqy_c(ic).eq."AC6H5") then
294            utilaer(12) = ic-1
295          endif
296
297          if (nomqy_c(ic).eq."C2H6") then
298            do j=1,jjp1
299              do i=1,5
300c             tablefluxtop(ic,j,i) = tablefluxtop(ic,j,i) * 640.
301             tablefluxtop(ic,j,i) = tablefluxtop(ic,j,i) * 1200.
302              enddo
303            enddo
304          endif
305          if (nomqy_c(ic).eq."C3H8") then
306            do j=1,jjp1
307              do i=1,5
308c             tablefluxtop(ic,j,i) = tablefluxtop(ic,j,i) * (-1.)
309             tablefluxtop(ic,j,i) = tablefluxtop(ic,j,i) * (-3000.)
310              enddo
311            enddo
312          endif
313          if (nomqy_c(ic).eq."C4H10") then
314            do j=1,jjp1
315              do i=1,5
316             tablefluxtop(ic,j,i) = tablefluxtop(ic,j,i) * (-1.)
317              enddo
318            enddo
319          endif
320
321c!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
322c         if ((nomqy_c(ic).eq."HC3N").or.
323c    $        (nomqy_c(ic).eq."C3N")) then
324c     DO j=1,ip1jmp1
325c       do l=1,34  ! p>~ 1 mbar
326c         qy_c(j,l,ic) = 1.e-30
327c       enddo
328c     ENDDO
329c         endif
330c!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
331
332        enddo
333               
334c taux de photodissociations:
335c --------------------------
336        call disso(krpd,jjp1)
337
338c reactions chimiques:
339c -------------------
340        call chimie(nomqy_c,nb,temp_c,krate,reactif,
341     .               nom_perte,nom_prod,perte,prod)
342c        print*,'nom_prod, nom_perte:'
343c        do ic=1,NC
344c          print*,nom_prod(ic),nom_perte(ic)
345c        enddo
346c        print*,'premieres prod, perte(1:reaction,2:compagnon):'
347c        do ic=1,NC
348c          print*,prod(1,ic),perte(1,1,ic),perte(2,1,ic)
349c        enddo
350
351c       l = klev-3
352c       print*,'krate a p=',press_c(l),' reactifs et produits:'
353c       do ic=1,ND+1
354c         print*,ic,krpd(7,ic,l,4)*nb(l),"  ",
355c    .     nomqy_c(reactif(1,ic)+1),
356c    .     nomqy_c(reactif(2,ic)+1),nomqy_c(reactif(3,ic)+1),
357c    .     nomqy_c(reactif(4,ic)+1),nomqy_c(reactif(5,ic)+1)
358c       enddo
359c       do ic=ND+2,NR
360c         print*,ic,krate(l,ic),"  ",
361c    .     nomqy_c(reactif(1,ic)+1),
362c    .     nomqy_c(reactif(2,ic)+1),nomqy_c(reactif(3,ic)+1),
363c    .     nomqy_c(reactif(4,ic)+1),nomqy_c(reactif(5,ic)+1)
364c       enddo
365
366      ENDIF  ! premier appel
367
368c***********************************************************************
369c-----------------------------------------------------------------------
370
371c   calcul declin_c (en degres)
372c   ---------------------------
373
374      declin_c = declin_rad*180./RPI
375c      print*,'declinaison en degre=',declin_c
376       
377c-----------------------------------------------------------------------
378c
379c   calcul du facteur d'interpolation entre deux saisons pour flux
380c   --------------------------------------------------------------
381
382       isaisonflux = int(ls_rad*2./RPI)+1
383       if (isaisonflux.eq.5) then
384         isaisonflux = 1
385       endif
386       factflux =    (sin(ls_rad)-sin((isaisonflux-1)*RPI/2.))/
387     .   (sin(isaisonflux*RPI/2.)-sin((isaisonflux-1)*RPI/2.))
388
389c***********************************************************************
390c***********************************************************************
391c
392c                BOUCLE SUR LES LATITUDES
393c
394      DO j=1,jjp1
395     
396c***********************************************************************
397c***********************************************************************
398
399c-----------------------------------------------------------------------
400c
401c   Temperature, pression (mbar), densite (cm-3)
402c   -------------------------------------------
403
404       DO l=1,klev
405c     temp_c (K):
406               temp_c(l)  = ctemp(j,l)
407c     press_c (mbar):
408               press_c(l) = cplay(j,l)/100.
409c     nb (cm-3):
410               nb(l) = 1.e-4*press_c(l) / (RKBOL*temp_c(l))
411       ENDDO
412       
413c-----------------------------------------------------------------------
414c
415c   Distances radiales (intercouches, en km)
416c   ----------------------------------------
417
418       rinter(1) = RA/1000. 
419       do l=2,klev
420c A REVOIR: g doit varier avec r !
421         rinter(l) = rinter(l-1) +
422     .    (cplev(j,l-1)-cplev(j,l))/cplay(j,l)*(RD*temp_c(l)/RG)/1000.
423c        print*,rinter(l)
424       enddo
425
426c!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
427c FLUX AU TOP: interpolation en saison et
428c conversion en cm-3 s-1 dans la couche klev-1 (NLEV-2 dans le C)
429c!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
430        do ic=1,NC
431          fluxtop(ic) = tablefluxtop(ic,j,isaisonflux)  *(1-factflux)
432     .                + tablefluxtop(ic,j,isaisonflux+1)*  factflux
433          fluxtop(ic) = fluxtop(ic)/((rinter(klev)-rinter(klev-1))*1e5)
434        enddo
435
436c TEST: sortie de l'un des flux avec saveLs et factflux
437c       dans un fichier special pour tracer avec gnuplot
438c       if (j.eq.2) then
439c       open(unit=11,file="flux_80N.txt",status='old',position='append')
440c         write(11,*) ls_rad*180./RPI, factflux,
441c    .           ((rinter(llm)-rinter(llm-1))*1e5), fluxtop
442c         write(11,*) ls_rad*180./RPI, factflux,
443c    .     fluxtop(utilaer(3)+1)*((rinter(llm)-rinter(llm-1))*1e5),  !C2H2
444c    .     fluxtop(utilaer(6)+1)*((rinter(llm)-rinter(llm-1))*1e5)   !HCN
445c       close(11)
446c       endif
447c       if (j.eq.17) then
448c       open(unit=11,file="flux_eq.txt",status='old',position='append')
449c         write(11,*) ls_rad*180./RPI, factflux,
450c    .           ((rinter(llm)-rinter(llm-1))*1e5), fluxtop
451c         write(11,*) ls_rad*180./RPI, factflux,
452c    .     fluxtop(utilaer(3)+1)*((rinter(llm)-rinter(llm-1))*1e5),  !C2H2
453c    .     fluxtop(utilaer(6)+1)*((rinter(llm)-rinter(llm-1))*1e5)   !HCN
454c       close(11)
455c       endif
456c FIN TEST: sortie de l'un des flux avec ls et factflux
457
458c!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
459
460       if (firstcal.and.(j.eq.1)) then
461         print*,'Alt, densites et temp au pole (chimie):'
462         print*,'level, z_bas, nb, temp_c'
463         do l=1,klev
464          print*,l,rinter(l)-RA/1000.,nb(l),temp_c(l)
465         enddo
466       endif
467
468       if (firstcal.and.(j.eq.jjm/2)) then
469c         print*,'g,mugaz'
470c         print*,g,mugaz
471         print*,'Alt, densites et temp a l equateur (chimie):'
472         print*,'level, z_bas, nb, temp_c'
473         do l=1,klev
474          print*,l,rinter(l)-RA/1000.,nb(l),temp_c(l)
475         enddo
476       endif
477       
478c-----------------------------------------------------------------------
479c
480c   composition
481c   ------------
482       
483       do ic=1,NC
484        do l=1,klev
485          cqy(l,ic) = qy_c(j,l,ic)
486        enddo
487       enddo
488             
489c-----------------------------------------------------------------------
490c
491c   total haze area (um2/cm3)
492c   -------------------------
493
494       if (htoh2.eq.1) then
495        do l=1,klev
496! ATTENTION, INVERSION PAR RAPPORT A pg2.F !!!
497         surfhaze(l) = psurfhaze(j,klev+1-l)
498c        if (j.eq.25)
499c    .    print*,'psurfhaze en um2/cm3:',surfhaze(l)
500        enddo
501       endif
502
503c-----------------------------------------------------------------------
504c
505c   Appel de chimietitan
506c   --------------------
507       
508       call gptitan(jjp1,rinter,temp_c,nb,
509     $              nomqy_c,cqy,fluxtop,
510     $              declin_c,duree,(j-1),mass,
511     $              botCH4,krpd,krate,reactif,
512     $              nom_prod,nom_perte,prod,perte,
513     $              aerprod,utilaer,cmaer,cprodaer,ccsn,ccsh,
514     $              htoh2,surfhaze)
515       
516c       if ( j.eq.jjm/2 )
517c    $        print*,cqy(1,1),cqy(klev,1),cqy(1,2),cqy(klev,2)
518c       if ( j.eq.jjm/2 )
519c    $  print*,qy_c(j,1,1),qy_c(j,klev,1),qy_c(j,1,2),qy_c(j,klev,2)
520
521c       stop
522
523c   Tendances composition
524c   ---------------------
525     
526       do ic=1,NC
527        do l=1,klev
528          dqyc(j,l,ic) = (cqy(l,ic) - qy_c(j,l,ic))/dtchim  ! en /s
529        enddo
530       enddo
531
532c-----------------------------------------------------------------------
533c
534c   production aer
535c   --------------
536       
537       if (aerprod.eq.1) then
538
539       do ic=1,4
540        do l=1,klev
541          prodaer(j,l,ic) = cprodaer(l,ic)
542          maer(j,l,ic)    = cmaer(l,ic)
543          csn(j,l,ic)     = ccsn(l,ic)
544          csh(j,l,ic)     = ccsh(l,ic)
545        enddo
546       enddo
547
548       endif
549
550c***********************************************************************
551c***********************************************************************
552c
553c              FIN: BOUCLE SUR LES LATITUDES
554c
555      ENDDO
556     
557c***********************************************************************
558c***********************************************************************
559
560
561      firstcal = .false.
562      RETURN
563      END
Note: See TracBrowser for help on using the repository browser.