source: trunk/LMDZ.MARS/libf/phymars/vdif_cd.F @ 276

Last change on this file since 276 was 276, checked in by acolaitis, 13 years ago

Minor modification in vdif_cd.F. Important modification to thermals scheme : added specific set of parameter values for use in mesoscale model. Thermals will be usable in Mesoscale after an other verification is made about subrgrid gustiness.

File size: 7.1 KB
Line 
1      SUBROUTINE vdif_cd(ngrid,nlay,pz0,
2     &           pg,pz,pu,pv,wmax,pts,ph,pcdv,pcdh)
3      IMPLICIT NONE
4c=======================================================================
5c
6c   Subject: computation of the surface drag coefficient using the
7c   -------  approch developed by Loui for ECMWF.
8c
9c   Author: Frederic Hourdin  15 /10 /93
10c   Modified by : Arnaud Colaitis 03/08/11
11c   -------
12c
13c   Arguments:
14c   ----------
15c
16c   inputs:
17c   ------
18c     ngrid            size of the horizontal grid
19c     pg               gravity (m s -2)
20c     pz(ngrid,nlay)   height of layers
21c     pu(ngrid,nlay)   u component of the wind
22c     pv(ngrid,nlay)   v component of the wind
23c     pts(ngrid)       surface temperature
24c     ph(ngrid)        potential temperature T*(p/ps)^kappa
25c
26c   outputs:
27c   --------
28c     pcdv(ngrid)      Cd for the wind
29c     pcdh(ngrid)      Cd for potential temperature
30c
31c=======================================================================
32c
33c-----------------------------------------------------------------------
34c   Declarations:
35c   -------------
36
37#include "comcstfi.h"
38
39c   Arguments:
40c   ----------
41
42      INTEGER, INTENT(IN) :: ngrid,nlay
43      REAL, INTENT(IN) :: pz0(ngrid)
44      REAL, INTENT(IN) :: pg,pz(ngrid,nlay)
45      REAL, INTENT(IN) :: pu(ngrid,nlay),pv(ngrid,nlay)
46      REAL, INTENT(IN) :: pts(ngrid),ph(ngrid,nlay)
47      REAL, INTENT(IN) :: wmax(ngrid)
48      REAL, INTENT(OUT) :: pcdv(ngrid),pcdh(ngrid) ! momentum and heat drag coefficient
49
50c   Local:
51c   ------
52
53      INTEGER ig
54
55      REAL karman,nu    ! Von Karman constant and fluid kinematic viscosity
56      LOGICAL firstcal
57      DATA karman,nu/.41,0.001/
58      DATA firstcal/.true./
59      SAVE karman,nu
60
61c    Local(2):
62c    ---------
63      REAL z1,zcd0
64
65      REAL rib(ngrid)  ! Bulk Richardson number
66      REAL rig(ngrid)  ! Gradient Richardson number
67      REAL fm(ngrid) ! stability function for momentum
68      REAL fh(ngrid) ! stability function for heat
69      REAL z1z0,z1z0t ! ratios z1/z0 and z1/z0T
70
71c phim = 1+betam*zeta   or   (1-bm*zeta)**am
72c phih = alphah + betah*zeta    or   alphah(1.-bh*zeta)**ah
73      REAL betam, betah, alphah, bm, bh, lambda
74c ah and am are assumed to be -0.25 and -0.5 respectively
75
76      REAL cdn(ngrid),chn(ngrid)  ! neutral momentum and heat drag coefficient
77      REAL pz0t        ! initial thermal roughness length. (local)
78      REAL ric         ! critical richardson number
79      REAL reynolds(ngrid)    ! reynolds number for UBL
80      REAL prandtl(ngrid)     ! prandtl number for UBL
81      REAL pz0tcomp(ngrid)     ! computed z0t
82      REAL ite
83      REAL residual
84      REAL zu2(ngrid)
85c-----------------------------------------------------------------------
86c   couche de surface:
87c   ------------------
88
89      reynolds(:)=0.
90
91c Original formulation :
92
93c      DO ig=1,ngrid
94c         z1=1.E+0 + pz(ig,1)/pz0(ig)
95c         zcd0=karman/log(z1)
96c         zcd0=zcd0*zcd0
97c         pcdv(ig)=zcd0
98c         pcdh(ig)=zcd0
99c      ENDDO
100     
101!      print*,'old : cd,ch; ',pcdv,pcdh
102
103c New formulation (AC) :
104
105c phim = 1+betam*zeta   or   (1-bm*zeta)**am
106c phih = alphah + betah*zeta    or   alphah(1.-bh*zeta)**ah
107c am=-0.25, ah=-0.5
108
109      pz0t = 0.     ! for the sake of simplicity
110      pz0tcomp(:) = 0.1*pz0(:)
111      rib(:)=0.
112
113      pcdv(:)=0.
114      pcdh(:)=0.
115
116c this formulation assumes alphah=1., implying betah=betam
117c We use Dyer et al. parameters, as they cover a broad range of Richardson numbers :
118      bm=16.            !UBL
119      bh=16.            !UBL
120      alphah=1.
121      betam=5.         !SBL
122      betah=5.         !SBL
123      lambda=(sqrt(bh/bm))/alphah
124      ric=betah/(betam**2)
125
126      DO ig=1,ngrid
127
128         ite=0.
129         residual=abs(pz0tcomp(ig)-pz0t)
130
131         do while((residual .gt. 0.01*pz0(ig)) .and.  (ite .lt. 10.))
132
133         pz0t=pz0tcomp(ig)
134
135         if ((pu(ig,1) .ne. 0.) .or. (pv(ig,1) .ne. 0.)) then
136
137c Classical Richardson number formulation
138
139c         rib(ig) = (pg/ph(ig,1))*pz(ig,1)*(ph(ig,1)-pts(ig))
140c     &           /(pu(ig,1)*pu(ig,1) + pv(ig,1)*pv(ig,1))
141
142c Richardson number formulation proposed by D.E. England et al. (1995)
143
144!         zu2=MAX(pu(ig,1)*pu(ig,1) + pv(ig,1)*pv(ig,1),0.25*wmax(ig)**2)
145!         zu2=pu(ig,1)*pu(ig,1) + pv(ig,1)*pv(ig,1)
146!         zu2=MAX(pu(ig,1)*pu(ig,1) + pv(ig,1)*pv(ig,1),wmax(ig)**2)
147       zu2(ig)= pu(ig,1)*pu(ig,1) + pv(ig,1)*pv(ig,1) + (1.*wmax(ig))**2
148
149               ! we add the wmax to simulate
150               ! bulk Ri changes due to subgrid wind feeding the thermals
151
152!          rig(ig) = (pg/ph(ig,1))*((pz(ig,1)-pz0(ig))**2
153!     &         /(pz(ig,1)-pz0t))*(ph(ig,1)-pts(ig))
154!     &         /zu2
155
156          rib(ig) = (pg/ph(ig,1))
157!     &      *pz(ig,1)*pz0(ig)/sqrt(pz(ig,1)*pz0t)
158     &      *sqrt(pz(ig,1)*pz0(ig))
159     &      *(((log(pz(ig,1)/pz0(ig)))**2)/(log(pz(ig,1)/pz0t)))
160     &      *(ph(ig,1)-pts(ig))
161     &  /zu2(ig)
162
163         else
164         print*,'warning, infinite Richardson at surface'
165         print*,pu(ig,1),pv(ig,1)
166         rib(ig) = ric          ! traiter ce cas !
167         endif
168
169         z1z0=pz(ig,1)/pz0(ig)
170         z1z0t=pz(ig,1)/pz0t
171
172         cdn(ig)=karman/log(z1z0)
173         cdn(ig)=cdn(ig)*cdn(ig)
174         chn(ig)=cdn(ig)*log(z1z0)/log(z1z0t)
175
176c Stable case :
177      if (rib(ig) .gt. 0.) then
178c From D.E. England et al. (95)
179      prandtl(ig)=1.
180         if(rib(ig) .lt. ric) then
181c Assuming alphah=1. and bh=bm for stable conditions :
182            fm(ig)=((ric-rib(ig))/ric)**2
183            fh(ig)=((ric-rib(ig))/ric)**2
184         else
185c For Ri>Ric, we consider Ri->Infinity => no turbulent mixing at surface
186            fm(ig)=0.
187            fh(ig)=0.
188         endif
189c Unstable case :
190      else
191c From D.E. England et al. (95)
192         fm(ig)=sqrt(1.-lambda*bm*rib(ig))
193         fh(ig)=(1./alphah)*((1.-lambda*bh*rib(ig))**0.5)*
194     &                     (1.-lambda*bm*rib(ig))**0.25
195         prandtl(ig)=alphah*((1.-lambda*bm*rib(ig))**0.25)/
196     &             ((1.-lambda*bh*rib(ig))**0.5)
197      endif
198
199       reynolds(ig)=karman*sqrt(fm(ig))
200     &      *sqrt(zu2(ig))
201c     &      *sqrt(pu(ig,1)**2 + pv(ig,1)**2)
202     &       *pz0(ig)/(log(z1z0)*nu)
203       pz0tcomp(ig)=pz0(ig)*exp(-karman*7.3*
204     &              (reynolds(ig)**0.25)*(prandtl(ig)**0.5))
205
206         
207      residual = abs(pz0t-pz0tcomp(ig))
208      ite = ite+1
209!      print*, "iteration nnumber, residual",ite,residual
210
211      enddo  ! of while
212
213          pz0t=0.
214
215c Drag computation :
216
217         pcdv(ig)=cdn(ig)*fm(ig)
218         pcdh(ig)=chn(ig)*fh(ig)
219       
220      ENDDO
221!
222!      print*,'new : cd,ch; ',pcdv,pcdh
223
224! Some useful diagnostics :
225
226!        call WRITEDIAGFI(ngrid,'RiB',
227!     &              'Bulk Richardson nb','no units',
228!     &                         2,rib)
229!                call WRITEDIAGFI(ngrid,'RiG',
230!     &              'Grad Richardson nb','no units',
231!     &                         2,rig)
232!        call WRITEDIAGFI(ngrid,'Pr',
233!     &              'Prandtl nb','no units',
234!     &                         0,prandtl)
235!       call WRITEDIAGFI(ngrid,'Re',
236!     &              'Reynolds nb','no units',
237!     &                         0,reynolds)
238!        call WRITEDIAGFI(ngrid,'z0tcomp',
239!     &              'computed z0t','m',
240!     &                         2,pz0tcomp)
241
242
243      RETURN
244      END
Note: See TracBrowser for help on using the repository browser.