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

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

Bug correction in the Ri surface layer. This actually does not change results (or by a few tenth of a Kelvin) because of the way the parametrization depend on the Richardson number, and the range of the variation.

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