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

Last change on this file since 1242 was 57, checked in by aslmd, 14 years ago

mineur LMD_MM_MARS: ajout du GCM ancienne physique, systeme maintenant complet sur SVN (ne manque que la base de donnees d'etats initiaux)

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