/[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.3 - (hide annotations) (download)
Tue May 24 00:02:29 2005 UTC (19 years, 1 month ago) by molod
Branch: MAIN
Changes since 1.2: +3 -1 lines
More prep for gravity wave drag testing

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

  ViewVC Help
Powered by ViewVC 1.1.22