source: trunk/LMDZ.MARS/libf/phymars/dustdevil.F90 @ 3393

Last change on this file since 3393 was 3292, checked in by emillour, 8 months ago

Mars PCM:
Code cleanup to prepare the addition of new schemes for dust lifting by
wind stress and dust devils. Renamed "dustlift" routine "dust_windstress_lift"
and made it a module; also made dustdevil a module.
EM

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