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

Last change on this file since 1660 was 1266, checked in by aslmd, 11 years ago

LMDZ.MARS
IMPORTANT CHANGE

  • Remove all reference/use of nlayermx and dimphys.h
  • Made use of automatic arrays whenever arrays are needed with dimension nlayer
  • Remove lots of obsolete reference to dimensions.h
  • Converted iono.h and param_v4.h into corresponding modules

(with embedded subroutine to allocate arrays)
(no arrays allocated if thermosphere not used)

  • Deleted param.h and put contents into module param_v4_h
  • Adapted testphys1d, newstart, etc...
  • Made DATA arrays in param_read to be initialized by subroutine

fill_data_thermos in module param_v4_h

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