source: trunk/LMDZ.PLUTO/libf/phypluto/newsedim_pluto.F @ 3356

Last change on this file since 3356 was 3356, checked in by afalco, 6 months ago

Pluto PCM:
sedimentation uses pphi. More precise than generic sedimentation?
molrad and visc adapted to Pluto.
AF

File size: 5.9 KB
Line 
1      SUBROUTINE newsedim_pluto(ngrid,nlay,naersize,ptimestep,
2     &  pplev,masse,epaisseur,pt,rd,rho,pqi,wq,pphi)
3
4      use comcstfi_mod, only: r, g, rad
5      IMPLICIT NONE
6!==================================================================
7!
8!     Purpose
9!     -------
10!      Calculates sedimentation of 1 tracer
11!      of radius rd (m) and density rho (kg.m-3)
12!
13!==================================================================
14
15c-----------------------------------------------------------------------
16c   declarations:
17c   -------------
18
19c
20c   arguments:
21c   ----------
22
23      INTEGER ngrid,nlay,naersize
24      REAL ptimestep            ! pas de temps physique (s)
25      REAL pplev(ngrid,nlay+1)   ! pression aux inter-couches (Pa)
26      REAL pt(ngrid,nlay)    ! temperature au centre des couches (K)
27      real masse (ngrid,nlay) ! masse d'une couche (kg)
28      real epaisseur (ngrid,nlay)  ! epaisseur d'une couche (m)
29      real rd(naersize)             ! particle radius (m)
30      real rho             ! particle density (kg.m-3)
31      real pphi(ngrid,nlay)  ! geeopotential
32
33
34c    Traceurs :
35      real pqi(ngrid,nlay)  ! traceur   (e.g. ?/kg)
36      real wq(ngrid,nlay+1)  ! flux de traceur durant timestep (?/m-2)
37
38c   local:
39c   ------
40
41      INTEGER l,ig, k, i
42      REAL rfall
43
44      LOGICAL firstcall
45      SAVE firstcall
46
47c    Traceurs :
48c    ~~~~~~~~
49      real traversee(ngrid,nlay)
50      real vstokes(ngrid,nlay)
51      real w(ngrid,nlay)
52      real ptop, dztop, Ep, Stra
53
54      DATA firstcall/.true./
55
56c    Physical constant
57c    ~~~~~~~~~~~~~~~~~
58      REAL visc, molrad
59c     Gas molecular viscosity (N.s.m-2)
60      data visc/6.67e-6/       ! N2 TB14
61c     Effective gas molecular radius (m)
62      data molrad/1.93e-10/   ! N2 TB14
63c     local and saved variable
64      real a,b
65      save a,b
66      real b2
67
68c    ** un petit test de coherence
69c       --------------------------
70
71      IF (firstcall) THEN
72         IF(ngrid.NE.ngrid) THEN
73            PRINT*,'STOP dans newsedim'
74            PRINT*,'probleme de dimensions :'
75            PRINT*,'ngrid  =',ngrid
76            PRINT*,'ngrid  =',ngrid
77            STOP
78         ENDIF
79         firstcall=.false.
80
81
82!=======================================================================
83!     Preliminary calculations for sedimenation velocity
84
85!       - Constant to compute stokes speed simple formulae
86!        (Vstokes =  b * rho* r**2   avec   b= (2/9) * rho * g / visc
87         b = 2./9. * g / visc
88
89!       - Constant  to compute gas mean free path
90!        l= (T/P)*a, avec a = (  0.707*8.31/(4*pi*molrad**2 * avogadro))
91         a = 0.707*8.31/(4*3.1416* molrad**2  * 6.023e23)
92
93c       - Correction to account for non-spherical shape (Murphy et al.  1990)
94c   (correction = 0.85 for irregular particles, 0.5 for disk shaped particles)
95c        a = a    * 0.85
96      ENDIF
97
98c      write(*,*) 'TB16 : stokes : g,visc,b,a,molrad ',g,visc,b,a,molrad
99
100
101
102c-----------------------------------------------------------------------
103c    1. initialisation
104c    -----------------
105
106c     Sedimentation velocity (m/s)
107c     ~~~~~~~~~~~~~~~~~~~~~~
108c     (stokes law corrected for low pressure by the Cunningham
109c     slip-flow correction  according to Rossow (Icarus 36, 1-50, 1978)
110        do  l=1,nlay
111          do ig=1, ngrid
112            if (naersize.eq.1) then
113              rfall=rd(1)
114            else
115              i=ngrid*(l-1)+ig
116              rfall=rd(i)
117            endif
118            !vstokes(ig,l) = b * rho * rfall**2 *
119            b2=((g*rad-pphi(ig,l))**2/(g*(rad**2)))*2./9./visc
120            vstokes(ig,l) = b2 * rho * rfall**2 *
121     &      (1 + 1.333* ( a*pt(ig,l)/pplev(ig,l) )/rfall)
122
123c           Layer crossing time (s) :
124            traversee(ig,l)= epaisseur(ig,l)/vstokes(ig,l)
125          end do
126        end do
127
128c     Calcul de la masse d'atmosphere correspondant a q transferee
129c     ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
130c     (e.g. on recherche le niveau  en dessous de laquelle le traceur
131c      va traverser le niveau intercouche l : "dztop" est sa hauteur
132c      au dessus de l (m), "ptop" est sa pression (Pa))
133
134      do  l=1,nlay
135        do ig=1, ngrid
136
137             dztop = vstokes(ig,l)*  ptimestep
138             Ep=0
139             k=0
140
141c **************************************************************
142c            Simple Method
143             w(ig,l) =
144     &       (1- exp(-dztop*g/(r*pt(ig,l))))*pplev(ig,l) / g
145cc           write(*,*) 'OK simple method l,w =', l, w(ig,l)
146cc           write(*,*) 'OK simple method dztop =', dztop
147c **************************************************************
148cccc         Complex method :
149            if (dztop.gt.epaisseur(ig,l)) then
150cccc            Cas ou on "epuise" la couche l : On calcule le flux
151cccc            Venant de dessus en tenant compte de la variation de Vstokes
152
153               Ep= epaisseur(ig,l)
154               Stra= traversee(ig,l)
155               do while(dztop.gt.Ep.and.l+k+1.le.nlay)
156                 k=k+1
157                 dztop= Ep + vstokes(ig,l+k)*(ptimestep -Stra)
158                 Ep = Ep + epaisseur(ig,l+k)
159                 Stra = Stra + traversee(ig,l+k)
160               enddo
161               Ep = Ep - epaisseur(ig,l+k)
162             end if
163             ptop=pplev(ig,l+k)*exp(-(dztop-Ep)*g/(r*pt(ig,l+k)))
164             w(ig,l) = (pplev(ig,l) -Ptop)/g
165c
166cc           write(*,*) 'OK new    method l,w =', l, w(ig,l)
167cc           write(*,*) 'OK new    method dztop =', dztop
168cc       if(l.eq.7)write(*,*)'l=7,k,pplev,Ptop',pplev(ig,l),Ptop
169cc       if(l.eq.7)write(*,*)'l=7,dztop,Ep',dztop,Ep
170cc            if(l.eq.6)write(*,*)'l=6,k, w',k, w(1,l)
171cc            if(l.eq.7)write(*,*)'l=7,k, w',k, w(1,l)
172cc            if(l.eq.8)write(*,*)'l=8,k, w',k, w(1,l)
173c **************************************************************
174        end do
175      end do
176
177      call vlz_fi(ngrid,nlay,pqi,2.,masse,w,wq)
178c         write(*,*) ' newsed: wq(6), wq(7), q(6)',
179c    &                wq(1,6),wq(1,7),pqi(1,6)
180
181
182      RETURN
183      END
184
Note: See TracBrowser for help on using the repository browser.