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

Last change on this file since 1236 was 1236, checked in by aslmd, 11 years ago

MESOSCALE. A necessary complement commit to r1234 where a upgraded interface making use of modules was proposed. Completed the new formulation for module_lmd_driver for newphys with improved interface with both ini/bdy conditions and physical parameterizations. Changed the Registry accordingly. Finished changes about I/O with the LMD physics (see LMDZ.MARS/README). Made all those changes compatible for old interface, and LES runs (checked with test cases), as well as old input files. Changed makemeso to account for full flexibility on changin nx ny ntracers nproc with newphys. Cleaned the now obsolete bits of code used in LMD physics shared with the GCM. ----- Everything is now ready to properly code both restart runs and nesting for mesoscale runs with new physics.

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