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

Last change on this file since 358 was 358, checked in by aslmd, 13 years ago

LMDZ.MARS:


A FIRST VERSION WITH SCAVENGING
TRANSPARENT TO CASUAL USER
FOR WATER CYCLE FOLKS, SEE BELOW


[TN and AS solved conflicts due to r330 >> r357]


07/11/11 == JBM

Changed watercloud.F to call two separate routines,

simpleclouds.F or improvedclouds.F, which are a simplified and
full microphysical scheme for cloud formation, respectively.
Removed the tag called "improved" in watercloud.F, and added
another tag called "microphys" which is defined in callphys.F
instead. Changed routines: callkeys, inifis, physiq, watercloud.

Reimplemented the use of typical profiles of dust particle sizes

and CCNs in simpleclouds.F. Corrected the previously used
analytical CCN profile. Moved ccn_factor to simpleclouds.F,
which won't be used in the new microphysical scheme. Changed
routines: aeropacity, physiq, simpleclouds, watercloud.

Computed rdust at the end of callsedim instead of updatereffrad,

except at firstcall. Renamed rfall into rsedcloud and moved it
in simpleclouds. Moved nuice_sed to initracer.F and added it to
tracer.h. Changed routines: callsedim, physiq, tracer.h,
watercloud, initracer, simpleclouds, updatereffrad.

Added two tracers for the CCNs. Added the different tests in

initracer.F to make sure that, for example, microphys is not
used without doubleq, etc. Corrected an inconsistency in
callsedim.F, and changed the way r0 is updated. Changes
routines: callsedim, inifis, initracer, physiq, testphys1d,
tracer.h.

Added the ability to have a spatially variable density in

newsedim (same method as that used for the radius of
sedimentation). Required the addition of one input to newsedim,
which is the size of the density variable "rho". Changed
routines: callsedim, newsedim.

Added an output to aeropacity called "tauscaling", which is a

factor to convert dust_mass and dust_number to true quantities,
based on tauvis. Removed ccn and qdust from aeropacity, which
are obsolete now.

Wrote improvedcloud.F which includes all the microphysical

scheme, and connected it to the sedimentation scheme. Added and
changed routines: callsedim, physiq, growthrate, nuclea,
improvedclouds, initracer, watercloud, microphys.h.

07/11/11 == TN

Added CCN & dust tracers updates in physiq.F

Corrected a bug that can give negative CCN numbers, due to the
use of single precision values (only 6 decimals) whereas up to 10E+10
CCN can be formed or disappears...

Corrected physical bug that causes h2o_vap or h2o_ice

to be negative in improvedclouds.F.

Corrected physical bug that causes CCN & dust tracers

to be negative in improvedclouds.F when all ice sublimates and
releases dust

Added parameter contact mteta in callphys.def

Default value is still 0.95, see inifis.F

Changed tendancy computation for dust_number in improvedclouds.F

that was not the right one. Indeed, the scavenged dust_number tracer
is computed from the dust_mass one, and its tendancy before scavenging
must be taken into account to compute its scavenging's tendancy.

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