source: trunk/LMDZ.MARS/libf/phymars/surflayer_interpol.F @ 267

Last change on this file since 267 was 267, checked in by acolaitis, 14 years ago

--- AC 03/08/2011 ---
M 265 libf/phymars/physiq.F
<> Added a PBL section for outputs, with a call to SL outputs via surflayer_interpol and thermals outputs

A 0 libf/phymars/surflayer_interpol.F
<> New subroutine to interpolate horizontal velocity norm and potential temperature in the surface layer.

THIS ROUTINE IS NOT VALIDATED YET. IT IS TURNED OFF BY DEFAULT AND IS HERE FOR DEVELOPMENT PURPOSES ONLY FOR NOW.

M 265 libf/phymars/vdif_cd.F
<> Important modification to the Reynolds formula : due to a confusion of symbols used in the litterature, a wrong simplification of

numerical values had been implicitely done... It is now corrected and yields better results for the mixed layer temperature.

M 265 libf/phymars/vdifc.F
<> Cosmetic modif (added comment for more clarity)


File size: 9.2 KB
Line 
1      SUBROUTINE surflayer_interpol(ngrid,nlay,pz0,
2     & pg,pz,pu,pv,wmax,pts,ph,z_out,Teta_out,u_out,ustar,tstar)
3      IMPLICIT NONE
4!=======================================================================
5!
6!   Subject: interpolation of temperature and velocity norm in the surface layer
7!   by recomputation of surface layer quantities (Richardson, Prandtl, u*, teta*)
8!   ------- 
9!
10!   Author: Arnaud Colaitis 05/08/11
11!   -------
12!
13!   Arguments:
14!   ----------
15!
16!   inputs:
17!   ------
18!     ngrid            size of the horizontal grid
19!     pg               gravity (m s -2)
20!     pz(ngrid,nlay)   height of layers
21!     pu(ngrid,nlay)   u component of the wind
22!     pv(ngrid,nlay)   v component of the wind
23!     pts(ngrid)       surface temperature
24!     ph(ngrid)        potential temperature T*(p/ps)^kappa
25!
26!
27!=======================================================================
28!
29!-----------------------------------------------------------------------
30!   Declarations:
31!   -------------
32
33#include "comcstfi.h"
34
35!   Arguments:
36!   ----------
37
38      INTEGER, INTENT(IN) :: ngrid,nlay
39      REAL, INTENT(IN) :: pz0(ngrid)
40      REAL, INTENT(IN) :: pg,pz(ngrid,nlay)
41      REAL, INTENT(IN) :: pu(ngrid,nlay),pv(ngrid,nlay)
42      REAL, INTENT(IN) :: wmax(ngrid)
43      REAL, INTENT(IN) :: pts(ngrid),ph(ngrid,nlay)
44      REAL, INTENT(INOUT) :: z_out                      ! output height (in m above surface)
45      REAL, INTENT(OUT) :: Teta_out(ngrid),u_out(ngrid) ! interpolated fields at z_out : potential temperature and norm(uv)
46      REAL, INTENT(OUT) :: ustar(ngrid), tstar(ngrid) ! u* and teta*
47
48!   Local:
49!   ------
50
51      INTEGER ig
52
53      REAL karman,nu
54      DATA karman,nu/.41,0.001/
55      SAVE karman,nu
56
57!    Local(2):
58!    ---------
59
60      REAL rib(ngrid)  ! Bulk Richardson number
61      REAL fm(ngrid) ! stability function for momentum
62      REAL fh(ngrid) ! stability function for heat
63      REAL z1z0,z1z0t ! ratios z1/z0 and z1/z0T
64
65! phim = 1+betam*zeta   or   (1-bm*zeta)**am
66! phih = alphah + betah*zeta    or   alphah(1.-bh*zeta)**ah
67      REAL betam, betah, alphah, bm, bh, lambda
68! ah and am are assumed to be -0.25 and -0.5 respectively
69
70      REAL cdn(ngrid),chn(ngrid)  ! neutral momentum and heat drag coefficient
71      REAL pz0t        ! initial thermal roughness length. (local)
72      REAL ric         ! critical richardson number
73      REAL reynolds(ngrid)    ! reynolds number for UBL
74      REAL prandtl(ngrid)     ! prandtl number for UBL
75      REAL pz0tcomp(ngrid)     ! computed z0t
76      REAL ite
77      REAL residual
78      REAL pcdv(ngrid),pcdh(ngrid)
79! For output :
80
81      REAL zu2                 ! Large-scale wind at first layer
82      REAL L_mo(ngrid)                ! Monin-Obukhov length
83!-----------------------------------------------------------------------
84!   couche de surface:
85!   ------------------
86     
87      tstar(:)=0.
88      ustar(:)=0.
89      reynolds(:)=0.
90
91! Original formulation :
92
93!      DO ig=1,ngrid
94!         z1=1.E+0 + pz(ig,1)/pz0(ig)
95!         zcd0=karman/log(z1)
96!         zcd0=zcd0*zcd0
97!         pcdv(ig)=zcd0
98!         pcdh(ig)=zcd0
99!      ENDDO
100
101!      print*,'old : cd,ch; ',pcdv,pcdh
102
103! New formulation (AC) :
104
105! phim = 1+betam*zeta   or   (1-bm*zeta)**am
106! phih = alphah + betah*zeta    or   alphah(1.-bh*zeta)**ah
107! am=-0.25, ah=-0.5
108
109      pz0t = 0.     ! for the sake of simplicity
110      pz0tcomp(:) = 0.1*pz0(:)
111      rib(:)=0.
112      pcdv(:)=0.
113      pcdh(:)=0.
114
115! this formulation assumes alphah=1., implying betah=betam
116! We use Dyer et al. parameters, as they cover a broad range of Richardson numbers :
117      bm=16.            !UBL
118      bh=16.            !UBL
119      alphah=1.
120      betam=5.         !SBL
121      betah=5.         !SBL
122      lambda=(sqrt(bh/bm))/alphah
123      ric=betah/(betam**2)
124
125      DO ig=1,ngrid
126
127         ite=0.
128         residual=abs(pz0tcomp(ig)-pz0t)
129
130         do while((residual .gt. 0.01*pz0(ig)) .and.  (ite .lt. 10.))
131
132         pz0t=pz0tcomp(ig)
133
134         if ((pu(ig,1) .ne. 0.) .or. (pv(ig,1) .ne. 0.)) then
135
136! Classical Richardson number formulation
137
138!         rib(ig) = (pg/ph(ig,1))*pz(ig,1)*(ph(ig,1)-pts(ig))
139!     &           /(pu(ig,1)*pu(ig,1) + pv(ig,1)*pv(ig,1))
140
141! Richardson number formulation proposed by D.E. England et al. (1995)
142
143          rib(ig) = (pg/ph(ig,1))
144     &      *pz(ig,1)*pz0(ig)/sqrt(pz(ig,1)*pz0t)
145!     &      *sqrt(pz(ig,1)*pz0(ig))
146     &      *(((log(pz(ig,1)/pz0(ig)))**2)/(log(pz(ig,1)/pz0t)))
147     &      *(ph(ig,1)-pts(ig))
148     &  /(pu(ig,1)*pu(ig,1) + pv(ig,1)*pv(ig,1))
149
150         else
151         print*,'warning, infinite Richardson at surface'
152         print*,pu(ig,1),pv(ig,1)
153         rib(ig) = ric          ! traiter ce cas !
154         endif
155
156         z1z0=pz(ig,1)/pz0(ig)
157         z1z0t=pz(ig,1)/pz0t
158
159         cdn(ig)=karman/log(z1z0)
160         cdn(ig)=cdn(ig)*cdn(ig)
161         chn(ig)=cdn(ig)*log(z1z0)/log(z1z0t)
162
163! Stable case :
164      if (rib(ig) .gt. 0.) then
165! From D.E. England et al. (95)
166      prandtl(ig)=1.
167         if(rib(ig) .lt. ric) then
168! Assuming alphah=1. and bh=bm for stable conditions :
169            fm(ig)=((ric-rib(ig))/ric)**2
170            fh(ig)=((ric-rib(ig))/ric)**2
171         else
172! For Ri>Ric, we consider Ri->Infinity => no turbulent mixing at surface
173            fm(ig)=0.
174            fh(ig)=0.
175         endif
176! Unstable case :
177      else
178! From D.E. England et al. (95)
179         fm(ig)=sqrt(1.-lambda*bm*rib(ig))
180         fh(ig)=(1./alphah)*((1.-lambda*bh*rib(ig))**0.5)*
181     &                     (1.-lambda*bm*rib(ig))**0.25
182         prandtl(ig)=alphah*((1.-lambda*bm*rib(ig))**0.25)/
183     &             ((1.-lambda*bh*rib(ig))**0.5)
184      endif
185
186       reynolds(ig)=karman*sqrt(fm(ig))*sqrt(pu(ig,1)**2 + pv(ig,1)**2)
187     &              *pz0(ig)/(log(z1z0)*nu)
188       pz0tcomp(ig)=pz0(ig)*exp(-karman*7.3*
189     &              (reynolds(ig)**0.25)*(prandtl(ig)**0.5))
190
191         
192      residual = abs(pz0t-pz0tcomp(ig))
193      ite = ite+1
194!      if(ite .eq. 10) then
195!        print*, 'iteration max reached'
196!      endif
197!      print*, "iteration nnumber, residual",ite,residual
198
199      enddo  ! of while
200
201          pz0t=0.
202
203! Drag computation :
204
205         pcdv(ig)=cdn(ig)*fm(ig)
206         pcdh(ig)=chn(ig)*fh(ig)
207       
208      ENDDO
209
210! Large-scale wind at first layer (with gustiness) and
211! u* theta* computation
212      DO ig=1,ngrid
213
214         if (rib(ig) .gt. ric) then
215           ustar(ig)=0.
216           tstar(ig)=0.
217         else
218           zu2=pu(ig,1)*pu(ig,1)+pv(ig,1)*pv(ig,1)+(0.*wmax(ig))**2
219           ustar(ig)=karman*sqrt(fm(ig)*zu2)/(log(pz(ig,1)/pz0(ig)))
220           tstar(ig)=karman*fh(ig)*(ph(ig,1)-pts(ig))
221     &                   /(log(pz(ig,1)/pz0tcomp(ig))*sqrt(fm(ig)))
222         endif
223      ENDDO
224
225! Monin Obukhov length :
226
227      DO ig=1,ngrid
228         if (rib(ig) .gt. ric) then
229            L_mo(ig)=0.
230         else
231            L_mo(ig)=pts(ig)*(ustar(ig)**2)/(pg*karman*tstar(ig))  !as defined here, L is positive for SBL, negative for UBL
232         endif
233      ENDDO
234
235      IF(z_out .ge. pz(ig,1)) THEN
236           z_out=1.
237           print*, 'Warning, z_out should be less than the first
238     &          vertical grid-point'
239           print*, 'z1 =',pz(ig,1)
240           print*, 'z_out=',z_out
241           print*, 'z_out has been changed to 1m
242     &                  and computation is resumed'
243      ENDIF
244
245      IF(z_out .lt. pz0(ig)) THEN
246           z_out=1.
247           print*, 'Warning, z_out should be more than the roughness
248     &          length'
249           print*, 'z0 =',pz0(ig)
250           print*, 'z_out=',z_out
251           print*, 'z_out has been changed to z0
252     &                  and computation is resumed'
253      ENDIF
254
255
256      print*, 'interpolation of u and teta at z_out=',z_out
257
258      DO ig=1,ngrid
259        IF (L_mo(ig) .gt. 0.) THEN
260           u_out(ig)=(ustar(ig)/karman)*log(z_out/pz0(ig)) +
261     &            5.*(ustar(ig)/(karman*L_mo(ig)))*(z_out-pz0(ig))
262           Teta_out(ig)=pts(ig)+(tstar(ig)/(prandtl(ig)*karman))
263     &                            *log(z_out/pz0tcomp(ig)) +
264     &            5.*(tstar(ig)/(prandtl(ig)*karman*L_mo(ig)))
265     &                            *(z_out-pz0tcomp(ig))
266        ELSEIF (L_mo(ig) .lt. 0.) THEN
267           u_out(ig)=(ustar(ig)/karman)*((
268     &  2.*atan((1.-16.*z_out/L_mo(ig))**0.25)
269     &  +log((-1.+(1.-16.*z_out/L_mo(ig))**0.25)
270     &  /(-1.+(1.-16.*z_out/L_mo(ig))**0.25)))-(
271     &  2.*atan((1.-16.*pz0(ig)/L_mo(ig))**0.25)
272     &  +log((-1.+(1.-16.*pz0(ig)/L_mo(ig))**0.25)
273     &  /(-1.+(1.-16.*pz0(ig)/L_mo(ig))**0.25)))
274     &                                  )
275           Teta_out(ig)=pts(ig)+(tstar(ig)/(prandtl(ig)*karman))*((
276     &  log((-1.+sqrt(1.-16.*z_out/L_mo(ig)))
277     &  /(1.+sqrt(1.-16.*z_out/L_mo(ig)))))-(
278     &  log((-1.+sqrt(1.-16.*pz0tcomp(ig)/L_mo(ig)))
279     &  /(1.+sqrt(1.-16.*pz0tcomp(ig)/L_mo(ig)))))
280     &                                                        )
281        ELSE
282           u_out(ig)=0.
283           Teta_out(ig)=0.
284        ENDIF
285      ENDDO
286
287         call WRITEDIAGFI(ngrid,'L',
288     &              'Monin Obukhov length','m',
289     &                         2,L_mo)
290         call WRITEDIAGFI(ngrid,'z0T',
291     &              'thermal roughness length','m',
292     &                         2,pz0tcomp)
293         call WRITEDIAGFI(ngrid,'z0',
294     &              'roughness length','m',
295     &                         2,pz0)
296
297
298      RETURN
299      END
Note: See TracBrowser for help on using the repository browser.