source: trunk/LMDZ.GENERIC/libf/phystd/newsedim.F @ 1834

Last change on this file since 1834 was 1384, checked in by emillour, 10 years ago

Generic GCM:

  • Some code cleanup: turning comcstfi.h into module comcstfi_mod.F90

EM

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