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

Last change on this file since 3303 was 175, checked in by slebonnois, 13 years ago

S.LEBONNOIS:

  • Revision majeure de la physique Titan => ajout des nuages version 10 bins (Jeremie Burgalat) Cette version reste a tester mais avec clouds=0, on reste sur l'ancienne.
  • Quelques ajouts dans la doc.
File size: 37.1 KB
Line 
1        subroutine pg3(tab1,tab2,tab3,tab4,tab5,tab6,tab7,
2     &  x1,x2,x3,x4,xnztop,ihor,xmu0,xfract)
3
4c     call pg3(dz,dzb,tb,t,pb,p,c,z1,zb1,ptimestep,ddt
5c    & ,nzhau,ihor)
6
7
8*1  dz, pas d'altitude pour les milieux de couches
9*2  dzb, pas d'altitude pour les limites superieures de couches
10*34 tb,t temperature a la limite superieure des couches et
11*4         au milieu des couches 
12*56 pb,p pression a la limite superieure des couches et
13*6         au milieu des couches 
14*7  c nombre de particules de la grille de rayon r a l'altitude z
15*1  z1, altitude du milieu de la couche superieure de l'atmosphere.
16*2  zb1, altitude de la limite superieure de la couche superieure
17*          de l'atmosphere
18*3  tmax, duree , en jour, de l'execution
19*4  dt, pas de temps, en heure. 
20
21*--------------------------------------------------------------*
22*                                                              *
23*            ENTRE 0 ET 1000 KILOMETRES                        *     
24*                                                              *
25*    la dimension fractale est en tableau, attention au        *
26*    raccordement entre le regime moleculaire et le regime     *
27*    fluide                                                    *
28*                                                              *
29*    Modele microphysique:    Cabane et al.,1992 /             *
30*    Modele version fractale: Cabane et al.,1993 /             *
31*                                                              *
32*--------------------------------------------------------------*
33* VERSION DU 2 JUIN 1993  --- AUT 1994 --- 11/04/96
34*
35* changer: altitude de production zalt0=/taux de production ctot=
36*        : la charge/micron, ne
37*        : df(h),rf...
38* raccordement aknc
39*
40* declaration des blocs communs
41*------------------------------
42
43#include "dimensions.h"
44#include "microtab.h"
45#include "clesphys.h"
46
47        common/donnees/p,t,rho,ach4,aar,an2,pb,tb,rhob
48        common/ini/z1,zb1,c0 
49        common/phys/pi,nav,rgp,kbz,rtit,g0,mch4,mar,mn2,rhol
50        common/grille/z,zb,dz,dzb
51        common/ctps/li,lf,tt,dt
52        common/con/c
53        common/part/v,rayon,vrat,dr,dv
54        common/coag/k
55        common/effets/ xsaison
56
57 
58* declaration des variables communes
59* ----------------------------------
60
61        integer xnztop
62        integer li,lf
63        real dt,tt
64        real p(nz),t(nz),rho(nz),ach4(nz),aar(nz),an2(nz)
65     &  ,pb(nz),tb(nz),rhob(nz)
66        real pi,nav,rgp,kbz,rtit,g0,mch4,mar,mn2,rhol
67        real zb(nz),z(nz),dz(nz),dzb(nz)
68        real c0(nz,nrad),c(nz,nrad,2)
69        real v(nrad),rayon(nrad),vrat,dr(nrad),dv(nrad)
70        real k(nz,nrad,nrad),knu
71        real xmu0,xfract
72       
73
74*  variables internes
75*  ------------------
76
77        integer h,ti,tmax,itime
78        real tab1(nz),tab2(nz+1),tab3(nz+1),tab4(nz)
79        real tab5(nz+1),tab6(nz),tab7(nz,nrad)
80        real x1,x2,x3,x4
81        real knd1,knd2,knd3,knd4,knd5,knd6
82
83       save itime
84       data itime/0/
85* initialisation
86* --------------
87
88c      print*,'Df aerosols /1 a nqtot/'
89c       write(*,*) (df(h),h=1,nrad)
90c       write(*,*) (rayon(h),h=1,nrad)
91c       write(*,*) (dr(h),h=1,nrad)
92c       write(*,*) (v(h),h=1,nrad)
93c       write(*,*) (dv(h),h=1,nrad)
94c       print*,vrat,rf,aknc
95
96* effet saisonnier
97* ----------------
98
99
100         xsaison=0.
101         xsaison=xmu0*4.*xfract 
102                              !=Pi si fract=1/2 (equinoxe) et
103                              !    si mu0=1 sous le soleil
104                              !    exactement.
105
106c        xsaison=0.
107c        if (ihor.le.9.or.ihor.ge.41) xsaison=8.  ! rapport des surfaces
108c        xsaison=1.
109
110* controles
111* ---------
112
113        do i=1,nz       
114         dz(i)=tab1(i)
115         dzb(i)=tab2(i)
116         tb(i)=tab3(i)
117         t(i)=tab4(i)
118         pb(i)=tab5(i)                 
119         p(i)=tab6(i)
120          do j=1,nrad
121            c(i,j,1)=tab7(i,j)
122            c(i,j,2)=0.0
123          enddo
124        enddo
125        z1=x1
126        zb1=x2
127        tmax=int(x3/x4)/2       ! 2. * tmax iterations
128        dt=x4                    ! 
129       
130
131        z(1)=z1 
132        zb(1)=zb1
133 
134        do 12 i=2,nz
135          z(i)=z(i-1)-dz(i-1)
136          zb(i)=zb(i-1)-dzb(i-1)
13712      continue
138
139c        print*, tmax,dt,z1,zb1
140c       do i=1,nz
141c        print*,i,z(i),p(i),t(i),zb(i),pb(i),tb(i),c(i,1,1)
142c       enddo
143 
144c       stop 'profile'
145
146       if (itime.eq.0) then
147
148        ITIME=1
149c        print*,'avant init'
150         call init
151c        print*,'apres init'
152c        print*,'avant calcoag'
153         call calcoag
154c        print*,'apres calcoag'
155
156c        print*,'***** TEST COAGULATION ********'
157c       do h=1,nz,20
158c        do i=1,3
159c         print*,'KOAG',h,i,k(h,1,i),k(h,2,i),k(h,3,i)
160c        enddo
161c       enddo
162
163       endif
164
165
166* iteration du modele sur le temps
167* ---------------------------------
168c      print*,'##############################################'
169c         print*,'debut microphysique'
170c       print*,'Df aerosols /1 a 6/'
171c       write(*,*) (df(h),h=1,6)
172c         call ecran(tt)
173c
174c      print*,'CHECK BEFORE COMPUTATION'
175c      print*,'nrad=',nrad,' nqtot=',nqtot,' ctrl...'
176c      print*,'##############################################'
177c      print*,'1.0 - tableaux de bases:'
178c      print*,'i        rayon(i)        '
179c       do i=1,nrad
180c        print*,i,rayon(i)
181c       enddo
182c      print*,'temps appel      pas de temps:'
183c      print*,tmax, dt
184c      print*,'##############################################'
185c      print*,'1.1 - Avec l altitude: '
186c      print*,' i       v1  v3 v5 v6 '
187c      print*, 'i       z(i)    c(i,1,1)        c(i,4,1)        c(i,6,1)'
188c      print*,'***      dz(i)   dzb(i)'
189c      print*,'***      pb(i)   p(i)    t(i)    tb(i)'
190c
191c      if(ihor.eq.25.or.IHOR.EQ.1.) THEN
192c       do i=1,nz,1
193c         print*,i,z(i),c(i,1,1),c(i,4,1),c(i,6,1)
194c         print*,'pbpttb',pb(i),p(i),t(i),tb(i)
195c            v1=vitesse(i,7,0)
196c            v2=vitesse(i,8,0)
197c            v3=vitesse(i,9,0)
198c            v4=vitesse(i,10,0)
199c            print*,ihor,z(i),v1,v2,v3,v4
200c      enddo
201c      endif
202c      if(ihor.eq.25) STOP
203c
204c       if (ihor.eq.25.or.ihor.eq.48.or.ihor.eq.1) then
205c      print*,'##############################################'
206c       print*,'ihor=',ihor
207c       do i=1,nz,1
208c             knd1=knu(i,5,1)
209c             knd2=knu(i,6,1)
210c             knd3=knu(i,7,1)
211c             knd4=knu(i,8,1)
212c             knd5=knu(i,9,1)
213c             knd6=knu(i,10,1)
214c         print*,i,z(i),knd2,knd4,knd6
215c      enddo
216c
217c      if(ihor.eq.49) STOP
218c
219c      endif
220c
221c      print*,'1.2 - Avec les rayons:'
222c      print*,'h        i       j       k(h,i,j)'
223c        do j=1,nqtot
224c         print*,h,i,j,k(h,i,j)
225c      enddo
226c      print*,'##############################################'
227c       stop 'end check'
228
229
230c       somme=0.
231c       do i=1,nz
232c        do j=1,nrad
233c         somme=somme+c(i,j,1)*dzb(i)*4.1888*rayon(j)**3.
234c        enddo
235c       enddo
236 
237c       print*,'bilan interne: ',somme,'  volume/m^2'
238
239
240                                            ! 1,tmax,2*dt :
241        do 10 ti=1,tmax                     ! a chaque passage, deux pas
242                                            ! de temps sont franchis....
243*  1ere iteration
244
245           tt=tt+dt
246
247            call coagul
248
249            call production(ihor)
250
251c           call nuages
252
253           li=3-li
254           lf=3-lf
255
256            call sedif
257
258
259
260
261*  2ieme iteration
262
263        tt=tt+dt
264
265        li=3-li
266        lf=3-lf
267
268
269        call sedif
270
271        li=3-li
272        lf=3-lf
273
274        call coagul
275
276        call production(ihor)
277
278c       call nuages
279
280            li=3-li
281            lf=3-lf
282
283
284
28510      continue
286
287379      continue
288
289          do i=1,nz
290           do j=1,nrad
291              tab7(i,j)=c(i,j,li)     ! li=1
292           enddo
293          enddo
294         
295c        total=0.
296c         do i=1,nz
297c          do j=1,nrad
298c             total=total+tab7(i,j)*dzb(j)*rayon(j)**3.
299c    &        *(1.333333*3.1415926)*1000.
300c          enddo
301c         enddo
302c          print*,'bilan colonne kg/m^2:',total
303
304
305777      return 
306
307         end
308*________________________________________________________________________
309                     subroutine ecran(tt)
310
311#include "dimensions.h"
312#include "microtab.h"
313cparameter(nz=200,nrad=nqtot,nztop=135)
314        common/con/c
315        real c(nz,nrad,2)
316          print*,'--------------------'
317          print*,'ecriture micro:'
318         do i=140,200,20
319         print*, c(i,1,1),c(i,4,1),c(i,6,1)
320         enddo
321
322        return
323        end
324
325
326
327
328                    subroutine coagul
329
330
331*********************************************************
332* ce programme calcule la nouvelle concentration dans   *
333* le a ieme intervalle de rayon, a l'altitude h, a      *
334* l'instant t+dt                                        *
335*********************************************************
336
337#include "dimensions.h"
338#include "microtab.h"
339
340* declaration des blocs communs
341*------------------------------
342
343        common/donnees/p,t,rho,ach4,aar,an2,pb,tb,rhob
344        common/phys/pi,nav,rgp,kbz,rtit,g0,mch4,mar,mn2,rhol
345        common/grille/z,zb,dz,dzb
346        common/ctps/li,lf,tt,dt
347        common/con/c
348        common/part/v,rayon,vrat,dr,dv
349
350* declaration des variables
351* --------------------------
352
353        integer li,lf
354        real tt,dt
355cparameter(nz=200,nrad=nqtot,nztop=135)
356        real p(nz),t(nz),rho(nz),ach4(nz),aar(nz),an2(nz),pi,nav
357        real pb(nz),tb(nz),rhob(nz)
358        real rgp,kbz,rtit,g0,mch4,mar,mn2,rhol,dz(nz)
359        real vrat,dr(nrad),dv(nrad)
360        real c(nz,nrad,2),v(nrad),rayon(nrad),z(nz),zb(nz),dzb(nz)
361
362* declaration des variables propres au ss-programme
363* -------------------------------------------------
364
365        integer h,a
366        real pr,pe
367
368*  traitement
369*  ----------
370
371
372        do 10 h=nztop,nz
373           do 11 a=1,nrad
374               call pertpro(h,a,pe,pr)
375c           if((1+dt*pe).lt.0.) stop 'denom.eq.0'
376            c(h,a,lf)=(c(h,a,li)+pr*dt)/(1+dt*pe)
377         
37811         continue
37910      continue
380
381        if (nztop.ne.1) then
382          do 12 h=1,nztop-1
383             do 12 a=1,nrad
384               c(h,a,lf)=c(h,a,li)
38512        continue
386        endif
387
388        return
389        end
390     
391     
392*__________________________________________________________________________
393
394             subroutine  calcoag
395
396***************************************************************
397*                                                             *
398*  Ce programme calcule les coefficients de collection  d'une *
399* particule de rayon x avec une particule de rayon b a une    *
400* altitude donnee h                                           *
401***************************************************************
402
403* declaration des blocs communs
404*------------------------------
405#include "dimensions.h"
406#include "microtab.h"
407
408        common/donnees/p,t,rho,ach4,aar,an2,pb,tb,rhob
409        common/phys/pi,nav,rgp,kbz,rtit,g0,mch4,mar,mn2,rhol
410        common/grille/z,zb,dz,dzb
411        common/ctps/li,lf,tt,dt
412        common/con/c
413        common/part/v,rayon,vrat,dr,dv
414        common/coag/k
415
416* declaration des variables
417* --------------------------
418
419        integer li,lf
420        real tt,dt
421cparameter(nz=200,nrad=nqtot)
422        real p(nz),t(nz),rho(nz),ach4(nz),aar(nz),an2(nz),pi,nav
423        real pb(nz),tb(nz),rhob(nz)
424        real rgp,kbz,rtit,g0,mch4,mar,mn2,rhol,dz(nz)
425        real vrat,dr(nrad),dv(nrad)
426        real c(nz,nrad,2),v(nrad),rayon(nrad),z(nz),zb(nz),dzb(nz)
427        real knu,nud,k(nz,nrad,nrad)
428
429* declaration des variables propres au ss-programme
430* -------------------------------------------------
431
432        integer h,b,x
433        real nua,lambb,lambx,knb,knx,alphab,alphax,d,e,f,kcg
434        real db,dx,rm,dm,deltab,deltax,del,g,beta,gx,gb
435         real*8 ne,qe,epso
436         real*8 corelec,yy
437
438        real kco,vx,vb,vitesse,sto,ee,a,dd,bb,p0,t0,l0,ccol
439        real st(37),ef(37)
440
441* initialisation
442* --------------
443c        print*,'**** calcoag'
444
445*  -nombres de STOCKES
446
447        data(st(i),i=1,37)/1.35,1.5,1.65,1.85,2.05,2.25,2.5,2.8,3.1,
448     s    3.35,3.6,3.95,4.3,4.7,5.05,5.45,5.9,6.4,7.,7.6,8.3,9.05,9.9,
449     s       10.9,11.1,13.5,15.3,17.25,20.5,24.5,30.4,39.3,48,57,86.,
450     s       187.,600./
451
452*  -coef. d'efficacite de collection
453
454        ef(1)=3.75
455        ef(2)=8.75
456        do 11 i=3,37
457        ef(i)=ef(i-1)+2.5
45811      continue
459
460        do 2 i=1,37
461        ef(i)=ef(i)*1e-2
4622       continue
463
464        qe=1.6e-19
465        ne=-30e+6
466        epso=1e-9/(36*pi)
467
468        d=1.257
469        e=0.4
470        f=-1.1
471
472*  iteration sur z
473 
474        do 1 h=1,nz
475        nua=nud(h,1)     
476
477*  iteration sur les rayons
478
479         do 1 b=1,nrad
480
481        knb=knu(h,b,1)
482        vb=vitesse(h,b,1)
483
484           do 1 x=1,b
485
486        knx=knu(h,x,1)
487        vx=vitesse(h,x,1)
488
489
490
491**  COAGULATION  ****************************************************
492** --------------****************************************************
493* calcul du terme correcteur 'slip-flow'
494
495        alphab=d+e*exp(f/knb)
496        alphax=d+e*exp(f/knx)
497
498* calcul du coefficient de diffusion
499
500        rfb=(rayon(b)**(3./df(b)))*((rf(b))**(1.-3./df(b)))
501        rfx=(rayon(x)**(3./df(x)))*((rf(x))**(1.-3./df(x)))
502        db=kbz*t(h)*(1+alphab*knb)/(6*pi*nua*rfb)
503        dx=kbz*t(h)*(1+alphax*knx)/(6*pi*nua*rfx)
504
505* calcul du coefficient de coagulation
506
507
508        rpr=rfb+rfx
509        kcg=4*pi*rpr*(db+dx)
510
511* calcul de la vitesse thermique
512
513        gx=sqrt(6*kbz*t(h)/(rhol*pi**2*rayon(x)**3))
514        gb=sqrt(6*kbz*t(h)/(rhol*pi**2*rayon(b)**3))
515
516* calcul du libre parcours apparent des aerosols
517
518        lambb=8*db/(pi*gb)
519        lambx=8*dx/(pi*gx)
520
521*calcul du terme correcteur beta
522
523        rm=rpr/2.
524        dm=(dx+db)/2.
525        g=sqrt(gx**2+gb**2)
526        deltab=(((2*rfb+lambb)**3-(4*rfb**2+lambb**2)**1.5)
527     s  /(6*rfb*lambb)-2*rfb)*sqrt(2.)
528        deltax=(((2*rfx+lambx)**3-(4*rfx**2+lambx**2)**1.5)
529     s  /(6*rfx*lambx)-2*rfx)*sqrt(2.)
530        del=sqrt(deltab**2+deltax**2)
531        beta=1/((rm/(rm+del/2))+(4*dm/(g*rm)))
532
533* calcul du coefficient de coagulation corrige
534
535        kcg=kcg*beta
536
537
538
539
540
541**  COALESCENCE  **************************************************
542**  -------------**************************************************
543
544
545        kco=0.
546
547        if ( b.eq. x) goto 9
548
549
550* calcul du nombre de Stockes de la petite particule
551
552        sto=2*rhol*rfx**2*abs(vx-vb)/(9*nua*rfb)
553
554* calcul du coef. de Cunningham-Millikan
555
556        a=1.246
557        bb=0.42
558        dd=0.87
559        l0=0.653e-7
560        p0=101325.
561        t0=288.
562
563        ee=1+(l0*t(h)*p0*(a+bb*exp(-dd*rfx*t0*p(h)/(l0*t(h)*p0))))
564     s    /(rfx*t0*p(h))
565
566* calcul du nombre de Stockes corrige
567
568        sto=sto*ee
569
570        if (sto .le. 1.2) goto 9
571
572        if (sto .ge. 600.) then
573           ccol=1.
574           goto 8
575        endif
576
577*  recherche du coefficient de collection
578
579        do 3 i=1,37
580          if (sto .gt. st(i)) then
581             goto 3
582          endif
583
584          if (sto .eq. st(i)) then
585                ccol=ef(i+1)
586          else
587                ccol=ef(i)
588          endif
589          goto 8
5903       continue
591
592*  calcul du coefficient de coalescence
593
5948        kco=pi*(rfb+rfx)**2*ccol*abs(vb-vx)
595
5969       continue
597
598**  CORRECTION ELECTRICITE *******************************
599**  ------------------------******************************
600
601
602        yy=1.d0*ne**2*rayon(x)*rayon(b)*qe**2
603     &  /(1.d0*kbz*t(h)*(rayon(b)+rayon(x))*4*pi*epso)
604
605        corovo=1
606        corcoll=1.                    ! efficacite de collage
607
608        corelec=0.
609        if (yy.lt.50.) corelec=yy/(exp(yy)-1.)
610
611        k(h,b,x)=(kcg+kco)*corelec*corovo*corcoll
612        k(h,x,b)=k(h,b,x)
613 
614
6151       continue
616        return
617        end
618
619*______________________________________________________________________
620
621            real function lambda(j,indic)
622*
623*------------------------------------------------------------------*
624*  fonction calculant le libre parcours moyen des molecules        *
625*  atmospheriques( rayon =ra) se trouvant dans la couche no j.     *
626*  pour indic=0  ...... la particule se trouve a la frontiere entre*
627*                        les couches j et j-1                      *
628*  pour indic=1  ...... la particule se trouve au milieu de la     *
629*                         la couche j                              *
630*------------------------------------------------------------------*
631*
632* declaration des blocs communs
633*------------------------------
634#include "dimensions.h"
635#include "microtab.h"
636
637        common/donnees/p,t,rho,ach4,aar,an2,pb,tb,rhob
638        common/phys/pi,nav,rgp,kbz,rtit,g0,mch4,mar,mn2,rhol
639        common/grille/z,zb,dz,dzb
640
641* declaration des variables communes
642* ----------------------------------
643
644cparameter(nz=200,nrad=nqtot)
645        real p(nz),t(nz),rho(nz),ach4(nz),aar(nz),an2(nz),pb(nz),tb(nz),
646     s     rhob(nz)
647        real pi,nav,rgp,kbz,rtit,g0,mch4,mar,mn2,rhol
648        real zb(nz),z(nz),dz(nz),dzb(nz)
649
650*  declaration des variables internes
651*  ----------------------------------
652
653        integer indic
654        real pp,ra
655
656        ra=1.75e-10
657
658* traitement
659* ----------
660
661        if (indic.eq.0) then
662           pp=pb(j)
663        else
664             if (indic.ne.1) then
665               print*,'erreur argument fonction lambda'
666               return
667             endif
668          pp=p(j)
669        endif
670
671        lambda=kbz*t(j)/(4*sqrt(2.)*pi*(ra**2)*pp)
672        end
673
674*******************************************************************************
675
676            real function knu(j,k,indic)
677*
678*--------------------------------------------------------------*
679*  fonction calculant le nombre de knudsen d'une particule     *
680*  d'aerosol de rayon rayon(k) se trouvant dans la couche no j *
681*  indic ......  idem function lambda                          *
682*--------------------------------------------------------------*
683*
684* declaration des blocs communs
685*------------------------------
686#include "dimensions.h"
687#include "microtab.h"
688
689        common/part/v,rayon,vrat,dr,dv
690
691* declaration des variables communes
692* ----------------------------------
693
694cparameter(nz=200,nrad=nqtot)
695        real v(nrad),rayon(nrad),vrat,dr(nrad),dv(nrad)
696
697*  declaration des variables internes
698*  ----------------------------------
699
700        integer indic
701        real lambda
702
703* traitement
704* ----------
705
706        if (indic.ne.0 .and.indic.ne.1) then
707               print*,'erreur argument fonction knu'
708               return
709        endif
710
711        rfk=(rayon(k)**(3./df(k)))*((rf(k))**(1.-3./df(k)))
712        knu=lambda(j,indic)/rfk
713        end
714
715*****************************************************************************
716
717             real function nud(j,indic)
718*
719*--------------------------------------------------------------*
720*  fonction calculant la viscosite dynamique (en USI) de l'air *
721*  d'apres la formule de Sutherlant a l'altitude j             *
722*  indic  ......... idem fonction lambda                       *
723*--------------------------------------------------------------*
724*
725#include "dimensions.h"
726#include "microtab.h"
727        integer indic
728cparameter (nz=200)
729        real nud0,c,tt
730        real p(nz),t(nz),rho(nz),ach4(nz),aar(nz),an2(nz),pb(nz),tb(nz),
731     s     rhob(nz)
732        common/donnees/p,t,rho,ach4,aar,an2,pb,tb,rhob
733*
734        nud0=1.74e-5
735        c=109.
736
737        if(indic.ne.0.and.indic.ne.1) then
738           print*,'erreur argument fonction nud'
739           return
740        endif
741
742        if(indic.eq.0) tt=tb(j)
743        if (indic.eq.1) tt=t(j)
744
745        nud=nud0*sqrt(tt/293)*(1+c/293)/(1+c/tt)
746        end
747
748****************************************************************************
749
750            real function vitesse(j,k,indic)
751*
752*-----------------------------------------------------------------*
753*  fonction calculant la vitesse de chute d'une particule de rayon*
754*  k se trouvant a l'altitude j  suivant la valeur du nombre de   *
755*   Knudsen                                                       *
756*  indic ....... idem function lambda                             *
757*-----------------------------------------------------------------*
758*
759
760* declaration des blocs communs
761*------------------------------
762#include "dimensions.h"
763#include "microtab.h"
764
765        common/donnees/p,t,rho,ach4,aar,an2,pb,tb,rhob
766        common/phys/pi,nav,rgp,kbz,rtit,g0,mch4,mar,mn2,rhol
767        common/grille/z,zb,dz,dzb
768        common/part/v,rayon,vrat,dr,dv
769
770* declaration des variables communes
771* ----------------------------------
772
773cparameter(nz=200,nrad=nqtot)
774        real p(nz),t(nz),rho(nz),ach4(nz),aar(nz),an2(nz)
775     s  ,pb(nz),tb(nz),rhob(nz)
776        real pi,nav,rgp,kbz,rtit,g0,mch4,mar,mn2,rhol
777        real zb(nz),z(nz),dz(nz),dzb(nz)
778        real v(nrad),rayon(nrad),vrat,dr(nrad),dv(nrad)
779
780*  declaration des variables internes
781*  ----------------------------------
782
783        integer indic
784        real w,g,m,a0,zz,knu,nud,knud,tt,rhoh
785
786*  traitement
787*  ----------
788
789        if (indic.ne.0.and.indic.ne.1) then
790            print*,'erreur argument fonction vitesse'
791            return
792        endif
793
794        if(indic.eq.0) then
795            zz=z(j)+dz(j)/2.
796            tt=tb(j)
797            rhoh=rhob(j)
798        endif
799        if(indic.eq.1) then
800           zz=z(j)
801           tt=t(j)
802           rhoh=rho(j)
803        endif
804
805        g=g0*(rtit/(rtit+zz))**2
806        a0=0.74
807        m=(ach4(j)*mch4+aar(j)*mar+an2(j)*mn2)/nav
808        knud=knu(j,k,indic)
809
810
811        akncx=aknc
812        if(df(k).gt.2.5) akncx=2.7
813
814        if(knud.ge.akncx) then
815
816        rbis=(rayon(k)**(3.-6./df(k)))*((rf(k))**(-2.+6./df(k)))
817          w=a0*g*rbis*rhol/(rhoh*sqrt(8*kbz*tt/(pi*m)))
818        endif
819
820        if(knud.lt.akncx) then
821
822        rfk=(rayon(k)**(3./df(k)))*((rf(k))**(1.-3./df(k)))
823          w=2./9.*rfk**(df(k)-1.)*rf(k)**(3.-df(k))*g*rhol/nud(j,indic)
824
825           if(knud.gt.0.01)  w=w*(1+knud)
826        endif
827
828c       if (p(j).lt.500..and.k.eq.nrad) then
829c          w=0.
830c       endif
831
832
833
834        vitesse=w
835        end
836***********************************************************************
837       
838              real function kd(h)
839*
840*--------------------------------------------------------------------*
841*  cette fonction calcule le coefficient du terme de 'eddy diffusion'*
842*  a l'altitude j                                                    *
843*--------------------------------------------------------------------*
844*
845
846#include "dimensions.h"
847#include "microtab.h"
848        common/donnees/p,t,rho,ach4,aar,an2,pb,tb,rhob
849        common/phys/pi,nav,rgp,kbz,rtit,g0,mch4,mar,mn2,rhol
850        common/grille/z,zb,dz,dzb
851
852
853cparameter(nz=200,nrad=nqtot)
854        real p(nz),t(nz),rho(nz),ach4(nz),aar(nz),an2(nz),pb(nz),tb(nz),
855     s   rhob(nz)
856        real pi,nav,rgp,kbz,rtit,g0,mch4,mar,mn2,rhol
857        real zb(nz),z(nz),dz(nz),dzb(nz)
858
859        integer h
860
861         zbx=z(h)+dz(h)/2.
862        if(zbx.le.42000.) then
863              kd=4.
864              kd=1.64e+12*(pb(h)/(kbz*tb(h)))**(-1./2.)
865        else
866c             kd=1.e+15*(pb(h)/(kbz*tb(h)))**(-2./3.)
867              kd=1.64e+12*(pb(h)/(kbz*tb(h)))**(-1./2.)
868        endif
869
870         kd=0.0*kd
871
872        return
873        end
874
875
876*____________________________________________________________________________
877
878           subroutine init
879*
880*--------------------------------------------------------------------*
881*  cette routine effectue  :                                         *
882*               1) interpolation a partir des donnees initiales des  *
883*                   valeurs de p,t,rho,ach4,aar,an2  sur la grille   *
884*               2) initialisation des constantes (common/phys/)      *
885*               3) initialisation des variables temporelles (common  *
886*                    /temps/)                                        *
887*               4) definition des grilles en rayon et verticale      *
888*               5)  initialisation de c(z,r,t) avec les donnees du   *
889*                     fichier unit=1                                 *
890*                                                                    *
891*  les donnees sont des valeurs caracterisques de l'atmosphere de    *
892*    TITAN  ( voir Lelouch and co )                                  *
893*--------------------------------------------------------------------*
894
895* declaration des blocs communs
896*------------------------------
897#include "dimensions.h"
898#include "microtab.h"
899
900        common/donnees/p,t,rho,ach4,aar,an2,pb,tb,rhob
901        common/ini/z1,zb1,c0 
902        common/phys/pi,nav,rgp,kbz,rtit,g0,mch4,mar,mn2,rhol
903        common/grille/z,zb,dz,dzb
904        common/ctps/li,lf,tt,dt
905        common/con/c
906        common/part/v,rayon,vrat,dr,dv
907
908* declaration des variables communes
909* ----------------------------------
910
911cparameter(nz=200,nrad=nqtot)
912        integer li,lf
913        real dt,tt
914        real p(nz),t(nz),rho(nz),ach4(nz),aar(nz),an2(nz),pb(nz),tb(nz),
915     s   rhob(nz)
916        real pi,nav,rgp,kbz,rtit,g0,mch4,mar,mn2,rhol
917        real zb(nz),z(nz),dz(nz),dzb(nz) 
918        real c(nz,nrad,2),c0(nz,nrad)
919        real v(nrad),rayon(nrad),vrat,dr(nrad),dv(nrad)
920
921* declaration des variables internes
922* ----------------------------------
923       
924        integer nzd
925        parameter (nzd=254)
926        integer limsup,liminf,j1,j2
927        real zd(nzd),ach4d(nzd),rap
928        real m 
929
930
931* initialisation des constantes physiques
932* ---------------------------------------
933
934        pi=4.*atan(1.)
935        nav=6.022e+23
936        rgp=8.3143
937        kbz=rgp/nav
938        rtit=2.8e+6
939        g0=1.35
940        mch4=16.043e-3
941        mar=36.4e-3
942        mn2=28.016e-3
943        rhol=1e+3
944
945
946* initialisation des variables temporelles
947* ----------------------------------------
948
949        li=1
950        lf=2
951
952 
953
954
955
956* interpolation de xch4,xar et xn2 sur la grille
957* ----------------------------------------------
958
959* donnees initiales (Lellouch et al,87)
960* -------------------------------------
961
962c       print*,'****** init'
963        do 1 i=1,168
964          zd(i)=(1000.-5*(i-1))*1000.
9651       continue
966        do 2 i=1,78
967          zd(168+i)=(160.-2*(i-1))*1000.
9682       continue
969        do 3 i=1,4
970          zd(246+i)=(5.-(i-1))*1000.
9713       continue
972        do 4 i=1,4
973          zd(250+i)=(1.5-(i-1)*0.5)*1000.
9744       continue
975
976        data (ach4d(i),i=1,168)/168*1.5e-2/
977        data (ach4d(i),i=169,254)/63*1.5e-2,1.6e-2,1.8e-2,1.8e-2,
978     1  1.9e-2,2.e-2,2.1e-2,2.3e-2,2.5e-2,2.8e-2,3.1e-2,3.6e-2,
979     2  4.1e-2,4.7e-2,5.7e-2,6.7e-2,7.5e-2,7*8.e-2/
980
981        liminf=0
982        limsup=0
983
984* interpolation des taux de melange de ch4,ar,n2 
985*----------------------------------------------- 
986
987        do 20 j1=1,nz
988           do 21 j2=1,nzd
989              if( zd(j2).le.z(j1)) goto 22
99021         continue
99122            liminf=j2
992          if (zd(liminf).eq.z(j1) )then
993            ach4(j1)=ach4d(liminf)
994            goto20
995          endif
996              if (j2.ne.1) then
997                 limsup=j2-1
998              else
999                 limsup=j2
1000              endif
1001
1002          if (limsup.eq.liminf) then
1003            ach4(j1)=ach4(limsup)
1004          else
1005            ach4(j1)=ach4d(liminf)-(ach4d(limsup)-ach4d(liminf))/
1006     s       (zd(limsup)-zd(liminf))*(zd(liminf)-z(j1))
1007          endif
100820      continue
1009
1010*  rap= aar/an2  cst sur l'altitude
1011
1012        rap=0.191
1013        do 23 i=1,nz
1014          an2(i)=(1.-ach4(i))/(1.+rap)
1015          aar(i)=rap*an2(i)
101623      continue
1017
1018        do 24 i=1,nz
1019          m=ach4(i)*mch4+an2(i)*mn2+aar(i)*mar
1020          rho(i)=p(i)*m/(rgp*t(i))
102124      continue
1022
1023        do 34 i=1,nz
1024          m=ach4(i)*mch4+an2(i)*mn2+aar(i)*mar
1025          rhob(i)=pb(i)*m/(rgp*tb(i))
1026c         print*,pb(i),m,rgp,tb(i),rhob(i),rho(i)
102734      continue
1028
1029* fin d'interpolation des taux de melange
1030*----------------------------------------
1031
1032c       print*,'**** fin init'
1033540     continue
1034        return
1035
1036500      print*,'erreur lecture initialisation de c...erreur=',ii
1037         stop
1038
1039        end
1040
1041*____________________________________________________________________________
1042
1043         subroutine pertpro(h,a,l_,pr_)
1044
1045*****************************************************************************
1046*                                                                          *
1047* ce programme permet le calcul du terme de production (pr) et de perte (l)*
1048* pour le phenomene de coagulation                                         *
1049* dans le a ieme intervalle de rayon a une altitude h                      *
1050****************************************************************************
1051
1052
1053
1054* declaration des blocs communs
1055*------------------------------
1056#include "dimensions.h"
1057#include "microtab.h"
1058
1059        common/donnees/p,t,rho,ach4,aar,an2,pb,tb,rhob
1060        common/phys/pi,nav,rgp,kbz,rtit,g0,mch4,mar,mn2,rhol
1061        common/grille/z,zb,dz,dzb
1062        common/ctps/li,lf,tt,dt
1063        common/con/c
1064        common/part/v,rayon,vrat,dr,dv
1065        common/coag/k
1066
1067* declaration des variables
1068* --------------------------
1069
1070        integer li,lf
1071        real tt,dt
1072cparameter(nz=200,nrad=nqtot)
1073        real p(nz),t(nz),rho(nz),ach4(nz),aar(nz),an2(nz),pi,nav
1074        real pb(nz),tb(nz),rhob(nz)
1075        real rgp,kbz,rtit,g0,mch4,mar,mn2,rhol,dz(nz)
1076        real vrat,dr(nrad),dv(nrad)
1077        real c(nz,nrad,2),v(nrad),rayon(nrad),z(nz),k(nz,nrad,nrad)
1078        real dzb(nz),zb(nz)
1079
1080* declaration des variables propres au ss-programme
1081* -------------------------------------------------
1082
1083        integer h,b,a,x
1084        real*8 pr,ss,s,l
1085        real pr_,l_,vol,del
1086
1087* traitement
1088* -----------
1089
1090*  production
1091*+++++++++++++
1092        s=0.d0
1093        ss=0.d0
1094        pr=0.
1095
1096        if (a .eq. 1) goto 2
1097         
1098          b=a-1
1099
1100        if (c(h,b,lf) .eq. 0 .and. c(h,b,li) .eq. 0) goto 2
1101 
1102        do 1 i=1,b
1103
1104         if(c(h,i,li) .eq. 0 .and. c(h,i,lf) .eq. 0) goto 1
1105         
1106            if (i .ne. b)del=1.
1107            if (i .eq. b) del=.5
1108
1109           s=(v(i)*1.d0)*del*(k(h,b,i)*1.d0)*(c(h,i,li)*1.d0)+s
1110           ss=(v(i)*1.d0)*del*(k(h,b,i)*1.d0)*(c(h,i,lf)*1.d0)+ss
1111c       if (a.eq.2) print*,'SS>',v(i),k(h,b,i),c(h,b,lf)
1112c       if (a.eq.2) print*,'SS>',del*v(i)*k(h,b,i)*c(h,b,lf)
1113
1114
11151        continue
1116
1117*  calcul du terme de production
1118
1119          pr=(c(h,b,lf)*s/(vrat-1.)+c(h,b,li)*ss)/v(a)
1120c        if (a.eq.2) print*,'PR>',s,ss,c(h,b,lf),v(a)
1121
11222        continue
1123
1124
1125*  perte
1126*- - - - -
1127
1128        l=0
1129
1130
1131*    condition limite : pas de perte dans le dernier intervalle
1132
1133        if (a .eq. nrad) goto 9
1134
1135        do 10 x=1,nrad
1136
1137          if (c(h,x,li) .eq. 0) goto 10
1138
1139          if (a .lt. x) vol=1.
1140          if (a .eq. x) vol=.5*vrat/(vrat-1)
1141          if (a .gt. x) vol=v(x)/(v(a)*(vrat-1))
1142
1143          l=l+k(h,a,x)*c(h,x,li)*vol*1.d0
1144
1145           
114610      continue
11479       continue
1148
1149#ifdef CRAY
1150        l_=l
1151        pr_=pr
1152#else
1153        l_=sngl(l)
1154        pr_=sngl(pr)
1155#endif
1156c       l_=sngl(l)
1157c       pr_=sngl(pr)
1158c         if (a.eq.2) print*,'pr_,l_',h,a,pr_,l_
1159c         if (a.eq.2) print*,'-----------------------'
1160
1161
1162
1163        return
1164
1165        end
1166
1167*_____________________________________________________________________________
1168
1169           subroutine production(ihor)
1170*
1171*--------------------------------------------------------------------*
1172*  routine calculant le terme de production des molecules organiques *
1173*  composant les aerosols . rini= rayon des aerosols initiaux        *
1174*--------------------------------------------------------------------*
1175*
1176#include "dimensions.h"
1177#include "microtab.h"
1178#include "clesphys.h"
1179
1180
1181        integer ndz
1182cparameter (nrad=nqtot,nz=200,nztop=135)
1183        real zb(nz),z(nz),dz(nz),dzb(nz)
1184        real c(nz,nrad,2)
1185        real v(nrad),rayon(nrad),vrat,dr(nrad),dv(nrad)
1186        integer li,lf
1187        real tt,dt
1188        real fonction,fonction1,fonction2,fonction3,fonction4
1189        real xlargeur1,xlargeur2,xlargeur3,xlargeur4,xlargeur5
1190        real pi,nav,rgp,kbz,rtit,g0,mch4,mar,mn2,rhol
1191        real zalt0,zy,c0,ctot,prod,rini,rfron
1192        real p(nz),t(nz),rho(nz),ach4(nz),aar(nz),an2(nz)
1193     &  ,pb(nz),tb(nz),rhob(nz)
1194        common/phys/pi,nav,rgp,kbz,rtit,g0,mch4,mar,mn2,rhol
1195        common /grille/ z,zb,dz,dzb
1196        common/ctps/li,lf,tt,dt
1197        common /con/c
1198        common/part/v,rayon,vrat,dr,dv
1199        common/donnees/p,t,rho,ach4,aar,an2,pb,tb,rhob
1200
1201        common/effets/ xsaison
1202
1203         
1204         
1205
1206c        p0=0.3
1207         p0=1.
1208         do i=1,nz-1
1209          if (pb(i).lt.p0.and.pb(i+1).gt.p0) zalt0=(z(i)+z(i+1))/2.
1210         enddo
1211       
1212        ctot=3.5e-13*tx ! ATTENTION, ??COHERENT AVEC INITPAR??
1213        ctot=ctot*xsaison  !
1214
1215c       zalt0=385.e+3
1216        zy=20.e+3
1217        rini=1.3e-9
1218        rini=rayon(1)   
1219        ndz=50
1220*
1221        do 10 i=1,nrad
1222           if(rini.lt.rayon(i)) goto 100
122310      continue
1224100     continue
1225        if (i.eq.1) then
1226          rini=rayon(1)
1227        else
1228          rfron=(rayon(i)+rayon(i-1))/2
1229          if (rini .lt.rfron) then
1230                rini=rayon(i-1)
1231               i=i-1
1232          else
1233                rini=rayon(i)
1234          endif
1235        endif
1236*
1237         c0=ctot/(sqrt(2.*pi)*zy)
1238         c0=c0*3./(4.*pi*rhol*rini**3)
1239*
1240        do 20 k=nztop,nz
1241c        zmid=(zb(k)+zb(k+1))/2.
1242         prod=0.
1243        do 201 k1=1,ndz
1244       prod=prod+c0*exp(-0.5*(((z(k)+dz(k)/2.-k1*dz(k)/(2.*ndz)
1245     s -zalt0)/zy)**2))*dt/ndz
1246201     continue
1247
1248            if (prod .le. 1) prod=0.
1249            c(k,i,lf)=c(k,i,lf)+prod
125020      continue
1251
1252
1253        return
1254        end
1255
1256*-------------------------------------------------------------------*
1257
1258
1259           subroutine nuages
1260*
1261*--------------------------------------------------------------------  *
1262* Cete routine transforme les aerosols fractals (i=1..9) en particules *
1263* spheriques (i=nrad) lors du passage en dessous de la pression de     *
1264* condensation (P=42 Pa) avec une constante de temps de                *
1265* de 10 jours-Titan                                                    *
1266*--------------------------------------------------------------------  *
1267*
1268#include "dimensions.h"
1269#include "microtab.h"
1270
1271
1272        integer ndz
1273cparameter (nrad=nqtot,nz=200,nztop=135)
1274        real zb(nz),z(nz),dz(nz),dzb(nz)
1275        real c(nz,nrad,2)
1276        real v(nrad),rayon(nrad),vrat,dr(nrad),dv(nrad)
1277        integer li,lf
1278        real tt,dt
1279        real pi,nav,rgp,kbz,rtit,g0,mch4,mar,mn2,rhol
1280        real zalt0,zy,c0,ctot,prod,rini,rfron
1281        real p(nz),t(nz),rho(nz),ach4(nz),aar(nz),an2(nz)
1282     &  ,pb(nz),tb(nz),rhob(nz)
1283        common/phys/pi,nav,rgp,kbz,rtit,g0,mch4,mar,mn2,rhol
1284        common /grille/ z,zb,dz,dzb
1285        common/ctps/li,lf,tt,dt
1286        common /con/c
1287        common/part/v,rayon,vrat,dr,dv
1288        common/donnees/p,t,rho,ach4,aar,an2,pb,tb,rhob
1289        common/effets/ xsaison
1290
1291          xnuage=0.01
1292
1293        P_0=900.
1294        P_0=3162.
1295
1296        do 20 k=nztop,nz
1297
1298c transfert i={1...9} vers i=10 au dessous de P_0.
1299
1300         if (p(k).gt.P_0) then
1301          do 10 i=1,nrad-1
1302            c(k,nrad,lf)=c(k,nrad,lf)+c(k,i,lf)*xnuage
1303     &               *(1.-exp(-dt/1.3824e+06/10.))
1304            c(k,i,lf)=c(k,i,lf)*exp(-dt/1.3824e+06/10.)
1305 10       continue
1306         endif
1307
1308c transfert i=10 vers i=5 au dessus de P_0 Pascals
1309
1310         if (p(k).le.P_0) then
1311            c(k,5,lf)=c(k,5,lf)+c(k,nrad,lf)
1312     &               *(1.-exp(-dt/1.3824e+06/30.))
1313         c(k,nrad,lf)=c(k,nrad,lf)*exp(-dt/1.3824e+06/30.)
1314         endif
1315
1316 20     continue
1317
1318        return
1319        end
1320
1321
1322*__________________________________________________________________________
1323
1324           subroutine sedif
1325*
1326*------------------------------------------------------------------*
1327*  cette routine calcule l'evolution de la fonction de distribution*
1328*  c(z,r,t) pour les phenomenes de sedimentation et de diffusion   *
1329*------------------------------------------------------------------*
1330*
1331*
1332* declaration des blocs communs
1333*------------------------------
1334#include "dimensions.h"
1335#include "microtab.h"
1336
1337        common/donnees/p,t,rho,ach4,aar,an2,pb,tb,rhob
1338        common/phys/pi,nav,rgp,kbz,rtit,g0,mch4,mar,mn2,rhol
1339        common/grille/z,zb,dz,dzb
1340        common/ctps/li,lf,tt,dt
1341        common/con/c
1342        common/part/v,rayon,vrat,dr,dv
1343
1344* declaration des variables communes
1345* ----------------------------------
1346
1347cparameter(nz=200,nrad=nqtot,nztop=135)
1348        integer li,lf
1349        real tt,dt
1350        real p(nz),t(nz),rho(nz),ach4(nz),aar(nz),an2(nz)
1351        real pb(nz),tb(nz),rhob(nz)
1352        real pi,nav,rgp,kbz,rtit,g0,mch4,mar,mn2,rhol
1353        real zb(nz),z(nz),dz(nz),dzb(nz)
1354        real c(nz,nrad,2)
1355        real v(nrad),rayon(nrad),vrat,dr(nrad),dv(nrad)
1356
1357* declaration des variables internes
1358* ----------------------------------
1359
1360        real w,w1,dzbX,dc
1361        double precision sigma,theta,hc,l,rap,cmp,wp
1362        double precision fs(nz+1),ft(nz+1)
1363        real as(nz),bs(nz),cs(nz),ds(nz)
1364        double precision asi(nztop:nz),bsi(nztop:nz),csi(nztop:nz)
1365        double precision dsi(nztop:nz),xsol(nztop:nz)
1366        real vitesse,kd
1367
1368        external dtridgl
1369* resolution
1370*------------
1371
1372c        print*,'ECHANTILLON.SEDIF.li'
1373c        print*,c(100,1,li),c(100,3,lf),c(100,5,lf)
1374c        print*,c(10,1,li),c(50,3,lf),c(50,5,lf)
1375c        print*,c(10,1,li),c(10,3,lf),c(10,5,lf)
1376
1377           do 10 k=1,nrad 
1378           do 20 j=nztop,nz
1379
1380            if (j.eq.1) goto 20
1381
1382* calcul de la vitesse corrigee
1383
1384             dzbX=(dz(j)+dz(j-1))/2.
1385             w=-1*vitesse(j,k,0)
1386               if (kd(j).ne.0.) then
1387                 theta=0.5*(w*dzbX/kd(j)+log(rho(j-1)/rho(j)))
1388                    if (theta.ne.0) then
1389                       sigma=1./dtanh(theta)-1./theta
1390                    else
1391                       sigma=1.
1392                    endif
1393               else
1394                 sigma=1.
1395               endif
1396               if(c(j,k,li).eq.0.) then
1397                 rap=10.
1398               else
1399                 rap=c(j-1,k,li)/c(j,k,li)
1400                  if( rap.gt.10.) rap=10.
1401                  if( rap.lt.0.1) rap=0.1
1402               endif
1403               if (rap.gt.0.9 .and. rap.lt.1.1) then
1404                  w1=w
1405               else
1406                  if(w.ne.0) then
1407                      hc=dzbX/dlog(rap)
1408                      l=dzbX/(w*dt)*(dexp(-w*dt/hc)-1.)/(1.-rap)
1409                      wp=w*1.d0
1410                      cmp=dlog(-wp)+abs(sigma)*dlog(l)
1411                      if (cmp.gt.38) then
1412                               goto 20
1413                      endif
1414                      w1=-dexp(cmp)
1415
1416                  else
1417                      w1=0.
1418                  endif
1419               endif
1420
1421*  calcul des flux aux interfaces
1422
1423
1424          if (kd(j).ne.0.) then
1425              if (theta.ne.0.) then
1426                ft(j)=(w1+log(rho(j-1)/rho(j))*kd(j)/dzbX)/(dexp(2.*
1427     s           theta)-1.)
1428                fs(j)=ft(j)*dexp(2.*theta)
1429              else
1430                ft(j)=kd(j)/dzbX
1431                fs(j)=kd(j)/dzbX
1432              endif
1433         else
1434           if (w1.lt.0.)then
1435             ft(j)=-w1
1436             fs(j)=0.
1437           else
1438             ft(j)=0.
1439             fs(j)=w1
1440           endif
1441        endif
1442
144320         continue
1444
1445* conditions aux limites pour les flux aux interfaces
1446
1447           fs(1)=0.
1448           ft(1)=0.
1449           fs(nz+1)=0.
1450           ft(nz+1)=-w1
1451
1452* calcul des coefficients de l'equation discrete
1453
1454           do 21 j=nztop,nz
1455             as(j)=-dz(j)/dt
1456             bs(j)=-ft(j)
1457             cs(j)=ft(j+1)+fs(j)-dz(j)/dt
1458             ds(j)=-fs(j+1)
1459
1460                 if ( cs(j).gt.0) goto100
146121        continue
1462
1463* cas explicite (mu=0) : calcul de la fonction c(z,r,t+1)
1464
1465          do 22 j=nztop,nz-1
1466
1467           if (j.eq.nztop) then
1468             dc=(cs(nztop)*c(nztop,k,li)+ds(nztop)
1469     &                    *c(nztop+1,k,li))/as(nztop)
1470             c(nztop,k,lf)=dc
1471
1472
1473             goto 22
1474           endif
1475
1476              dc=(bs(j)*c(j-1,k,li)+cs(j)*c(j,k,li)+ds(j)*c(j+1,k,li))
1477     s        /as(j)
1478             c(j,k,lf)=dc
1479
1480
148122        continue
1482
1483             dc=(bs(nz)*c(nz-1,k,li)+cs(nz)*c(nz,k,li))/as(nz)
1484             c(nz,k,lf)=dc
1485
1486
1487          if (nztop.ne.1) then
1488          do 32 j=1,nztop-1
1489            c(j,k,lf)=c(j,k,li)
149032        continue
1491          endif
1492
1493        goto 10
1494
1495100      continue
1496
1497* cas implicite (mu=1) : calcul de la fonction c(z,r,t+1)
1498
1499         do 101 j=nztop,nz
1500            asi(j)=ft(j)
1501            bsi(j)=-(ft(j+1)+fs(j)+dz(j)/dt)
1502            csi(j)=fs(j+1)
1503            dsi(j)=-dz(j)/dt*c(j,k,li)
1504101      continue
1505
1506* inversion de la matrice tridiagonale
1507
1508        nb=nz-nztop+1
1509
1510        call dtridgl(nb,asi,bsi,csi,dsi,xsol)
1511
1512
1513        do 102 j=nztop,nz
1514         c(j,k,lf)=xsol(j)
1515102     continue
1516
1517        if (nztop.ne.1) then
1518          do 110 j=1,nztop-1
1519           c(j,k,lf)=c(j,k,li)
1520110       continue
1521         endif
1522
1523
1524
152510      continue
1526
1527        return
1528
1529        end
1530
Note: See TracBrowser for help on using the repository browser.