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

Last change on this file since 1112 was 1047, checked in by emillour, 11 years ago

Mars GCM:

  • IMPORTANT CHANGE: Removed all reference/use of ngridmx (dimphys.h) in routines (necessary prerequisite to using parallel dynamics); in most cases this just means adding 'ngrid' as routine argument, and making local saved variables allocatable (and allocated at first call). In the process, had to convert many *.h files to equivalent modules: yomaer.h => yomaer_h.F90 , surfdat.h => surfdat_h.F90 , comsaison.h => comsaison_h.F90 , yomlw.h => yomlw_h.F90 , comdiurn.h => comdiurn_h.F90 , dimradmars.h => dimradmars_mod.F90 , comgeomfi.h => comgeomfi_h.F90, comsoil.h => comsoil_h.F90 , slope.h => slope_mod.F90
  • Also updated EOF routines, everything is now in eofdump_mod.F90
  • Removed unused routine lectfux.F (in dyn3d)

EM

File size: 7.2 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(ngrid,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 (ngrid,nlay)
53      real vstokes(ngrid,nlay)
54      real w(ngrid,nlay)
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
74         firstcall=.false.
75
76
77c       Preliminary calculations for sedimenation velocity :
78c       ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
79
80c       - Constant to compute stokes speed simple formulae
81c        (Vstokes =  b * rho* r**2   avec   b= (2/9) * rho * g / visc
82         b = 2./9. * g / visc
83      ENDIF ! of IF(firstcall)
84     
85c       - Constant  to compute gas mean free path
86c        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*molrad * 6.023e23)
88
89c       - Correction to account for non-spherical shape (Murphy et al.  1990)
90         a = a * beta
91
92
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
105c           radius
106            if (naersize.eq.1) then
107              rfall=rd(1)
108            else
109              i=ngrid*(l-1)+ig
110              rfall=rd(i)
111            endif 
112c           density
113            if (nrhosize.eq.1) then
114              rhofall=rho(1)
115            else
116              i=ngrid*(l-1)+ig
117              rhofall=rho(i)
118            endif 
119c           vstokes
120            vstokes(ig,l) = b * rhofall * rfall*rfall *
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
142            w(ig,l) = 0. !! JF+AS ajout initialisation
143c **************************************************************
144c            Simple Method
145
146cc             w(ig,l) =
147cc     &       (1.- exp(-dztop*g/(r*pt(ig,l))))*pplev(ig,l) / g
148cccc           write(*,*) 'OK simple method l,w =', l, w(ig,l)
149cccc           write(*,*) 'OK simple method dztop =', dztop
150
151             w(ig,l) = 1. - exp(-dztop*g/(r*pt(ig,l)))
152             !!! Diagnostic: JF. Fix: AS. Date: 05/11
153             !!! Probleme arrondi avec la quantite ci-dessus
154             !!! ---> vaut 0 pour -dztop*g/(r*pt(ig,l)) trop petit
155             !!! ---> dans ce cas on utilise le developpement limite !
156             !!! ---> exp(-x) = 1 - x lorsque x --> 0 avec une erreur de x^2 / 2           
157             IF ( w(ig,l) .eq. 0. ) THEN
158                w(ig,l) = ( dztop*g/(r*pt(ig,l)) ) * pplev(ig,l) / g
159             ELSE
160                w(ig,l) = w(ig,l) * pplev(ig,l) / g 
161             ENDIF
162
163
164c **************************************************************
165cccc         Complex method :
166            if (dztop.gt.epaisseur(ig,l)) then                !!!if on traverse plus d'une couche
167cccc            Cas ou on "epuise" la couche l : On calcule le flux
168cccc            Venant de dessus en tenant compte de la variation de Vstokes
169c **************************************************************
170               Ep= epaisseur(ig,l)
171               Stra= traversee(ig,l)
172               do while(dztop.gt.Ep.and.l+k+1.le.nlay)
173                 k=k+1
174                 dztop= Ep + vstokes(ig,l+k)*(ptimestep -Stra)
175                 Ep = Ep + epaisseur(ig,l+k)
176                 Stra = Stra + traversee(ig,l+k)
177               enddo
178               Ep = Ep - epaisseur(ig,l+k)
179             !ptop=pplev(ig,l+k)*exp(-(dztop-Ep)*g/(r*pt(ig,l+k)))
180
181             !!! JF+AS 05/11 Probleme arrondi potentiel, meme solution que ci-dessus
182             ptop=exp(-(dztop-Ep)*g/(r*pt(ig,l+k)))
183             IF ( ptop .eq. 1. ) THEN
184                !PRINT*, 'newsedim: exposant trop petit ', ig, l
185                ptop=pplev(ig,l+k) * ( 1. - (dztop-Ep)*g/(r*pt(ig,l+k)))
186             ELSE
187                ptop=pplev(ig,l+k) * ptop
188             ENDIF
189             w(ig,l) = (pplev(ig,l) - Ptop)/g
190
191            endif                !!!!!if complex method
192
193
194cc           write(*,*) 'OK new    method l,w =', l, w(ig,l)
195cc           write(*,*) 'OK new    method dztop =', dztop
196cc       if(l.eq.7)write(*,*)'l=7,k,pplev,Ptop',pplev(ig,l),Ptop
197cc       if(l.eq.7)write(*,*)'l=7,dztop,Ep',dztop,Ep
198cc            if(l.eq.6)write(*,*)'l=6,k, w',k, w(1,l)
199cc            if(l.eq.7)write(*,*)'l=7,k, w',k, w(1,l)
200cc            if(l.eq.8)write(*,*)'l=8,k, w',k, w(1,l)
201c **************************************************************
202
203
204        end do
205      end do
206
207      call vlz_fi(ngrid,nlay,pqi,2.,masse,w,wq)
208c         write(*,*) ' newsed: wq(6), wq(7), q(6)',
209c    &                wq(1,6),wq(1,7),pqi(1,6)
210
211
212      RETURN
213      END
214
Note: See TracBrowser for help on using the repository browser.