/[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.8 - (hide annotations) (download)
Thu Jun 9 00:05:30 2005 UTC (19 years ago) by molod
Branch: MAIN
Changes since 1.7: +4 -4 lines
Little indexing problem in one little place

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

  ViewVC Help
Powered by ViewVC 1.1.22