source: trunk/LMDZ.MARS/libf/phymars/dustdevil.F @ 1747

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