/[MITgcm]/MITgcm/pkg/fizhi/fizhi_gwdrag.F
ViewVC logotype

Annotation of /MITgcm/pkg/fizhi/fizhi_gwdrag.F

Parent Directory Parent Directory | Revision Log Revision Log | View Revision Graph Revision Graph


Revision 1.11 - (hide annotations) (download)
Fri Jul 1 01:12:00 2005 UTC (19 years ago) by jmc
Branch: MAIN
CVS Tags: checkpoint64y, checkpoint64x, checkpoint58l_post, checkpoint64z, checkpoint57t_post, checkpoint64q, checkpoint64p, checkpoint64s, checkpoint64r, checkpoint64u, checkpoint64t, checkpoint64w, checkpoint64v, checkpoint64i, checkpoint64h, checkpoint64k, checkpoint64j, checkpoint64m, checkpoint64l, checkpoint64o, checkpoint64n, checkpoint64a, checkpoint57o_post, checkpoint64c, checkpoint64b, checkpoint64e, checkpoint64d, checkpoint64g, checkpoint64f, checkpoint58e_post, checkpoint57v_post, checkpoint58u_post, checkpoint58w_post, checkpoint57m_post, checkpoint57s_post, checkpoint63p, checkpoint63q, checkpoint63r, checkpoint63s, checkpoint63l, checkpoint63m, checkpoint63n, checkpoint63o, checkpoint63h, checkpoint63i, checkpoint63j, checkpoint63k, checkpoint63d, checkpoint63e, checkpoint63f, checkpoint63g, checkpoint63a, checkpoint63b, checkpoint63c, checkpoint57k_post, checkpoint64, checkpoint65, checkpoint60, checkpoint61, checkpoint62, checkpoint63, checkpoint58r_post, checkpoint57y_post, checkpoint66g, checkpoint66f, checkpoint66e, checkpoint66d, checkpoint66c, checkpoint66b, checkpoint66a, checkpoint66o, checkpoint66n, checkpoint66m, checkpoint66l, checkpoint66k, checkpoint66j, checkpoint66i, checkpoint66h, checkpoint58n_post, checkpoint58x_post, checkpoint58t_post, checkpoint58h_post, checkpoint65z, checkpoint65x, checkpoint65y, checkpoint65r, checkpoint65s, checkpoint65p, checkpoint65q, checkpoint65v, checkpoint65w, checkpoint65t, checkpoint65u, checkpoint65j, checkpoint65k, checkpoint65h, checkpoint65i, checkpoint65n, checkpoint65o, checkpoint65l, checkpoint65m, checkpoint65b, checkpoint65c, checkpoint65a, checkpoint65f, checkpoint65g, checkpoint65d, checkpoint65e, checkpoint57y_pre, checkpoint58q_post, checkpoint59q, checkpoint59p, checkpoint59r, checkpoint58j_post, checkpoint59e, checkpoint59d, checkpoint59g, checkpoint59f, checkpoint59a, checkpoint59c, checkpoint59b, checkpoint59m, checkpoint59l, checkpoint59o, checkpoint59n, checkpoint59i, checkpoint59h, checkpoint59k, checkpoint59j, checkpoint57r_post, checkpoint59, checkpoint58, checkpoint58f_post, checkpoint57x_post, checkpoint57n_post, checkpoint58d_post, checkpoint58c_post, checkpoint57w_post, checkpoint57p_post, checkpint57u_post, checkpoint58a_post, checkpoint58i_post, checkpoint57q_post, checkpoint58g_post, checkpoint58o_post, checkpoint57z_post, checkpoint62c, checkpoint62b, checkpoint62a, checkpoint62g, checkpoint62f, checkpoint62e, checkpoint62d, checkpoint62k, checkpoint62j, checkpoint62i, checkpoint62h, checkpoint62o, checkpoint62n, checkpoint62m, checkpoint62l, checkpoint62s, checkpoint62r, checkpoint62q, checkpoint62p, checkpoint62w, checkpoint62v, checkpoint62u, checkpoint62t, checkpoint62z, checkpoint62y, checkpoint62x, checkpoint58y_post, checkpoint58k_post, checkpoint58v_post, checkpoint58s_post, checkpoint61f, checkpoint61g, checkpoint61d, checkpoint61e, checkpoint61b, checkpoint61c, checkpoint58p_post, checkpoint61a, checkpoint61n, checkpoint61o, checkpoint61l, checkpoint61m, checkpoint61j, checkpoint61k, checkpoint61h, checkpoint61i, checkpoint61v, checkpoint61w, checkpoint61t, checkpoint61u, checkpoint61r, checkpoint61s, checkpoint61p, checkpoint61q, checkpoint61z, checkpoint61x, checkpoint61y, checkpoint58b_post, checkpoint58m_post, checkpoint57l_post, HEAD
Changes since 1.10: +3 -3 lines
fix number of pressure interfaces (=Lm+1 instead of Lm)

