/[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.12 - (hide annotations) (download)
Tue May 24 14:31:14 2011 UTC (12 years, 11 months ago) by jmc
Branch: MAIN
CVS Tags: checkpoint62z, checkpoint62y, checkpoint63g, checkpoint63, checkpoint63p, checkpoint63q, checkpoint63r, checkpoint63s, checkpoint63l, checkpoint63m, checkpoint63n, checkpoint63o, checkpoint63h, checkpoint63i, checkpoint63j, checkpoint63k, checkpoint63d, checkpoint63e, checkpoint63f, checkpoint63a, checkpoint63b, checkpoint63c
Changes since 1.11: +4 -2 lines
split header file "OBCS.h" into 4 separated files:
  OBCS_PARAMS.h, OBCS_GRID.h, OBCS_FIELDS.h & OBCS_SEAICE.h

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

  ViewVC Help
Powered by ViewVC 1.1.22