source: codes/icosagcm/branches/SATURN_DYNAMICO/LMDZ.COMMON/libf/phystd/newsedim.F @ 227

Last change on this file since 227 was 227, checked in by milmd, 10 years ago

Last LMDZ version (1315) with OpenMP directives and other stuff

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