1 jmc 1.11 C $Header: /u/gcmpack/MITgcm/pkg/fizhi/fizhi_gwdrag.F,v 1.10 2005/06/17 16:51:24 ce107 Exp $
2 molod 1.1 C $Name: $
3     #include "FIZHI_OPTIONS.h"
4     subroutine gwdrag (myid,pz,pl,ple,dpres,pkz,uz,vz,tz,qz,phis_var,
5 molod 1.4 . dudt,dvdt,dtdt,im,jm,Lm,bi,bj,istrip,npcs,imglobal)
6 molod 1.1 C***********************************************************************
7     C
8     C PURPOSE:
9     C ========
10     C Driver Routine for Gravity Wave Drag
11     C
12     C INPUT:
13     C ======
14     C myid ....... Process ID
15     C pz ....... Surface Pressure [im,jm]
16 molod 1.4 C pl ....... 3D pressure field [im,jm,Lm]
17     C ple ....... 3d pressure at model level edges [im,jm,Lm+1]
18     C dpres ....... pressure difference across level [im,jm,Lm]
19     C pkz ....... pressure**kappa [im,jm,Lm]
20     C uz ....... zonal velocity [im,jm,Lm]
21     C vz ....... meridional velocity [im,jm,Lm]
22     C tz ....... temperature [im,jm,Lm]
23     C qz ....... specific humidity [im,jm,Lm]
24 molod 1.1 C phis_var .... topography variance
25     C im ....... number of grid points in x direction
26     C jm ....... number of grid points in y direction
27 molod 1.4 C Lm ....... number of grid points in vertical
28 molod 1.1 C istrip ...... 'strip' length for cache size control
29     C npcs ....... number of strips
30     C imglobal .... (avg) number of longitude points around the globe
31     C
32     C INPUT/OUTPUT:
33     C ============
34     C dudt ....... Updated U-Wind Tendency including Gravity Wave Drag
35     C dvdt ....... Updated V-Wind Tendency including Gravity Wave Drag
36     C dtdt ....... Updated Pi*Theta Tendency including Gravity Wave Drag
37     C
38     C***********************************************************************
39     implicit none
40    
41     c Input Variables
42     c ---------------
43 molod 1.4 integer myid,im,jm,Lm,bi,bj,istrip,npcs,imglobal
44 molod 1.2 _RL pz(im,jm)
45 molod 1.4 _RL pl(im,jm,Lm)
46     _RL ple(im,jm,Lm+1)
47     _RL dpres(im,jm,Lm)
48     _RL pkz(im,jm,Lm)
49     _RL uz(im,jm,Lm)
50     _RL vz(im,jm,Lm)
51     _RL tz(im,jm,Lm)
52     _RL qz(im,jm,Lm)
53 molod 1.2 _RL phis_var(im,jm)
54    
55 molod 1.4 _RL dudt(im,jm,Lm)
56     _RL dvdt(im,jm,Lm)
57     _RL dtdt(im,jm,Lm)
58 molod 1.1
59     c Local Variables
60     c ---------------
61 molod 1.4 _RL tv(im,jm,Lm)
62     _RL dragu(im,jm,Lm), dragv(im,jm,Lm)
63     _RL dragt(im,jm,Lm)
64 molod 1.2 _RL dragx(im,jm), dragy(im,jm)
65     _RL sumu(im,jm)
66 molod 1.1 integer nthin(im,jm),nbase(im,jm)
67     integer nthini, nbasei
68    
69 molod 1.2 _RL phis_std(im,jm)
70 molod 1.1
71 molod 1.2 _RL std(istrip), ps(istrip)
72 molod 1.4 _RL us(istrip,Lm), vs(istrip,Lm), ts(istrip,Lm)
73     _RL dragus(istrip,Lm), dragvs(istrip,Lm)
74 molod 1.2 _RL dragxs(istrip), dragys(istrip)
75 jmc 1.11 _RL plstr(istrip,Lm),plestr(istrip,Lm+1),dpresstr(istrip,Lm)
76 molod 1.1 integer nthinstr(istrip),nbasestr(istrip)
77    
78     integer n,i,j,L
79 molod 1.2 _RL getcon, pi
80     _RL grav, rgas, cp, cpinv, lstar
81     #ifdef ALLOW_DIAGNOSTICS
82     logical diagnostics_is_on
83     external diagnostics_is_on
84     _RL tmpdiag(im,jm)
85     #endif
86 molod 1.1
87     c Initialization
88     c --------------
89     pi = 4.0*atan(1.0)
90     grav = getcon('GRAVITY')
91     rgas = getcon('RGAS')
92     cp = getcon('CP')
93     cpinv = 1.0/cp
94     lstar = 2*getcon('EARTH RADIUS')*cos(pi/3.0)/imglobal
95    
96     c Compute NTHIN and NBASE
97     c -----------------------
98     do j=1,jm
99     do i=1,im
100    
101 molod 1.4 do nthini = 1,Lm+1
102     if( pz(i,j)-ple(i,j,Lm+2-nthini).gt.25. ) then
103 molod 1.1 nthin(i,j) = nthini
104     goto 10
105     endif
106     enddo
107     10 continue
108 molod 1.4 do nbasei = 1,Lm+1
109     if( ple(i,j,Lm+2-nbasei).lt.(0.667*pz(i,j)) ) then
110 molod 1.1 nbase(i,j) = nbasei
111     goto 20
112     endif
113     enddo
114     20 continue
115 molod 1.4 if( (0.667*pz(i,j))-ple(i,j,Lm+2-nbase(i,j)) .gt.
116     . ple(i,j,Lm+3-nbase(i,j))-(0.667*pz(i,j)) ) then
117 molod 1.1 nbase(i,j) = nbase(i,j)-1
118     endif
119    
120     enddo
121     enddo
122 molod 1.4
123 molod 1.1 c Compute Topography Sub-Grid Standard Deviation
124 molod 1.4 c and constrain the Maximum Value
125 molod 1.1 c ----------------------------------------------
126     do j=1,jm
127     do i=1,im
128 ce107 1.10 phis_std(i,j) = min( 400.0 _d 0, sqrt( max(0.0 _d 0,
129     $ phis_var(i,j)) )/grav )
130 molod 1.1 enddo
131     enddo
132    
133     c Compute Virtual Temperatures
134     c ----------------------------
135 molod 1.4 do L = 1,Lm
136 molod 1.1 do j = 1,jm
137     do i = 1,im
138     tv(i,j,L) = tz(i,j,L)*pkz(i,j,L)*(1.+.609*qz(i,j,L))
139     enddo
140     enddo
141     enddo
142    
143 molod 1.4 do L = 1,Lm
144     do j = 1,jm
145     do i = 1,im
146     dragu(i,j,L) = 0.
147     dragv(i,j,L) = 0.
148     dragt(i,j,L) = 0.
149     enddo
150     enddo
151     enddo
152    
153 molod 1.1 c Call Gravity Wave Drag Paramterization on A-Grid
154     c ------------------------------------------------
155    
156     do n=1,npcs
157    
158 molod 1.7 call stripit ( phis_std,std,im*jm,im*jm,istrip,1,n )
159 molod 1.1
160 molod 1.7 call stripit ( pz,ps,im*jm,im*jm,istrip,1 ,n )
161     call stripit ( uz,us,im*jm,im*jm,istrip,Lm,n )
162     call stripit ( vz,vs,im*jm,im*jm,istrip,Lm,n )
163     call stripit ( tv,ts,im*jm,im*jm,istrip,Lm,n )
164     call stripit ( pl,plstr,im*jm,im*jm,istrip,Lm,n )
165 jmc 1.11 call stripit ( ple,plestr,im*jm,im*jm,istrip,Lm+1,n )
166 molod 1.7 call stripit ( dpres,dpresstr,im*jm,im*jm,istrip,Lm,n )
167     call stripitint ( nthin,nthinstr,im*jm,im*jm,istrip,1,n )
168     call stripitint ( nbase,nbasestr,im*jm,im*jm,istrip,1,n )
169 molod 1.1
170     call GWDD ( ps,us,vs,ts,
171     . dragus,dragvs,dragxs,dragys,std,
172     . plstr,plestr,dpresstr,grav,rgas,cp,
173 molod 1.4 . istrip,Lm,nthinstr,nbasestr,lstar )
174 molod 1.1
175 molod 1.7 call pastit( dragus,dragu,istrip,im*jm,im*jm,Lm,n )
176     call pastit( dragvs,dragv,istrip,im*jm,im*jm,Lm,n )
177     call pastit( dragxs,dragx,istrip,im*jm,im*jm,1 ,n )
178     call pastit( dragys,dragy,istrip,im*jm,im*jm,1 ,n )
179 molod 1.1
180     enddo
181    
182     c Add Gravity-Wave Drag to Wind and Theta Tendencies
183     c --------------------------------------------------
184 molod 1.4 do L = 1,Lm
185 molod 1.1 do j = 1,jm
186     do i = 1,im
187 ce107 1.10 dragu(i,j,L) = sign( min(0.006 _d 0,abs(dragu(i,j,L))), dragu(i
188     $ ,j,L) )
189     dragv(i,j,L) = sign( min(0.006 _d 0,abs(dragv(i,j,L))), dragv(i
190     $ ,j,L) )
191 molod 1.1 dragt(i,j,L) = -( uz(i,j,L)*dragu(i,j,L)+vz(i,j,L)*dragv(i,j,L) )
192     . *cpinv
193 molod 1.5 dudt(i,j,L) = dudt(i,j,L) + dragu(i,j,L)
194     dvdt(i,j,L) = dvdt(i,j,L) + dragv(i,j,L)
195     dtdt(i,j,L) = dtdt(i,j,L) + dragt(i,j,L)*pz(i,j)/pkz(i,j,L)
196 molod 1.1 enddo
197     enddo
198     enddo
199    
200     c Compute Diagnostics
201     c -------------------
202 molod 1.2 #ifdef ALLOW_DIAGNOSTICS
203 molod 1.4 do L = 1,Lm
204 molod 1.2
205     if(diagnostics_is_on('GWDU ',myid) ) then
206     do j=1,jm
207     do i=1,im
208     tmpdiag(i,j) = dragu(i,j,L)*86400
209     enddo
210     enddo
211     call diagnostics_fill(tmpdiag,'GWDU ',L,1,3,bi,bj,myid)
212     endif
213    
214     if(diagnostics_is_on('GWDV ',myid) ) then
215     do j=1,jm
216     do i=1,im
217     tmpdiag(i,j) = dragv(i,j,L)*86400
218     enddo
219     enddo
220     call diagnostics_fill(tmpdiag,'GWDV ',L,1,3,bi,bj,myid)
221     endif
222    
223     if(diagnostics_is_on('GWDT ',myid) ) then
224     do j=1,jm
225     do i=1,im
226     tmpdiag(i,j) = dragt(i,j,L)*86400
227     enddo
228     enddo
229     call diagnostics_fill(tmpdiag,'GWDT ',L,1,3,bi,bj,myid)
230     endif
231    
232 molod 1.1 enddo
233    
234     c Gravity Wave Drag at Surface (U-Wind)
235     c -------------------------------------
236 molod 1.2 if(diagnostics_is_on('GWDUS ',myid) ) then
237     call diagnostics_fill(dragx,'GWDUS ',0,1,3,bi,bj,myid)
238 molod 1.1 endif
239    
240     c Gravity Wave Drag at Surface (V-Wind)
241     c -------------------------------------
242 molod 1.2 if(diagnostics_is_on('GWDVS ',myid) ) then
243     call diagnostics_fill(dragy,'GWDVS ',0,1,3,bi,bj,myid)
244 molod 1.1 endif
245    
246     c Gravity Wave Drag at Model Top (U-Wind)
247     c ---------------------------------------
248 molod 1.2 if(diagnostics_is_on('GWDUT ',myid) ) then
249 molod 1.1 do j = 1,jm
250     do i = 1,im
251     sumu(i,j) = 0.0
252     enddo
253     enddo
254 molod 1.4 do L = 1,Lm
255 molod 1.1 do j = 1,jm
256     do i = 1,im
257     sumu(i,j) = sumu(i,j) + dragu(i,j,L)*dpres(i,j,L)/pz(i,j)
258     enddo
259     enddo
260     enddo
261 molod 1.2 do j=1,jm
262     do i=1,im
263     tmpdiag(i,j) = dragx(i,j) + sumu(i,j)*pz(i,j)/grav*100
264     enddo
265     enddo
266     call diagnostics_fill(tmpdiag,'GWDUT ',0,1,3,bi,bj,myid)
267 molod 1.1 endif
268    
269     c Gravity Wave Drag at Model Top (V-Wind)
270     c ---------------------------------------
271 molod 1.2 if(diagnostics_is_on('GWDVT ',myid) ) then
272 molod 1.1 do j = 1,jm
273     do i = 1,im
274     sumu(i,j) = 0.0
275     enddo
276     enddo
277 molod 1.4 do L = 1,Lm
278 molod 1.1 do j = 1,jm
279     do i = 1,im
280     sumu(i,j) = sumu(i,j) + dragv(i,j,L)*dpres(i,j,L)/pz(i,j)
281     enddo
282     enddo
283     enddo
284 molod 1.2 do j=1,jm
285     do i=1,im
286     tmpdiag(i,j) = dragy(i,j) + sumu(i,j)*pz(i,j)/grav*100
287     enddo
288     enddo
289     call diagnostics_fill(tmpdiag,'GWDVT ',0,1,3,bi,bj,myid)
290 molod 1.1 endif
291 molod 1.2 #endif
292 molod 1.1
293     return
294     end
295     SUBROUTINE GWDD ( ps,u,v,t,dudt,dvdt,xdrag,ydrag,
296     . std,pl,ple,dpres,
297 molod 1.4 . grav,rgas,cp,irun,Lm,nthin,nbase,lstar )
298 molod 1.1 C***********************************************************************
299     C
300     C Description:
301     C ============
302     C Parameterization to introduce a Gravity Wave Drag
303     C due to sub-grid scale orographic forcing
304     C
305     C Input:
306     C ======
307     C ps ......... Surface Pressure
308     C u .......... Zonal Wind (m/sec)
309     C v .......... Meridional Wind (m/sec)
310     C t .......... Virtual Temperature (deg K)
311     C std ........ Standard Deviation of sub-grid Orography (m)
312     C ple ....... Model pressure Edge Values
313     C pl ........ Model pressure Values
314     C dpres....... Model Delta pressure Values
315     C grav ....... Gravitational constant (m/sec**2)
316     C rgas ....... Gas constant
317     C cp ......... Specific Heat at constant pressure
318     C irun ....... Number of grid-points in horizontal dimension
319 molod 1.4 C Lm ......... Number of grid-points in vertical dimension
320 molod 1.1 C lstar ...... Monochromatic Wavelength/(2*pi)
321     C
322     C Output:
323     C =======
324     C dudt ....... Zonal Acceleration due to GW Drag (m/sec**2)
325     C dvdt ....... Meridional Acceleration due to GW Drag (m/sec**2)
326     C xdrag ...... Zonal Surface and Base Layer Stress (Pa)
327     C ydrag ...... Meridional Surface and Base Layer Stress (Pa)
328     C
329 molod 1.4 C NOTE: Quantities computed locally in GWDD use a
330     C bottom-up counting of levels
331     C The fizhi code uses a top-down so all
332     C Quantities that came in through the arg list
333     C must use reverse vertical indexing!!!
334 molod 1.1 C***********************************************************************
335    
336     implicit none
337    
338     c Input Variables
339     c ---------------
340 molod 1.4 integer irun,Lm
341 molod 1.2 _RL ps(irun)
342 molod 1.4 _RL u(irun,Lm), v(irun,Lm), t(irun,Lm)
343     _RL dudt(irun,Lm), dvdt(irun,Lm)
344 molod 1.2 _RL xdrag(irun), ydrag(irun)
345     _RL std(irun)
346 molod 1.4 _RL ple(irun,Lm+1), pl(irun,Lm), dpres(irun,Lm)
347 molod 1.2 _RL grav, rgas, cp
348 molod 1.1 integer nthin(irun),nbase(irun)
349 molod 1.2 _RL lstar
350 molod 1.1
351     c Dynamic Allocation Variables
352     c ----------------------------
353 molod 1.2 _RL ubar(irun), vbar(irun), robar(irun)
354     _RL speed(irun), ang(irun)
355 molod 1.4 _RL bv(irun,Lm)
356 molod 1.2 _RL nbar(irun)
357    
358 molod 1.4 _RL XTENS(irun,Lm+1), YTENS(irun,Lm+1)
359     _RL TENSIO(irun,Lm+1)
360 molod 1.2 _RL DRAGSF(irun)
361 molod 1.4 _RL RO(irun,Lm), DZ(irun,Lm)
362 molod 1.1
363     integer icrilv(irun)
364    
365     c Local Variables
366     c ---------------
367 molod 1.4 integer i,L
368     _RL a,g,agrav,akwnmb
369 molod 1.2 _RL gocp,roave,roiave,frsf,gstar,vai1,vai2
370     _RL vaisd,velco,deluu,delvv,delve2,delz,vsqua
371     _RL richsn,crifro,crif2,fro2,coef
372 molod 1.1
373     c Initialization
374     c --------------
375     a = 1.0
376     g = 1.0
377 molod 1.4 agrav = 1.0/grav
378 molod 1.1 akwnmb = 1.0/lstar
379 molod 1.4 gocp = grav/cp
380 molod 1.1
381 molod 1.4 c Compute Atmospheric Density (with virtual temp)
382     c -----------------------------------------------
383     do l = 1,Lm
384 molod 1.1 do i = 1,irun
385 molod 1.4 ro(i,L) = pl(i,Lm+1-L)/(rgas*t(i,Lm+1-L))
386 molod 1.1 enddo
387     enddo
388    
389     c Compute Layer Thicknesses
390     c -------------------------
391 molod 1.4 do l = 2,Lm
392 molod 1.1 do i = 1,irun
393 molod 1.4 roiave = ( 1./ro(i,L-1) + 1./ro(i,L) )*0.5
394 molod 1.5 dz(i,L) = agrav*roiave*( pl(i,Lm+2-L)-pl(i,Lm+1-L) )
395 molod 1.1 enddo
396     enddo
397    
398    
399 molod 1.4 c***********************************************************************
400     c Surface and Base Layer Stress *
401     c***********************************************************************
402 molod 1.1
403     c Definition of Surface Wind Vector
404     c ---------------------------------
405     do i = 1,irun
406 molod 1.4 robar(i) = 0.0
407 molod 1.1 ubar(i) = 0.0
408     vbar(i) = 0.0
409     enddo
410    
411     do i = 1,irun
412     do L = 1,nbase(i)-1
413 molod 1.5 robar(i) = robar(i) + ro(i,L) * (ple(i,Lm+2-L)-ple(i,Lm+1-L))
414     ubar(i) = ubar(i) + u(i,Lm+1-L) * (ple(i,Lm+2-L)-ple(i,Lm+1-L))
415     vbar(i) = vbar(i) + v(i,Lm+1-L) * (ple(i,Lm+2-L)-ple(i,Lm+1-L))
416 molod 1.1 enddo
417     enddo
418    
419     do i = 1,irun
420 molod 1.8 robar(i) = robar(i)/(ps(i)-ple(i,Lm+1-(nbase(i)-1))) * 100.0
421     ubar(i) = ubar(i)/(ps(i)-ple(i,Lm+1-(nbase(i)-1)))
422     vbar(i) = vbar(i)/(ps(i)-ple(i,Lm+1-(nbase(i)-1)))
423 molod 1.1
424 molod 1.4 speed(i) = sqrt( ubar(i)*ubar(i) + vbar(i)*vbar(i) )
425     ang(i) = atan2(vbar(i),ubar(i))
426 molod 1.1 enddo
427    
428     c Brunt Vaisala Frequency
429     c -----------------------
430     do i = 1,irun
431 molod 1.4 do l = 2,nbase(i)
432     vai1 = (t(i,Lm+1-L)-t(i,Lm+2-L))/dz(i,L)+gocp
433     if( vai1.LT.0.0 ) then
434     vai1 = 0.0
435     endif
436     vai2 = 2.0*grav/( t(i,Lm+1-L)+t(i,Lm+2-L) )
437     vsqua = vai1*vai2
438     bv(i,L) = sqrt(vsqua)
439     enddo
440 molod 1.1 enddo
441    
442     c Stress at the Surface Level
443     c ---------------------------
444     do i = 1,irun
445 molod 1.4 nbar(i) = 0.0
446 molod 1.1 enddo
447     do i = 1,irun
448     do l = 2,nbase(i)
449 molod 1.5 nbar(i) = nbar(i) + bv(i,L)*(pl(i,Lm+2-L)-pl(i,Lm+1-L))
450 molod 1.1 enddo
451     enddo
452    
453     do i = 1,irun
454 molod 1.4 nbar(i) = nbar(i)/(pl(i,Lm)-pl(i,Lm+1-nbase(i)))
455     frsf = nbar(i)*std(i)/speed(i)
456 molod 1.1
457 molod 1.4 if( speed(i).eq.0.0 .or. nbar(i).eq.0.0 ) then
458     tensio(i,1) = 0.0
459     else
460     gstar = g*frsf*frsf/(frsf*frsf+a*a)
461     tensio(i,1) = gstar*(robar(i)*speed(i)*speed(i)*speed(i))
462     . / (nbar(i)*lstar)
463     endif
464 molod 1.1
465 molod 1.4 xtens(i,1) = tensio(i,1) * cos(ang(i))
466     ytens(i,1) = tensio(i,1) * sin(ang(i))
467     dragsf(i) = tensio(i,1)
468     xdrag(i) = xtens(i,1)
469     ydrag(i) = ytens(i,1)
470 molod 1.1 enddo
471    
472     c Check for Very thin lowest layer
473     c --------------------------------
474     do i = 1,irun
475 molod 1.4 if( nthin(i).gt.1 ) then
476     do l = 1,nthin(i)
477     tensio(i,L) = tensio(i,1)
478     xtens(i,L) = xtens(i,1)
479     ytens(i,L) = ytens(i,1)
480     enddo
481     endif
482 molod 1.1 enddo
483    
484     c******************************************************
485     c Compute Gravity Wave Stress from NTHIN+1 to NBASE *
486     c******************************************************
487    
488     do i = 1,irun
489 molod 1.4 do l = nthin(i)+1,nbase(i)
490 molod 1.1
491 molod 1.4 velco = 0.5*( (u(i,Lm+1-L)*ubar(i) + v(i,Lm+1-L)*vbar(i))
492     . + (u(i,Lm+2-L)*ubar(i) + v(i,Lm+2-L)*vbar(i)) )
493 molod 1.1 . / speed(i)
494    
495     C Convert to Newton/m**2
496 molod 1.4 roave = 0.5*(ro(i,L-1)+ro(i,L)) * 100.0
497 molod 1.1
498 molod 1.4 if( velco.le.0.0 ) then
499     tensio(i,L) = tensio(i,L-1)
500     goto 1500
501     endif
502 molod 1.1
503     c Froude number squared
504     c ---------------------
505 molod 1.4 fro2 = bv(i,L)/(akwnmb*roave*velco*velco*velco)*tensio(i,L-1)
506     deluu = u(i,Lm+1-L)-u(i,Lm+2-L)
507     delvv = v(i,Lm+1-L)-v(i,Lm+2-L)
508     delve2 = ( deluu*deluu + delvv*delvv )
509 molod 1.1
510     c Compute Richarson Number
511     c ------------------------
512 molod 1.4 if( delve2.ne.0.0 ) then
513     delz = dz(i,L)
514     vsqua = bv(i,L)*bv(i,L)
515     richsn = delz*delz*vsqua/delve2
516     else
517     richsn = 99999.0
518     endif
519    
520     if( richsn.le.0.25 ) then
521     tensio(i,L) = tensio(i,L-1)
522     goto 1500
523     endif
524 molod 1.1
525     c Stress in the Base Layer changes if the local Froude number
526     c exceeds the Critical Froude number
527     c ----------------------------------
528 molod 1.4 crifro = 1.0 - 0.25/richsn
529     crif2 = crifro*crifro
530 ce107 1.9 if( l.eq.2 ) crif2 = min(0.7 _d 0,crif2)
531 molod 1.4
532     if( fro2.gt.crif2 ) then
533     tensio(i,L) = crif2/fro2*tensio(i,L-1)
534     else
535     tensio(i,L) = tensio(i,L-1)
536     endif
537    
538     1500 continue
539     xtens(i,L) = tensio(i,L)*cos(ang(i))
540     ytens(i,L) = tensio(i,L)*sin(ang(i))
541 molod 1.1
542 molod 1.4 enddo
543 molod 1.1 enddo
544    
545     c******************************************************
546     c Compute Gravity Wave Stress from Base+1 to Top *
547     c******************************************************
548    
549     do i = 1,irun
550 molod 1.4 icrilv(i) = 0
551 molod 1.1 enddo
552    
553     do i = 1,irun
554 molod 1.4 do l = nbase(i)+1,Lm+1
555 molod 1.1
556 molod 1.4 tensio(i,L) = 0.0
557 molod 1.1
558     c Check for Critical Level Absorption
559     c -----------------------------------
560 molod 1.4 if( icrilv(i).eq.1 ) goto 130
561 molod 1.1
562     c Let Remaining Stress escape out the top edge of model
563     c -----------------------------------------------------
564 molod 1.4 if( l.eq.Lm+1 ) then
565     tensio(i,L) = tensio(i,L-1)
566     goto 130
567     endif
568 molod 1.1
569 molod 1.4 roave = 0.5*(ro(i,L-1)+ro(i,L)) * 100.0
570     vai1 = (t(i,Lm+1-L)-t(i,Lm+2-L))/dz(i,L)+gocp
571 molod 1.1
572 molod 1.4 if( vai1.lt.0.0 ) then
573     icrilv(i) = 1
574     tensio(i,L) = 0.0
575     goto 130
576     endif
577    
578     vai2 = 2.0*grav/(t(i,Lm+1-L)+t(i,Lm+2-L))
579     vsqua = vai1*vai2
580     vaisd = sqrt(vsqua)
581 molod 1.1
582 molod 1.4 velco = 0.5*( (u(i,Lm+1-L)*ubar(i) + v(i,Lm+1-L)*vbar(i))
583     . + (u(i,Lm+2-L)*ubar(i) + v(i,Lm+2-L)*vbar(i)) )
584 molod 1.1 . / speed(i)
585    
586 molod 1.4 if( velco.lt.0.0 ) then
587     icrilv(i) = 1
588     tensio(i,L) = 0.0
589     goto 130
590     endif
591 molod 1.1
592     c Froude number squared
593     c ---------------------
594 molod 1.4 fro2 = vaisd/(akwnmb*roave*velco*velco*velco)*tensio(i,L-1)
595     deluu = u(i,Lm+1-L)-u(i,Lm+2-L)
596     delvv = v(i,Lm+1-L)-v(i,Lm+2-L)
597     delve2 = ( deluu*deluu + delvv*delvv )
598 molod 1.1
599     c Compute Richarson Number
600     c ------------------------
601 molod 1.4 if( delve2.ne.0.0 ) then
602     delz = dz(i,L)
603     richsn = delz*delz*vsqua/delve2
604     else
605     richsn = 99999.0
606     endif
607    
608     if( richsn.le.0.25 ) then
609     tensio(i,L) = 0.0
610     icrilv(i) = 1
611     goto 130
612     endif
613 molod 1.1
614     c Stress in Layer changes if the local Froude number
615     c exceeds the Critical Froude number
616     c ----------------------------------
617 molod 1.4 crifro = 1.0 - 0.25/richsn
618     crif2 = crifro*crifro
619 molod 1.1
620 molod 1.4 if( fro2.ge.crif2 ) then
621     tensio(i,L) = crif2/fro2*tensio(i,L-1)
622     else
623     tensio(i,L) = tensio(i,L-1)
624     endif
625    
626     130 continue
627     xtens(i,L) = tensio(i,L)*cos(ang(i))
628     ytens(i,L) = tensio(i,L)*sin(ang(i))
629     enddo
630 molod 1.1 enddo
631    
632     C ******************************************************
633     C MOMENTUM CHANGE FOR FREE ATMOSPHERE *
634     C ******************************************************
635    
636     do i = 1,irun
637 molod 1.4 do l = nthin(i)+1,Lm
638 molod 1.5 coef = -grav*ps(i)/dpres(i,Lm+1-L)
639 molod 1.4 dudt(i,Lm+1-L) = coef*(xtens(i,L+1)-xtens(i,L))
640     dvdt(i,Lm+1-L) = coef*(ytens(i,L+1)-ytens(i,L))
641 molod 1.1 enddo
642     enddo
643    
644     c Momentum change near the surface
645     c --------------------------------
646     do i = 1,irun
647 molod 1.5 coef = grav*ps(i)/(ple(i,Lm+1-nthin(i))-ple(i,Lm+1))
648 molod 1.4 dudt(i,Lm) = coef*(xtens(i,nthin(i)+1)-xtens(i,1))
649     dvdt(i,Lm) = coef*(ytens(i,nthin(i)+1)-ytens(i,1))
650 molod 1.1 enddo
651    
652     c If Lowest layer is very thin, it is strapped to next layer
653     c ----------------------------------------------------------
654     do i = 1,irun
655 molod 1.4 if( nthin(i).gt.1 ) then
656     do l = 2,nthin(i)
657     dudt(i,Lm+1-L) = dudt(i,Lm)
658     dvdt(i,Lm+1-L) = dvdt(i,Lm)
659     enddo
660     endif
661 molod 1.1 enddo
662    
663     c Convert Units to (m/sec**2)
664     c ---------------------------
665 molod 1.4 do l = 1,Lm
666 molod 1.1 do i = 1,irun
667 molod 1.4 dudt(i,L) = - dudt(i,L)/ps(i)*0.01
668     dvdt(i,L) = - dvdt(i,L)/ps(i)*0.01
669 molod 1.1 enddo
670     enddo
671    
672     return
673     end

  ViewVC Help
Powered by ViewVC 1.1.22