source: trunk/LMDZ.TITAN.old/libf/phytitan/pg2.old @ 3303

Last change on this file since 3303 was 1545, checked in by emillour, 9 years ago

Venus and Titan GCMs:

Adaptation wrt previous changes for Titan and Venus where
longitude and latitude arrays (in phycommon/geometry_mod) were overwritten
with values from startphy.nc files, where values are given in degrees.
For the sake of homegeneity with other physics package, revert to "default"
behaviour: longitude/latitude are in radians and longitude_deg/latitude_deg
are in degrees.
Also added checking in phyetat0 that the longitude/latitude read in the
restartphy.nc files match the ones provided by the dynamics.

EM

File size: 17.7 KB
Line 
1            subroutine pg2(
2     &      tpplev,tpt,tq,tdq,nq,ptimestep,mu0,fract,last)
3c
4c
5c
6c
7c
8c
9c    &      tpplev,tpt,tq,tdq,nq,ptimestep,last)
10c                     /                    \
11c       |  PHYSIQUE  | AEROSOLS            |
12c
13c                     \|/
14c                    (o o)
15c-----------------oOo--O--oOo--------------------------
16c                     
17c Interface entre physiq.F et aerosols.F
18c
19c Date: 5 Nov 96
20c
21c   -->(  )          q(x,nlayer,nq)
22c
23c             q(x,nlayer,nq) <==>  c(nz,nrad)
24c
25c          c(nz,nrad)(t) -->  aerosol.F --> c(nz,nrad)(t+dt)
26c
27c             c(nz,nrad) <==> q(x,nlayer,nq)
28c     
29c              c(IHOR,NRAD,NRAD)  en aerosols
30c              c0(NZ,NRAD)        en aerosols/m^3 
31c
32c   L'ECHANGE N'EST POSSIBLE QUE SI LES QUANTITES SONT
33c   DES NOMBRES D'AEROSOLS.........
34c
35c   LES QUANTITES Q SONT EN AEROSOLS / CASE (BOUT DE COLONNE
36c   DE 1m^2 * DZ(J)..................ATTENTION AU PASSAGE
37c      PHYSIQUE <---> DYNAMIQUE QUI A BESOINS DE ????
38c
39c   LE MODELE MICROPHYSIQUE A BESOIN DE CONCENTRATIONS
40c                     AEROSOLS/M^3
41c------------------------------------------------------
42
43      use dimphy
44      USE geometry_mod, ONLY: latitude_deg
45#include "dimensions.h"
46#include "microtab.h"
47#include "paramet.h"
48#include "aerprod.h"
49#include "clesphys.h"
50#include "YOMCST.h"
51
52     
53        parameter (NG=jjm+1)   ! NG: on travaille en moyenne zonale
54 
55c*************************************
56c declaration des variables internes *
57c*************************************
58       
59c       GCM        *
60c------------------*
61
62        real tzzlev(ng,klev+1)
63     &         ,tpplev(ng,klev+1)
64     &         ,tzzlay(ng,klev)
65     &         ,tpt(ng,klev)
66     &         ,tq(ng,klev,nq)
67     &         ,tdq(ng,klev,nq)
68        real   mu0(ng),fract(ng)
69
70        real    zzlev(NG,klev+1)
71     &         ,pplev(NG,klev+1)
72     &         ,zzlay(NG,klev)
73     &         ,pt(NG,klev)
74     &         ,q(NG,klev,nq)
75     &         ,qdel(NG,klev,nq)
76     &         ,qcumul(NG,0:200,nq)
77
78        integer jsup,jinf,h
79 
80        logical last
81
82
83c    microphysique    *
84c---------------------*
85
86        real aire(ng),airetot,lati(ng)
87        save aire,lati
88
89        real z(nz),zb(nz+1),alt(200)
90        real dz(nz),dzb(nz+1)
91        real pb(nz+1),p(nz)
92        real tb(nz+1),t(nz)
93 
94        real c0(200,nrad),c(nz,nrad),ctp(nz,nrad)
95        double precision c0lu(200,nrad)
96        real cmemoire(nz,nrad)
97        real micropas,ddt
98
99      integer iprem
100      save iprem
101      data iprem/0/
102
103c          print*,'DEBUT DE PG2'
104
105
106         ngrid=ng
107         nlayer=klev
108         if(nrad.ne.nq) then
109             print*,'microphysique:nrad.ne.nq:',nrad,nq
110             stop
111         endif
112
113* ici, on evalue les niveaux d'altitudes en fonction des niveaux de
114*  pressions.
115
116          do h=1,ngrid
117          tpplev(h,nlayer+1)=tpplev(h,nlayer)*.1
118          enddo
119
120        r=8.314*1000./28.
121
122* pour chaque point de grille
123
124       do h=1,ngrid
125         zz=0.
126         tzzlev(h,1)=zz
127
128* bord de couche
129
130        do l=1,nlayer
131         eff_g = 1.345*(2575./(2575.+zz/1000.))**2
132          zz=zz+r*2.*tpt(h,l)/
133     &    eff_g*(tpplev(h,l)-tpplev(h,l+1))/(tpplev(h,l)+tpplev(h,l+1))
134          tzzlev(h,l+1)=zz
135c         print*,l,eff_g,tpplev(h,l),tpplev(h,l+1),zz
136        enddo
137
138* milieu  de couche
139
140        do l=1,nlayer
141        xlog=( alog(tpplev(h,l+1)) + alog(tpplev(h,l)) )/2.
142        rapport=(tzzlev(h,l+1)-tzzlev(h,l))
143     &             /(alog(tpplev(h,l+1))-alog(tpplev(h,l)))
144        tzzlay(h,l)=rapport*(xlog-alog(tpplev(h,l+1)))
145     &              +tzzlev(h,l+1)
146        enddo
147       enddo
148
149
150c       PRINT*,'PROFILE #1'
151c       h=10
152c       do l=1,nlayer
153c        print*, tpplev(h,l),tpt(h,l),tq(h,1,1),tq(h,l,7)
154c       enddo
155c        print*, tpplev(h,nlayer+1)
156
157         do j=1,200
158           alt(j)=(j-1)*5000.     !0 5000 10000 15000 .......!
159         enddo
160         
161
162
163
164c                       **************************
165c                       INITIALISATION DE TABLEAUX
166c                       **************************
167c                         A NE FAIRE QU'UNE FOIS
168c                       **************************
169
170 
171        IF (iprem.eq.0) THEN
172
173       qdel = 0.
174
175c initialisation de aire(ig)
176c --------------------------
177
178      airetot=0.
179     
180      lati(1)     = 0.5*RPI
181      DO ig=2,ngrid-1
182        lati(ig)  = latitude_deg(2+(ig-2)*iim)*RPI/180.
183      ENDDO
184      lati(ngrid) = -0.5*RPI
185     
186      DO ig=1,ngrid
187      if(ig.eq.1)
188     &   aire(ig)=2*RPI*(1.-sin(lati(ig)/2.+lati(ig+1)/2.))*RA*RA
189      if(ig.eq.ngrid)
190     &   aire(ig)=2*RPI*(1.+sin(lati(ig-1)/2.+lati(ig)/2.))*RA*RA
191       if(ig.ne.1. .and. ig.ne.ngrid) aire(ig)=2*RPI*RA*RA*
192     &      (sin(lati(ig-1)/2.+lati(ig)/2.)
193     &      -sin(lati(ig)/2.+lati(ig+1)/2.))
194
195      airetot=airetot+aire(ig)
196      ENDDO
197c     print*,"ENTREE PG2 PREMIER APPEL"
198c     print*,airetot,' airetot?= ',4.*RPI*RA*RA
199c     print*,1,latitude_deg(1),aire(1),aire(1)/airetot,' aires'
200c     DO ig=2,ngrid-1
201c     print*,ig,latitude_deg(2+(ig-2)*iim),aire(ig),aire(ig)/airetot,' aires'
202c     ENDDO
203c     print*,ngrid,latitude_deg(klon),aire(ngrid),aire(ngrid)/airetot,' aires'
204c     stop
205     
206c initialisation de c(z,r)
207c --------------------------
208
209
210        itype=2
211
212
213c remplissage type 1:            OBSOLETE !
214c----------------------
215
216
217        if(itype.eq.1) then !****************************
218
219        taer=tcorrect
220
221#ifdef CRAY
222        open (unit=32,file='aerosols',status='old',iostat=ii,
223     1  form='formatted')
224        if(ii.ne.0) then
225           print*,'WARNING!!! pas de reinitialisation des traceurs'
226           print*,'On part des traceurs contenus dans start'
227           return
228        endif
229        print*,'pg2 apres open version cray',ii
230        read(32,'(e8.3)') tt
231        read(32,'(5e10.3)') c0
232        close(32)
233#else
234        print*,'pg2 avant open'
235        open (unit=31,file='initfich',iostat=ii,
236     1  access='sequential',form='formatted')
237
23813      read(unit=31,fmt=1010,iostat=ii,end=15)tt,((c0lu(j,k),
239     1   k=1,nrad),j=1,200)
2401010    format(e8.3,2000(e8.3))
241
24215      continue
243
244c Conversion: lecture en double, variable utile en simple...
245        do j=1,200
246        do k=1,nrad
247          c0(j,k) = real(c0lu(j,k))
248c          print*,c0(j,k)
249        enddo
250        enddo
251#endif
252 
253c        print*,'fichier microphysique'
254c        do j=1,200
255c        print*,'L&0',j,c0(j,1),c0(j,3),c0(j,5),c0(j,7),c0(j,9)
256c        enddo
257
258         close (unit=31)
259       
260         do k=1,nrad
261         do h=1,ngrid
262            qcumul(h,0,k)=0.
263            qcumul(h,1,k)=c0(200,k)*taer*5000.
264          do j=2,200
265            qcumul(h,j,k)=c0(200-j+1,k)*taer*5000.+qcumul(h,j-1,k)   
266          enddo
267          do j=1,nlayer
268           qdel(h,j,k)=tq(h,j,k)   ! etat q provenant des starts a effacer!
269           tq(h,j,k)=0.
270          enddo
271         enddo
272         enddo
273c        do j=1,200
274c        print*,'L&1',j,qcumul(12,j,1),qcumul(12,j,3),qcumul(12,j,5)
275c        enddo
276         write(92,*) qdel
277
278c interpolation des q_cumules
279
280c         do j=1,nlayer
281c          print*,tzzlev(10,j),alt(j)
282c         enddo
283         do k=1,nrad
284         do h=1,ngrid
285          jsup=int(tzzlev(h,2)/5000.+2.)
286          xfact=tzzlev(h,2)/alt(jsup)
287          tq(h,1,k)=xfact*qcumul(h,1,k)
288          do j=2,nlayer
289             jsup=int(tzzlev(h,j+1)/5000.+2.)
290             jinf=int(tzzlev(h,j+1)/5000.+1.)
291             xfact=(tzzlev(h,j+1)-alt(jinf))/(alt(jsup)-alt(jinf))
292             tq(h,j,k)=xfact*(qcumul(h,jsup-1,k)-qcumul(h,jinf-1,k))
293     &       +qcumul(h,jinf-1,k)
294          enddo
295         enddo
296         enddo
297
298c soustraction des q_cumules
299
300         do k=1,nrad
301         do h=1,ngrid
302         do j=nlayer,2,-1
303          tq(h,j,k)=tq(h,j,k)-tq(h,j-1,k)
304         enddo
305         enddo
306         enddo
307
308c on inverse q <--> tq, et tq=0 ====> dq=q-qt a la fin pour intitialiser.
309
310         do k=1,nrad
311         do h=1,ngrid
312         do j=nlayer,1,-1
313             q(h,j,k)=tq(h,nlayer-j+1,k)
314             tq(h,nlayer-j+1,k)=0.
315
316c        if (h.eq.12) then
317c         if (k.eq.nrad) then
318c            print*,'L&3',j,q(12,j,1),q(12,j,3),q(12,j,5)
319c          endif
320c        endif
321
322         enddo
323         enddo
324         enddo
325           print*,'itype=1'
326
327         do h=1,ngrid
328          somme=0.
329         do k=1,nrad
330         do j=nlayer,1,-1
331         ref=1.63789E-09*(2.**.3333333333)**(4.*(k-1))
332           somme=somme+q(h,j,k)*4.1888*ref**3.
333         enddo
334         enddo
335           print*,'bilan externe: m3/m2 grid#',h, somme
336         enddo
337
338
339           else  !**********************************
340
341c remplissage type 2:
342c----------------------
343
344c       open (unit=31,file='finfich',iostat=ii,
345c    1  access='sequential',form='formatted')
346
347c       read(unit=31,fmt=1011,iostat=ii,end=18)tt,(((q(i,j,k),
348c    1  k=1,nrad),j=1,nlayer),i=1,ngrid)
349c8      continue
350c       close (unit=31)
351c----------------------
352
353
354          print*,'entre dans itype2'
355
356
357         do k=1,nrad
358         do h=1,ngrid
359         do j=nlayer,1,-1
360
361         
362
363          q(h,nlayer+1-j,k)=tq(h,j,k)*tcorrect
364
365             tq(h,j,k)=0. 
366c
367c  Car les q initiaux sont lus dans la physiq, mais les dq doivent
368c  etre passes dans la dynamique via dqfi. C'est ici que les valeurs
369c  de dqfi=(q_lu*tcorrect - 0) sont definie
370
371         enddo
372         enddo
373         enddo
374
375
376           print*,'itype=2'
377         do h=1,ngrid
378          somme=0.
379         do k=1,nrad
380         do j=nlayer,1,-1
381         ref=1.63789E-09*(2.**.3333333333)**(4.*(k-1))
382           somme=somme+q(h,j,k)*4.1888*ref**3.
383         enddo
384         enddo
385           print*,'bilan externe: m3/m2 grid#',h, somme
386         enddo
387
388
389
390
391
392        endif
393
394
395        ENDIF !FIN IPREM
396 
397
398
399c             ************************************
400c                FIN: A NE FAIRE QU'UNE FOIS
401c             ************************************
402c             
403
404
405
406c          ************************************
407c            IL FAUT INVERSER LES TABLEAUX...           
408c          ************************************
409
410
411
412
413       do n=1,ngrid
414         do j=1,NLAYER+1               ! j de 1 a 120
415           zzlev(n,j)=tzzlev(n,nlayer-j+2) ! indice de 120 a 1
416           pplev(n,j)=tpplev(n,nlayer-j+2)
417         enddo
418       enddo
419
420c les tq() doivent etre en nombre d'aerosols / cases
421
422       do j=1,NLAYER                ! j de 1 a 119
423         do n=1,ngrid
424           zzlay(n,j)=tzzlay(n,nlayer-j+1)  ! indice de 119 a 1
425           pt(n,j)=tpt(n,nlayer-j+1)
426         enddo
427       enddo
428
429        if (iprem.eq.0) goto 119  ! pour ne pas effacer les q()|t=0
430
431       do j=1,NLAYER                ! j de 1 a 119
432         do n=1,ngrid
433           do i=1,nq
434             qdel(n,j,i)=0.
435             q(n,j,i)=tq(n,nlayer-j+1,i)
436           enddo
437         enddo
438       enddo
439
440 119    continue
441
442
443c               ******************************
444c                      BILAN DE MASSE
445c               ******************************
446
447       total=0.
448       do ihor=1,ngrid
449          do iq=1,nq
450           do JALT=1,nlayer
451            total=total+tq(ihor,JALT,iq)*(16.**(iq-5))*aire(ihor)
452           enddo
453          enddo
454       enddo
455c         print*,'Bilan entree masse des qaer (unite M_mono)',total   
456   
457
458c****************************************
459c                                       *
460c         ADAPTATION GCM > micro        *
461c                                       *
462c****************************************
463
464
465c correpondance des couches / sens GCM > microphysique
466c-----------------------------------------------------
467c
468c But remplir les c(nz,i) avec les concentrations
469c Q(ng,NLAYER,i) d'aerosols calculee par gcm.F
470
471
472 
473      totalc1=0.
474      totalc2=0.
475     
476      if (iprem.eq.0) then
477c ici, les tableaux definissant la structure des aerosols sont
478c remplis: rf,df(nq),rayon(nq,)v(nq)......
479       call rdf()
480      endif
481
482
483
484c---------------------------------------------
485
486       IF (iprem.eq.0) goto 102
487
488c      !! La premiere fois, on ne passe pas par
489c      !! q--->c et par pg3.F
490c      !! on passe directement au remplissage c-->q
491c---------------------------------------------
492
493       
494       do IHOR=1,NGRID      ! GRANDE BOUCLE HORIZONTALE
495
496         cpt=0.
497         cpx=0.
498         nzhau=0
499 
500
501       do JALT=1,nlayer-1         ! 1ere BOUCLE SUR Z (indice nz=1,120)
502         dz(jalt)=(zzlay(ihor,jalt)-zzlay(ihor,jalt+1))
503       enddo   
504         dz(nlayer)=dz(nlayer-1)  ! ARBITRAIRE ET SANS IMPORTANCE!!!!!
505
506       do JALT=1,nlayer         ! 1ere BOUCLE SUR Z (indice nz=1,120)
507         dzb(jalt)=(zzlev(ihor,jalt)-zzlev(ihor,jalt+1))
508         pb(jalt)=pplev(ihor,jalt)
509         t(jalt)=pt(ihor,jalt)
510       enddo
511         pb(nlayer+1)=pplev(ihor,nlayer+1)
512 
513
514
515c** T(>300km) = T(300km)
516
517
518         pb(nlayer+1)=pplev(IHOR,nlayer+1)
519
520         zb1=zzlev(ihor,1)
521         z1 =zzlay(ihor,1)
522
523
524c        if(ihor.eq.12)
525c    &   print*,'nzhau pour la latitude # ',ihor,' : ',nzhau
526c        if(ihor.eq.1)
527c    &   print*,'nzhau pour la latitude # ',ihor,' : ',nzhau
528c        if(ihor.eq.24)
529c    &   print*,'nzhau pour la latitude # ',ihor,' : ',nzhau
530
531
532c Interpolation des tableaux tb et p a partir de t et pb
533c******************************************************
534
535        do i=1,nz-1
536         tb(i+1)=(t(i)+t(i+1))/2.  ! temperature au bord des couches
537        enddo
538
539         tb(1)=t(1)
540         tb(nz+1)=(t(nz)-t(nz-1))*.5+t(nz)
541         
542        do i=1,nz
543         p(i)=(alog(pb(i))+alog(pb(i+1)))/2. ! pression au centre des couches
544         p(i)=exp(p(i))
545        enddo
546
547
548       
549c****************************************
550c
551c   APPEL DU MODEL MICROPHYSIQUE
552c
553c****************************************
554
555
556        do i=1,nrad
557         do j=1,nz
558          c(j,i)=q(IHOR,j,i)/dzb(j) ! concentration aerosols/m^3
559         enddo
560        enddo
561
562c                                   -------
563101      continue
564
565
566       ddt=0.
567       micropas=min(36000.,ptimestep)       
568103    micropas=micropas/2.
569      ddt=ptimestep/(int(ptimestep/(2*micropas))*1.)/2. 
570      if (int(ptimestep/ddt/2.).lt.2) goto 103
571
572      call pg3(dz,dzb,tb,t,pb,p,c,z1,zb1,ptimestep,ddt
573     & ,nzhau,ihor,mu0(ihor),fract(ihor))
574
575 
576       do i=1,nrad
577         do j=1,nz
578            totalc2=totalc2+c(J,i)*dzb(j)
579     &      *2.**(i*7.-7.)
580          q(IHOR,j,i)=c(j,i)*dzb(j) ! nombre  aerosols
581         enddo
582       enddo
583
584       ENDDO             ! Fin de la boucle IHOR
585
586
587102   CONTINUE           ! la premiere fois, c'est une boucle vide!
588
589
590
591c***************************************************************
592c FIN: on renvoie les nouvelles valeurs de dq=q(t+dt)-q(t)
593c***************************************************************
594
595
596
597
598       do n=1,ngrid
599       do i=1,nq
600       do j=1,NLAYER                ! j de 1 a 54
601
602
603          tdq(n,nlayer+1-j,i)=0.
604
605          tdq(n,nlayer+1-j,i)=(q(n,j,i)
606     &                         -tq(n,nlayer+1-j,i))/ptimestep
607
608       if (tdq(n,nlayer+1-j,i).eq.0.)  tdq(n,nlayer+1-j,i)=1.e-20
609       enddo
610       enddo
611       enddo
612
613c Calcul de la surface des aerosols pour la chimie heterogene
614c-------------------------------------------------------------
615
616       do ihor=1,ngrid
617       do jalt=1,nlayer
618
619         dzb(jalt)=(zzlev(ihor,jalt)-zzlev(ihor,jalt+1))
620         psurfhaze(ihor,jalt)=0.
621
622         do iq=1,nq
623          if(iq .le. 6)
624     &       surf1=4.*3.1415926353*rf(6)**2./(2.519842**(6-iq))**2.
625          if(iq .gt. 6)
626     &       surf1=4.*3.1415926353*rf(6)**2. * (16.**(iq-6))
627
628            psurfhaze(ihor,jalt)=psurfhaze(ihor,jalt)+
629     &             q(ihor,nlayer+1-jalt,iq)/dzb(jalt)*surf1
630         enddo
631
632         psurfhaze(ihor,jalt)=psurfhaze(ihor,jalt)
633     &                        *1.e12/1.e6  !passage m^2/m^3 a um^2/cm^3
634c        print*,psurfhaze(ihor,jalt),dzb(jalt),q(ihor,nlayer+1-jalt,1)
635c    &         ,surf1,rf(6)
636
637         enddo
638       enddo
639
640c***** WARNING, SI IPREM=0 ON DOIT EGALEMENT SOUSTRAIRE QDEL
641c******* VOIR PLUS LOIN. DANS CE CAS, LA BOUCLE SI DESSUS
642c****** NE SRT QU'A FAIRE LE BIALN DQ=Q_FICHIER-0
643c**** LE DQ EFFECTIVEMENT PRIS EN COMPTE EST CALCULE APRES LE BILAN
644
645c      BILAN DE MASSE SORTIE
646
647
648       total=0.
649       tmass=0.
650       do ihor=1,ngrid
651          do iq=1,nq
652           do JALT=1,nlayer
653            total=total+tdq(ihor,JALT,iq)*(16.**(iq-5))
654     .                      *aire(ihor)*ptimestep
655            tmass=tmass+q(ihor,JALT,iq)*(16.**(iq-5))*aire(ihor)
656           enddo
657          enddo
658       enddo
659c         print*,'Bilan sortie masse des qaer (unite M_mono)',
660c    .                  tmass,total,total/tmass   
661
662
663c POUR LE PREMIER PASSAGE, IL FAUT ELIMINER L'ETAT DE Q
664c PROVENANT DE LA LECTURE DES FICHIERS STARTS
665c QD DOIT DONC CONTENIR -QDEL
666
667       if (iprem.eq.0) then
668
669       do n=1,ngrid
670       do i=1,nq
671       do j=1,NLAYER                ! j de 1 a 54
672
673             tdq(n,nlayer+1-j,i)=0.
674
675             tdq(n,nlayer+1-j,i)=(q(n,j,i)
676     &                         -tq(n,nlayer+1-j,i)
677     &                       -qdel(n,nlayer+1-j,i))/ptimestep
678
679
680       tq(n,nlayer+1-j,i)=tq(n,nlayer+1-j,i)+qdel(n,nlayer+1-j,i)
681
682       if (tdq(n,nlayer+1-j,i).eq.0.)  tdq(n,nlayer+1-j,i)=1.e-20
683
684       enddo
685       enddo
686       enddo
687       endif
688
689c      print*,'ok1'
690c EN GENERAL, TDQ= (Q_FICHIER - Q_START)/PTIMESTEP
691
692 
693          iprem=1       ! LA PROCHAINE FOIS NE SERA PLUS LA 1ERE
694c      print*,'************************************'
695c      print*,'***********TABLEAU APRES************'
696c      print*,'************************************'
697c      do h=12,12
698c      do j=1,NLAYER
699c         print*,'exit',h,j,tdq(h,j,7),q(h,j,7),tpt(h,j),tpplev(h,j)
700c      enddo
701c      enddo
702c      print*,'************************************'
703
704c Au dernier appel...on ecrit finfich
705
706          if (last) then
707        open (unit=31,file='finfich',iostat=ii,
708     1  access='sequential',form='formatted')
709
710
711         write(unit=31,fmt=1011,iostat=ii)tt,(((q(i,j,k),
712     1   k=1,nrad),j=1,nz),i=1,ngrid)
713         endif
714c        print*,'ok2'
715
7161011    format(e8.3,21000(e8.3))
717
718 
719 16      return 
720 500    print*,'erreur lecture initfich'
721          stop
722 499    print*,'erreur ouverture initfich'
723          stop
724          end
725
726
727c---------------------------------------------------------------------
Note: See TracBrowser for help on using the repository browser.