/[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.6 - (hide annotations) (download)
Tue May 31 20:14:37 2005 UTC (19 years, 1 month ago) by molod
Branch: MAIN
Changes since 1.5: +4 -4 lines
little bug fix

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

  ViewVC Help
Powered by ViewVC 1.1.22