/[MITgcm]/MITgcm/pkg/obcs/orlanski_west.F
ViewVC logotype

Annotation of /MITgcm/pkg/obcs/orlanski_west.F

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


Revision 1.6 - (hide annotations) (download)
Tue Jul 6 20:23:32 2004 UTC (19 years, 10 months ago) by adcroft
Branch: MAIN
Changes since 1.5: +10 -10 lines
Fixed some F77 formatting problems
 o source code beyond 72nd column

1 adcroft 1.6 C $Header: /u/gcmpack/MITgcm/pkg/obcs/orlanski_west.F,v 1.5 2004/07/06 18:25:52 adcroft Exp $
2     C $Name: $
3 adcroft 1.5 cc
4 adcroft 1.2
5     #include "OBCS_OPTIONS.h"
6    
7     SUBROUTINE ORLANSKI_WEST( bi, bj, futureTime,
8     I uVel, vVel, wVel, theta, salt,
9     I myThid )
10     C /==========================================================\
11     C | SUBROUTINE ORLANSKI_WEST |
12     C | o Calculate future boundary data at open boundaries |
13     C | at time = futureTime by applying Orlanski radiation |
14     C | conditions. |
15     C |==========================================================|
16     C | |
17     C \==========================================================/
18     IMPLICIT NONE
19    
20     C === Global variables ===
21     #include "SIZE.h"
22     #include "EEPARAMS.h"
23     #include "PARAMS.h"
24     #include "GRID.h"
25     #include "OBCS.h"
26     #include "ORLANSKI.h"
27    
28 adcroft 1.3 C SPK 6/2/00: Added radiative OBCs for salinity.
29 adcroft 1.2 C SPK 6/6/00: Changed calculation of OB*w. When K=1, the
30     C upstream value is used. For example on the eastern OB:
31     C IF (K.EQ.1) THEN
32     C OBEw(J,K,bi,bj)=wVel(I_obc-1,J,K,bi,bj)
33     C ENDIF
34     C
35     C SPK 7/7/00: 1) Removed OB*w fix (see above).
36     C 2) Added variable CMAX. Maximum diagnosed phase speed is now
37     C clamped to CMAX. For stability of AB-II scheme (CFL) the
38     C (non-dimensional) phase speed must be <0.5
39     C 3) (Sonya Legg) Changed application of uVel and vVel.
40     C uVel on the western OB is actually applied at I_obc+1
41     C while vVel on the southern OB is applied at J_obc+1.
42 adcroft 1.3 C 4) (Sonya Legg) Added templates for forced OBs.
43 adcroft 1.2 C
44     C SPK 7/17/00: Non-uniform resolution is now taken into account in diagnosing
45     C phase speeds and time-stepping OB values. CL is still the
46     C non-dimensional phase speed; CVEL is the dimensional phase
47     C speed: CVEL = CL*(dx or dy)/dt, where dx and dy is the
48     C appropriate grid spacings. Note that CMAX (with which CL
49     C is compared) remains non-dimensional.
50     C
51     C SPK 7/18/00: Added code to allow filtering of phase speed following
52     C Blumberg and Kantha. There is now a separate array
53     C CVEL_**, where **=Variable(U,V,T,S,W)Boundary(E,W,N,S) for
54     C the dimensional phase speed. These arrays are initialized to
55     C zero in ini_obcs.F. CVEL_** is filtered according to
56     C CVEL_** = fracCVEL*CVEL(new) + (1-fracCVEL)*CVEL_**(old).
57     C fracCVEL=1.0 turns off filtering.
58     C
59     C SPK 7/26/00: Changed code to average phase speed. A new variable
60     C 'cvelTimeScale' was created. This variable must now be
61     C specified. Then, fracCVEL=deltaT/cvelTimeScale.
62     C Since the goal is to smooth out the 'singularities' in the
63     C diagnosed phase speed, cvelTimeScale could be picked as the
64     C duration of the singular period in the unfiltered case. Thus,
65     C for a plane wave cvelTimeScale might be the time take for the
66     C wave to travel a distance DX, where DX is the width of the region
67     C near which d(phi)/dx is small.
68 adcroft 1.5 C
69     C JBG 3/24/03: Fixed phase speed at western boundary (as suggested by
70     C Dale Durran's MWR paper). Fixed value (in m/s) is
71     C passed in as variable CFIX in data.obcs.
72     C
73     C JBG 4/10/03: allow choice of Orlanski or fixed wavespeed (by means of new
74     C booleans useFixedCEast and useFixedCWest) without
75     C having to recompile each time
76     c SAL 1/7/03: Fixed bug: implementation for salinity was incomplete
77     C
78 adcroft 1.2
79     C == Routine arguments ==
80     INTEGER bi, bj
81     _RL futureTime
82     _RL uVel (1-OLx:sNx+OLx,1-OLy:sNy+OLy,Nr,nSx,nSy)
83     _RL vVel (1-OLx:sNx+OLx,1-OLy:sNy+OLy,Nr,nSx,nSy)
84     _RL wVel (1-OLx:sNx+OLx,1-OLy:sNy+OLy,Nr,nSx,nSy)
85     _RL theta(1-OLx:sNx+OLx,1-OLy:sNy+OLy,Nr,nSx,nSy)
86     _RL salt (1-OLx:sNx+OLx,1-OLy:sNy+OLy,Nr,nSx,nSy)
87     INTEGER myThid
88    
89     #ifdef ALLOW_ORLANSKI
90    
91     C == Local variables ==
92     INTEGER J, K, I_obc
93     _RL CL, ab1, ab2, fracCVEL, f1, f2
94    
95     ab1 = 1.5 _d 0 + abEps /* Adams-Bashforth coefficients */
96     ab2 = -0.5 _d 0 - abEps
97     /* CMAX is maximum allowable phase speed-CFL for AB-II */
98     /* cvelTimeScale is averaging period for phase speed in sec. */
99    
100     fracCVEL = deltaT/cvelTimeScale /* fraction of new phase speed used*/
101 adcroft 1.3 f1 = fracCVEL /* dont change this. Set cvelTimeScale */
102     f2 = 1.0-fracCVEL /* dont change this. set cvelTimeScale */
103 adcroft 1.2
104     C Western OB (Orlanski Radiation Condition)
105     DO K=1,Nr
106     DO J=1-Oly,sNy+Oly
107     I_obc=OB_Iw(J,bi,bj)
108     IF (I_obc.ne.0) THEN
109     C uVel (to be applied at I_obc+1)
110     IF ((UW_STORE_2(J,K,bi,bj).eq.0.).and.
111     & (UW_STORE_3(J,K,bi,bj).eq.0.)) THEN
112     CL=0.
113     ELSE
114     CL=(uVel(I_obc+2,J,K,bi,bj)-UW_STORE_1(J,K,bi,bj))/
115     & (ab1*UW_STORE_2(J,K,bi,bj) + ab2*UW_STORE_3(J,K,bi,bj))
116     ENDIF
117     IF (CL.lt.0.) THEN
118     CL=0.
119     ELSEIF (CL.gt.CMAX) THEN
120     CL=CMAX
121     ENDIF
122 adcroft 1.5 IF (useFixedCWest) THEN
123     C Fixed phase speed (ignoring all of that painstakingly
124     C saved data...)
125     CVEL_UW(J,K,bi,bj) = CFIX
126     ELSE
127 adcroft 1.6 CVEL_UW(J,K,bi,bj) = f1*(CL*dxF(I_obc+2,J,bi,bj)/deltaT
128     & )+f2*CVEL_UW(J,K,bi,bj)
129 adcroft 1.5 ENDIF
130 adcroft 1.2 C update OBC to next timestep
131     OBWu(J,K,bi,bj)=uVel(I_obc+1,J,K,bi,bj)+
132 adcroft 1.5 & CVEL_UW(J,K,bi,bj)*(deltaT/dxF(I_obc+1,J,bi,bj))*
133 adcroft 1.2 & (ab1*(uVel(I_obc+2,J,K,bi,bj)-uVel(I_obc+1,J,K,bi,bj))+
134     & ab2*(UW_STORE_1(J,K,bi,bj)-UW_STORE_4(J,K,bi,bj)))
135     C vVel
136     IF ((VW_STORE_2(J,K,bi,bj).eq.0.).and.
137     & (VW_STORE_3(J,K,bi,bj).eq.0.)) THEN
138     CL=0.
139     ELSE
140     CL=(vVel(I_obc+1,J,K,bi,bj)-VW_STORE_1(J,K,bi,bj))/
141     & (ab1*VW_STORE_2(J,K,bi,bj) + ab2*VW_STORE_3(J,K,bi,bj))
142     ENDIF
143     IF (CL.lt.0.) THEN
144     CL=0.
145     ELSEIF (CL.gt.CMAX) THEN
146     CL=CMAX
147     ENDIF
148 adcroft 1.5 IF (useFixedCWest) THEN
149     C Fixed phase speed (ignoring all of that painstakingly
150     C saved data...)
151     CVEL_VW(J,K,bi,bj) = CFIX
152     ELSE
153 adcroft 1.6 CVEL_VW(J,K,bi,bj) = f1*(CL*dxV(I_obc+2,J,bi,bj)/deltaT
154     & )+f2*CVEL_VW(J,K,bi,bj)
155 adcroft 1.5 ENDIF
156 adcroft 1.2 C update OBC to next timestep
157     OBWv(J,K,bi,bj)=vVel(I_obc,J,K,bi,bj)+
158 adcroft 1.5 & CVEL_VW(J,K,bi,bj)*(deltaT/dxV(I_obc+1,J,bi,bj))*
159 adcroft 1.2 & (ab1*(vVel(I_obc+1,J,K,bi,bj)-vVel(I_obc,J,K,bi,bj))+
160     & ab2*(VW_STORE_1(J,K,bi,bj)-VW_STORE_4(J,K,bi,bj)))
161     C Temperature
162     IF ((TW_STORE_2(J,K,bi,bj).eq.0.).and.
163     & (TW_STORE_3(J,K,bi,bj).eq.0.)) THEN
164     CL=0.
165     ELSE
166     CL=(theta(I_obc+1,J,K,bi,bj)-TW_STORE_1(J,K,bi,bj))/
167     & (ab1*TW_STORE_2(J,K,bi,bj) + ab2*TW_STORE_3(J,K,bi,bj))
168     ENDIF
169     IF (CL.lt.0.) THEN
170     CL=0.
171     ELSEIF (CL.gt.CMAX) THEN
172     CL=CMAX
173     ENDIF
174 adcroft 1.5 IF (useFixedCWest) THEN
175     C Fixed phase speed (ignoring all of that painstakingly
176     C saved data...)
177     CVEL_TW(J,K,bi,bj) = CFIX
178     ELSE
179 adcroft 1.6 CVEL_TW(J,K,bi,bj) = f1*(CL*dxC(I_obc+2,J,bi,bj)/deltaT
180     & )+f2*CVEL_TW(J,K,bi,bj)
181 adcroft 1.5 ENDIF
182 adcroft 1.2 C update OBC to next timestep
183     OBWt(J,K,bi,bj)=theta(I_obc,J,K,bi,bj)+
184 adcroft 1.5 & CVEL_TW(J,K,bi,bj)*(deltaT/dxC(I_obc+1,J,bi,bj))*
185 adcroft 1.2 & (ab1*(theta(I_obc+1,J,K,bi,bj)-theta(I_obc,J,K,bi,bj))+
186     & ab2*(TW_STORE_1(J,K,bi,bj)-TW_STORE_4(J,K,bi,bj)))
187     C Salinity
188     IF ((SW_STORE_2(J,K,bi,bj).eq.0.).and.
189     & (SW_STORE_3(J,K,bi,bj).eq.0.)) THEN
190     CL=0.
191     ELSE
192     CL=(salt(I_obc+1,J,K,bi,bj)-SW_STORE_1(J,K,bi,bj))/
193     & (ab1*SW_STORE_2(J,K,bi,bj) + ab2*SW_STORE_3(J,K,bi,bj))
194     ENDIF
195     IF (CL.lt.0.) THEN
196     CL=0.
197     ELSEIF (CL.gt.CMAX) THEN
198     CL=CMAX
199     ENDIF
200 adcroft 1.5 IF (useFixedCWest) THEN
201     C Fixed phase speed (ignoring all of that painstakingly
202     C saved data...)
203     CVEL_SW(J,K,bi,bj) = CFIX
204     ELSE
205 adcroft 1.6 CVEL_SW(J,K,bi,bj) = f1*(CL*dxC(I_obc+2,J,bi,bj)/deltaT
206     & )+f2*CVEL_SW(J,K,bi,bj)
207 adcroft 1.5 ENDIF
208 adcroft 1.2 C update OBC to next timestep
209     OBWs(J,K,bi,bj)=salt(I_obc,J,K,bi,bj)+
210 adcroft 1.5 & CVEL_SW(J,K,bi,bj)*(deltaT/dxC(I_obc+1,J,bi,bj))*
211 adcroft 1.2 & (ab1*(salt(I_obc+1,J,K,bi,bj)-salt(I_obc,J,K,bi,bj))+
212     & ab2*(SW_STORE_1(J,K,bi,bj)-SW_STORE_4(J,K,bi,bj)))
213     C wVel
214     #ifdef ALLOW_NONHYDROSTATIC
215     IF ((WW_STORE_2(J,K,bi,bj).eq.0.).and.
216     & (WW_STORE_3(J,K,bi,bj).eq.0.)) THEN
217     CL=0.
218     ELSE
219     CL=(wVel(I_obc+1,J,K,bi,bj)-WW_STORE_1(J,K,bi,bj))/
220     & (ab1*WW_STORE_2(J,K,bi,bj)+ab2*WW_STORE_3(J,K,bi,bj))
221     ENDIF
222     IF (CL.lt.0.) THEN
223     CL=0.
224     ELSEIF (CL.gt.CMAX) THEN
225     CL=CMAX
226     ENDIF
227 adcroft 1.5 IF (useFixedCWest) THEN
228     C Fixed phase speed (ignoring all of that painstakingly
229     C saved data...)
230     CVEL_WW(J,K,bi,bj) = CFIX
231     ELSE
232     CVEL_WW(J,K,bi,bj)=f1*(CL*dxC(I_obc+2,J,bi,bj)/deltaT)
233 adcroft 1.2 & + f2*CVEL_WW(J,K,bi,bj)
234 adcroft 1.5 ENDIF
235 adcroft 1.2 C update OBC to next timestep
236     OBWw(J,K,bi,bj)=wVel(I_obc,J,K,bi,bj)+
237 adcroft 1.5 & CVEL_WW(J,K,bi,bj)*(deltaT/dxC(I_obc+1,J,bi,bj))*
238 adcroft 1.2 & (ab1*(wVel(I_obc+1,J,K,bi,bj)-wVel(I_obc,J,K,bi,bj))+
239     & ab2*(WW_STORE_1(J,K,bi,bj)-WW_STORE_4(J,K,bi,bj)))
240     #endif
241     C update/save storage arrays
242     C uVel
243     C copy t-1 to t-2 array
244     UW_STORE_3(J,K,bi,bj)=UW_STORE_2(J,K,bi,bj)
245     C copy (current time) t to t-1 arrays
246     UW_STORE_2(J,K,bi,bj)=uVel(I_obc+3,J,K,bi,bj) -
247     & uVel(I_obc+2,J,K,bi,bj)
248     UW_STORE_1(J,K,bi,bj)=uVel(I_obc+2,J,K,bi,bj)
249     UW_STORE_4(J,K,bi,bj)=uVel(I_obc+1,J,K,bi,bj)
250     C vVel
251     C copy t-1 to t-2 array
252     VW_STORE_3(J,K,bi,bj)=VW_STORE_2(J,K,bi,bj)
253     C copy (current time) t to t-1 arrays
254     VW_STORE_2(J,K,bi,bj)=vVel(I_obc+2,J,K,bi,bj) -
255     & vVel(I_obc+1,J,K,bi,bj)
256     VW_STORE_1(J,K,bi,bj)=vVel(I_obc+1,J,K,bi,bj)
257     VW_STORE_4(J,K,bi,bj)=vVel(I_obc,J,K,bi,bj)
258     C Temperature
259     C copy t-1 to t-2 array
260     TW_STORE_3(J,K,bi,bj)=TW_STORE_2(J,K,bi,bj)
261     C copy (current time) t to t-1 arrays
262     TW_STORE_2(J,K,bi,bj)=theta(I_obc+2,J,K,bi,bj) -
263     & theta(I_obc+1,J,K,bi,bj)
264     TW_STORE_1(J,K,bi,bj)=theta(I_obc+1,J,K,bi,bj)
265     TW_STORE_4(J,K,bi,bj)=theta(I_obc,J,K,bi,bj)
266 adcroft 1.5 c Salinity
267     C copy t-1 to t-2 array
268     SW_STORE_3(J,K,bi,bj)=SW_STORE_2(J,K,bi,bj)
269     C copy (current time) t to t-1 arrays
270     SW_STORE_2(J,K,bi,bj)=salt(I_obc+2,J,K,bi,bj) -
271     & salt(I_obc+1,J,K,bi,bj)
272     SW_STORE_1(J,K,bi,bj)=salt(I_obc+1,J,K,bi,bj)
273     SW_STORE_4(J,K,bi,bj)=salt(I_obc,J,K,bi,bj)
274 adcroft 1.2 C wVel
275     #ifdef ALLOW_NONHYDROSTATIC
276     C copy t-1 to t-2 array
277     WW_STORE_3(J,K,bi,bj)=WW_STORE_2(J,K,bi,bj)
278     C copy (current time) t to t-1 arrays
279     WW_STORE_2(J,K,bi,bj)=wVel(I_obc+2,J,K,bi,bj) -
280     & wVel(I_obc+1,J,K,bi,bj)
281     WW_STORE_1(J,K,bi,bj)=wVel(I_obc+1,J,K,bi,bj)
282     WW_STORE_4(J,K,bi,bj)=wVel(I_obc,J,K,bi,bj)
283     #endif
284     ENDIF
285     ENDDO
286     ENDDO
287    
288     #endif /* ALLOW_ORLANSKI */
289     RETURN
290     END

  ViewVC Help
Powered by ViewVC 1.1.22