source: trunk/LMDZ.MARS/libf/phymars/dustdevil.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: 6.8 KB
Line 
1      SUBROUTINE dustdevil(ngrid,nlay,nq, pplev,pu,pv,pt, ptsurf,pq2,
2     &                pdqdev,pdqs_dev)
3
4      use tracer_mod, only: alpha_devil
5      use surfdat_h, only: z0_default
6      IMPLICIT NONE
7
8c=======================================================================
9c
10c
11c  VERSION SPECIAL TRACEURS :
12c  Parameterization of dust devil activities
13c  to estimate dust lifting
14c  The dust devil activity is estimated based on
15c  Renno et al. 1998 (JAS 55, 3244-3252) 
16c
17c  It is proportional to (1-b)*Fs
18c
19c  With b= [ps**(rcp+1) - ptop**(rcp+1)] / [(ps-ptop)*(rcp+1)* ps**rcp]
20c  with ptop pressure of the top of the boundary layer
21c       rcp = R/cp
22c
23c  and Fs the surface sensible heat flux = Cd*|U|*(T(1) -Tsurf)
24c       
25c=======================================================================
26
27c-----------------------------------------------------------------------
28c   declarations:
29c   -------------
30
31!#include "dimensions.h"
32!#include "dimphys.h"
33#include "comcstfi.h"     
34c#include "comconst.h"        ! TEMPORAIRE AVEC ANLDEVIL !!!!
35!#include "surfdat.h"
36!#include "comgeomfi.h"
37!#include "tracer.h"
38c   arguments:
39c   ----------
40
41      INTEGER ngrid,nlay
42      REAL pplev(ngrid,nlay+1)
43      REAL pt(ngrid,nlay)
44      REAL pu(ngrid,nlay)
45      REAL pv(ngrid,nlay)
46      REAL pq2(ngrid,nlay+1)
47      REAL ptsurf(ngrid)
48
49c    Traceurs :
50      integer nq
51      real pdqdev(ngrid,nlay,nq)
52      real pdqs_dev(ngrid,nq)
53     
54c   local:
55c   ------
56
57      INTEGER ig,l,iq
58      real Cd, z1
59      save Cd
60
61      LOGICAL firstcall
62      SAVE firstcall
63
64
65      REAL devila(ngrid)
66      integer ltop(ngrid)
67      real b,rho,Fs,wind
68
69
70
71      REAL  q2top , seuil
72      SAVE  q2top , seuil
73      DATA q2top/.5/ ! value of q2 at the top of PBL
74      DATA seuil/.3/ ! value of minimum dust devil activity for dust lifting
75
76
77      DATA firstcall/.true./
78
79c   TEMPORAIRE AVEC ANLDEVIL : *************
80c        real b_diag(ngrid)
81c       real localtime(ngrid)
82c       common/temporaire/localtime
83c      real ztop(ngrid),magwind(ngrid),t1(ngrid)
84c      real rcp ,cpp
85c      rcp = kappa
86c      cpp = r/rcp
87c   **********************************
88       
89
90c-----------------------------------------------------------------------
91c    initialisation
92c    --------------
93
94      IF (firstcall) THEN
95
96        write(*,*) 'In dustdevil :'
97        write(*,*) '    q2top= ',q2top,'     seuil= ', seuil
98
99c A rough estimation of the horizontal drag coefficient Cd
100c (the scale heigh is taken to be 13 km since we are typically
101c dealing with daytime temperature around 250K.
102c
103         z1= -0.5*13.e3*log(pplev(1,2)/pplev(1,1))
104         Cd = (0.4/log(z1/z0_default))**2
105
106         firstcall=.false.
107
108c        Temporaire
109c        open(77,file='devil')
110     
111      ENDIF
112
113c-----------------------------------------------------------------------
114c Initialisation
115      do iq=1,nq
116       do l=1,nlay
117           do ig=1,ngrid
118             pdqdev(ig,l,iq)= 0
119           end do
120       end do
121      end do
122
123
124c-----------------------------------------------------------------------
125c      Determining the top of the boundary layer
126c      ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
127      do ig=1,ngrid
128         do  l=2,nlay-1
129            if (pq2(ig,l).lt.q2top)then
130              ltop(ig)=l
131              goto 99
132            end if
133         enddo
134 99      continue
135
136c        ***************************************
137cc        if (ptsurf(ig).gt.255)then
138c         write(*,*) 'tsurf, ztop (km): ', ig,
139c     &   ptsurf(ig), -12.*log(pplev(ig,ltop(ig))/pplev(ig,1))
140c         if ((ptsurf(ig).gt.50.).and.(
141c     &      (-12.*log(pplev(ig,ltop(ig))/pplev(ig,1))).gt.60.))then
142c            do l=1,nlay
143c             write(*,*) l,
144c     &       -12.*log(pplev(ig,l)/pplev(ig,1)),pq2(ig,l)
145c            end do
146c         end if
147cc        end if
148c        ***************************************
149     
150      enddo
151
152c        ***************************************
153c        do ig=100,148
154c           write(*,*)'time,tsurf,ztop', localtime(ig),ptsurf(ig),
155c    &      -12.*log(pplev(ig,ltop(ig))/pplev(ig,1))
156c        end do
157c        ***************************************
158
159
160c   Calculation : dust devil intensity
161c   ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
162      do ig=1,ngrid
163
164c --------------------------------------------------
165c 1) Version 1 : sensible heat flux using actual wind :
166c        Wind magnitude:
167c        wind = sqrt(pu(ig,1)**2+pv(ig,1)**2)
168c
169c --------------------------------------------------
170c 2) Version 2 : sensible heat flux using  wind = 15 m/s
171         wind = 15.
172c ----------------------------------------------------
173c        Density :
174         rho=pplev(ig,1)/(R*pt(ig,1))
175
176c        Sensible heat flux (W.m-2) (>0 if up)
177         Fs= rho*cpp*Cd * wind
178     &       * (ptsurf(ig) -pt(ig,1))
179         b= (pplev(ig,1)**(rcp+1) - pplev(ig,ltop(ig))**(rcp+1)) /
180     &    ( (pplev(ig,1)-pplev(ig,ltop(ig)))*(rcp+1)*pplev(ig,1)**rcp)
181
182c        b_diag(ig) = b     ! TEMPORAIRE (pour diagnostique)
183
184c   Energy flux available to drive dust devil (W.m-2) : (1-b)*Fs
185c   Dust devil activity :
186         devila(ig)= max( 0. , (1-b)*Fs - seuil )
187      enddo
188c   
189c     lifted dust (kg m-2 s-1)  (<0 when lifting)
190c     ~~~~~~~~~~ 
191      do iq=1,nq
192         do ig=1,ngrid
193           pdqs_dev(ig,iq)= - alpha_devil(iq) * devila(ig)
194         end do
195      end do
196
197c     Injection of dust in the atmosphere (up to the top of pbl)
198c     ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
199      do iq=1,nq
200       do ig=1,ngrid
201         if (devila(ig).ne.0.) then
202           do l=1,ltop(ig)
203             pdqdev(ig,l,iq)=-pdqs_dev(ig,iq)*g/
204     &        (pplev(ig,1)-pplev(ig,ltop(ig)))
205           end do
206         end if
207       end do
208      end do
209
210c *********************************************************     
211c     TEMPORAIRE AVEC ANLDEVIL:
212c     IF (ngrid.gt.1) THEN
213c      do ig=2,ngrid-1
214c       write(77,88) lati(ig)*180./pi,localtime(ig),
215c    &        -12.*log(pplev(ig,ltop(ig))/pplev(ig,1)),
216c    &   devil(ig),min(sqrt(pu(ig,1)**2+pv(ig,1)**2),40.),
217c    &   ptsurf(ig)-pt(ig,1),ptsurf(ig),pplev(ig,1)
218c      end do   
219c88    format (f7.3,1x,f7.3,1x,f6.3,1x,f6.4,1x,f7.4,1x,
220c    &        f7.3,1x,f7.3,1x,f9.3)
221c      do ig=1,ngrid
222c       ztop(ig) = -12.*log(pplev(ig,ltop(ig))/pplev(ig,1))
223c       magwind(ig) = sqrt(pu(ig,1)**2+pv(ig,1)**2)
224c       t1(ig) =max(ptsurf(ig)- pt(ig,1),0.)
225c      end do
226
227c       call WRITEDIAGFI(ngrid,'dqs_dev','dqs devil',
228c    &               'kg.m-2.s-1',2,pdqs_dev)
229c       call WRITEDIAGFI(ngrid,'wind','wind',
230c    &               'm.s-1',2,magwind)
231c       call WRITEDIAGFI(ngrid,'ztop','top pbl',
232c    &               'km',2,ztop)
233c       call WRITEDIAGFI(ngrid,'tsurf','tsurf',
234c    &               'K',2,ptsurf)
235c       call WRITEDIAGFI(ngrid,'T1','T(1)',
236c    &               'K',2,t1)
237c       call WRITEDIAGFI(ngrid,'b','b',
238c    &               ' ',2,b_diag)
239c     END If
240c *********************************************************     
241         
242      RETURN
243      END
244
245
Note: See TracBrowser for help on using the repository browser.