source: trunk/LMDZ.MARS/libf/phymars/newsedim.F @ 1242

Last change on this file since 1242 was 1226, checked in by aslmd, 11 years ago

LMDZ.MARS : Replaced comcstfi and planete includes by modules.

File size: 7.2 KB
Line 
1      SUBROUTINE newsedim(ngrid,nlay,naersize,nrhosize,ptimestep,
2     &  pplev,masse,epaisseur,pt,rd,rho,pqi,wq,beta)
3      USE comcstfi_h
4      IMPLICIT NONE
5
6c=======================================================================
7c
8c      Compute sedimentation of 1 tracer
9c      of radius rd (m) and density rho (kg.m-3)
10c
11c=======================================================================
12
13c-----------------------------------------------------------------------
14c   declarations:
15c   -------------
16
17!#include "dimensions.h"
18!#include "dimphys.h"
19
20c
21c   arguments:
22c   ----------
23
24      INTEGER,INTENT(IN) :: ngrid,nlay,naersize,nrhosize
25      REAL,INTENT(IN) :: ptimestep            ! pas de temps physique (s)
26      REAL,INTENT(IN) :: pplev(ngrid,nlay+1) ! pression aux inter-couches (Pa)
27      REAL,INTENT(IN) :: pt(ngrid,nlay) ! temperature au centre des couches (K)
28      real,intent(in) :: masse (ngrid,nlay) ! masse d'une couche (kg)
29      real,intent(in) :: epaisseur (ngrid,nlay)  ! epaisseur d'une couche (m)
30      real,intent(in) :: rd(naersize)             ! particle radius (m)
31      real,intent(in) :: rho(nrhosize)             ! particle density (kg.m-3)
32
33
34c    Traceurs :
35      real,intent(inout) :: pqi(ngrid,nlay)  ! traceur   (e.g. ?/kg)
36      real,intent(out) :: wq(ngrid,nlay+1)  ! flux de traceur durant timestep (?/m-2)
37      real,intent(in) :: beta ! correction for the shape of the particles
38                !   (see Murphy et al. JGR 1990 vol.95)
39                !   beta=1 for spheres
40                !   beta=0.85 for irregular particles
41                !   beta=0.5 for disk shaped particles
42     
43c   local:
44c   ------
45
46      INTEGER l,ig, k, i
47      REAL rfall,rhofall
48
49      LOGICAL,SAVE :: firstcall=.true.
50
51c    Traceurs :
52c    ~~~~~~~~
53      real traversee (ngrid,nlay)
54      real vstokes(ngrid,nlay)
55      real w(ngrid,nlay)
56      real ptop, dztop, Ep, Stra
57
58
59c    Physical constant
60c    ~~~~~~~~~~~~~~~~~
61c     Gas molecular viscosity (N.s.m-2)
62      real,parameter :: visc=1.e-5       ! CO2
63c     Effective gas molecular radius (m)
64      real,parameter :: molrad=2.2e-10   ! CO2
65
66c     local and saved variable
67      real,save :: a,b
68
69
70c    ** un petit test de coherence
71c       --------------------------
72
73      IF (firstcall) THEN
74
75         firstcall=.false.
76
77
78c       Preliminary calculations for sedimenation velocity :
79c       ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
80
81c       - Constant to compute stokes speed simple formulae
82c        (Vstokes =  b * rho* r**2   avec   b= (2/9) * rho * g / visc
83         b = 2./9. * g / visc
84      ENDIF ! of IF(firstcall)
85     
86c       - Constant  to compute gas mean free path
87c        l= (T/P)*a, avec a = (  0.707*8.31/(4*pi*molrad**2 * avogadro))
88         a = 0.707*8.31/(4*3.1416* molrad*molrad * 6.023e23)
89
90c       - Correction to account for non-spherical shape (Murphy et al.  1990)
91         a = a * beta
92
93
94
95c-----------------------------------------------------------------------
96c    1. initialisation
97c    -----------------
98
99c     Sedimentation velocity (m/s)
100c     ~~~~~~~~~~~~~~~~~~~~~~
101c     (stokes law corrected for low pressure by the Cunningham
102c     slip-flow correction  according to Rossow (Icarus 36, 1-50, 1978)
103
104        do  l=1,nlay
105          do ig=1, ngrid
106c           radius
107            if (naersize.eq.1) then
108              rfall=rd(1)
109            else
110              i=ngrid*(l-1)+ig
111              rfall=rd(i)
112            endif 
113c           density
114            if (nrhosize.eq.1) then
115              rhofall=rho(1)
116            else
117              i=ngrid*(l-1)+ig
118              rhofall=rho(i)
119            endif 
120c           vstokes
121            vstokes(ig,l) = b * rhofall * rfall*rfall *
122     &      (1 + 1.333* ( a*pt(ig,l)/pplev(ig,l) )/rfall)
123
124c           Layer crossing time (s) :
125            traversee(ig,l)= epaisseur(ig,l)/vstokes(ig,l)
126          end do
127        end do
128
129
130c     Calcul de la masse d'atmosphere correspondant a q transferee
131c     ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
132c     (e.g. on recherche le niveau  en dessous de laquelle le traceur
133c      va traverser le niveau intercouche l : "dztop" est sa hauteur
134c      au dessus de l (m), "ptop" est sa pression (Pa))
135
136      do  l=1,nlay
137        do ig=1, ngrid
138             
139             dztop = vstokes(ig,l)*  ptimestep
140             Ep=0
141             k=0
142
143            w(ig,l) = 0. !! JF+AS ajout initialisation
144c **************************************************************
145c            Simple Method
146
147cc             w(ig,l) =
148cc     &       (1.- exp(-dztop*g/(r*pt(ig,l))))*pplev(ig,l) / g
149cccc           write(*,*) 'OK simple method l,w =', l, w(ig,l)
150cccc           write(*,*) 'OK simple method dztop =', dztop
151
152             w(ig,l) = 1. - exp(-dztop*g/(r*pt(ig,l)))
153             !!! Diagnostic: JF. Fix: AS. Date: 05/11
154             !!! Probleme arrondi avec la quantite ci-dessus
155             !!! ---> vaut 0 pour -dztop*g/(r*pt(ig,l)) trop petit
156             !!! ---> dans ce cas on utilise le developpement limite !
157             !!! ---> exp(-x) = 1 - x lorsque x --> 0 avec une erreur de x^2 / 2           
158             IF ( w(ig,l) .eq. 0. ) THEN
159                w(ig,l) = ( dztop*g/(r*pt(ig,l)) ) * pplev(ig,l) / g
160             ELSE
161                w(ig,l) = w(ig,l) * pplev(ig,l) / g 
162             ENDIF
163
164
165c **************************************************************
166cccc         Complex method :
167            if (dztop.gt.epaisseur(ig,l)) then                !!!if on traverse plus d'une couche
168cccc            Cas ou on "epuise" la couche l : On calcule le flux
169cccc            Venant de dessus en tenant compte de la variation de Vstokes
170c **************************************************************
171               Ep= epaisseur(ig,l)
172               Stra= traversee(ig,l)
173               do while(dztop.gt.Ep.and.l+k+1.le.nlay)
174                 k=k+1
175                 dztop= Ep + vstokes(ig,l+k)*(ptimestep -Stra)
176                 Ep = Ep + epaisseur(ig,l+k)
177                 Stra = Stra + traversee(ig,l+k)
178               enddo
179               Ep = Ep - epaisseur(ig,l+k)
180             !ptop=pplev(ig,l+k)*exp(-(dztop-Ep)*g/(r*pt(ig,l+k)))
181
182             !!! JF+AS 05/11 Probleme arrondi potentiel, meme solution que ci-dessus
183             ptop=exp(-(dztop-Ep)*g/(r*pt(ig,l+k)))
184             IF ( ptop .eq. 1. ) THEN
185                !PRINT*, 'newsedim: exposant trop petit ', ig, l
186                ptop=pplev(ig,l+k) * ( 1. - (dztop-Ep)*g/(r*pt(ig,l+k)))
187             ELSE
188                ptop=pplev(ig,l+k) * ptop
189             ENDIF
190             w(ig,l) = (pplev(ig,l) - Ptop)/g
191
192            endif                !!!!!if complex method
193
194
195cc           write(*,*) 'OK new    method l,w =', l, w(ig,l)
196cc           write(*,*) 'OK new    method dztop =', dztop
197cc       if(l.eq.7)write(*,*)'l=7,k,pplev,Ptop',pplev(ig,l),Ptop
198cc       if(l.eq.7)write(*,*)'l=7,dztop,Ep',dztop,Ep
199cc            if(l.eq.6)write(*,*)'l=6,k, w',k, w(1,l)
200cc            if(l.eq.7)write(*,*)'l=7,k, w',k, w(1,l)
201cc            if(l.eq.8)write(*,*)'l=8,k, w',k, w(1,l)
202c **************************************************************
203
204
205        end do
206      end do
207
208      call vlz_fi(ngrid,nlay,pqi,2.,masse,w,wq)
209c         write(*,*) ' newsed: wq(6), wq(7), q(6)',
210c    &                wq(1,6),wq(1,7),pqi(1,6)
211
212
213      RETURN
214      END
215
Note: See TracBrowser for help on using the repository browser.