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

Diff of /MITgcm/pkg/obcs/orlanski_east.F

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

revision 1.3.6.1 by heimbach, Tue Feb 5 20:23:59 2002 UTC revision 1.13 by jmc, Tue Sep 18 20:09:17 2012 UTC
# Line 1  Line 1 
1  C $Header$  C $Header$
2  C $Name$  C $Name$
3    cc
4    
5  #include "OBCS_OPTIONS.h"  #include "OBCS_OPTIONS.h"
6    
7        SUBROUTINE ORLANSKI_EAST( bi, bj, futureTime,        SUBROUTINE ORLANSKI_EAST( bi, bj, futureTime,
8       I                      uVel, vVel, wVel, theta, salt,       I                      uVel, vVel, wVel, theta, salt,
9       I                      myThid )       I                      myThid )
10  C     /==========================================================\  C     /==========================================================\
11  C     | SUBROUTINE ORLANSKI_EAST                                 |  C     | SUBROUTINE ORLANSKI_EAST                                 |
# Line 21  C     === Global variables === Line 22  C     === Global variables ===
22  #include "EEPARAMS.h"  #include "EEPARAMS.h"
23  #include "PARAMS.h"  #include "PARAMS.h"
24  #include "GRID.h"  #include "GRID.h"
25  #include "OBCS.h"  #include "OBCS_PARAMS.h"
26    #include "OBCS_GRID.h"
27    #include "OBCS_FIELDS.h"
28  #include "ORLANSKI.h"  #include "ORLANSKI.h"
29    
30  C SPK 6/2/00: Added radiative OBC's for salinity.  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  C SPK 6/6/00: Changed calculation of OB*w. When K=1, the
32  C             upstream value is used. For example on the eastern OB:  C             upstream value is used. For example on the eastern OB:
33  C                IF (K.EQ.1) THEN  C                IF (K.EQ.1) THEN
34  C                   OBEw(J,K,bi,bj)=wVel(I_obc-1,J,K,bi,bj)  C                   OBEw(J,K,bi,bj)=wVel(I_obc-1,J,K,bi,bj)
35  C                ENDIF  C                ENDIF
36  C                          C
37  C SPK 7/7/00: 1) Removed OB*w fix (see above).  C SPK 7/7/00: 1) Removed OB*w fix (see above).
38  C             2) Added variable CMAX. Maximum diagnosed phase speed is now  C             2) Added variable CMAX. Maximum diagnosed phase speed is now
39  C                clamped to CMAX. For stability of AB-II scheme (CFL) the  C                clamped to CMAX. For stability of AB-II scheme (CFL) the
40  C                (non-dimensional) phase speed must be <0.5  C                (non-dimensional) phase speed must be <0.5
41  C             3) (Sonya Legg) Changed application of uVel and vVel.  C             3) (Sonya Legg) Changed application of uVel and vVel.
42  C                uVel on the western OB is actually applied at I_obc+1  C                uVel on the western OB is actually applied at I_obc+1
43  C                while vVel on the southern OB is applied at J_obc+1.  C                while vVel on the southern OB is applied at J_obc+1.
44  C             4) (Sonya Legg) Added templates for forced OB's.  C             4) (Sonya Legg) Added templates for forced OBs.
45  C  C
46  C SPK 7/17/00: Non-uniform resolution is now taken into account in diagnosing  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  C              phase speeds and time-stepping OB values. CL is still the
48  C              non-dimensional phase speed; CVEL is the dimensional phase  C              non-dimensional phase speed; CVEL is the dimensional phase
49  C              speed: CVEL = CL*(dx or dy)/dt, where dx and dy is the  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  C              appropriate grid spacings. Note that CMAX (with which CL
51  C              is compared) remains non-dimensional.  C              is compared) remains non-dimensional.
52  C  C
53  C SPK 7/18/00: Added code to allow filtering of phase speed following  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  C              Blumberg and Kantha. There is now a separate array
55  C              CVEL_**, where **=Variable(U,V,T,S,W)Boundary(E,W,N,S) for  C              CVEL_**, where **=Variable(U,V,T,S,W)Boundary(E,W,N,S) for
56  C              the dimensional phase speed. These arrays are initialized to  C              the dimensional phase speed. These arrays are initialized to
57  C              zero in ini_obcs.F. CVEL_** is filtered according to  C              zero in ini_obcs.F. CVEL_** is filtered according to
58  C              CVEL_** = fracCVEL*CVEL(new) + (1-fracCVEL)*CVEL_**(old).  C              CVEL_** = fracCVEL*CVEL(new) + (1-fracCVEL)*CVEL_**(old).
59  C              fracCVEL=1.0 turns off filtering.  C              fracCVEL=1.0 turns off filtering.
60  C  C
61  C SPK 7/26/00: Changed code to average phase speed. A new variable  C SPK 7/26/00: Changed code to average phase speed. A new variable
62  C              'cvelTimeScale' was created. This variable must now be  C              'cvelTimeScale' was created. This variable must now be
63  C              specified. Then, fracCVEL=deltaT/cvelTimeScale.  C              specified. Then, fracCVEL=deltaT/cvelTimeScale.
64  C              Since the goal is to smooth out the 'singularities' in the  C              Since the goal is to smooth out the 'singularities' in the
65  C              diagnosed phase speed, cvelTimeScale could be picked as the  C              diagnosed phase speed, cvelTimeScale could be picked as the
66  C              duration of the singular period in the unfiltered case. Thus,  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  C              for a plane wave cvelTimeScale might be the time take for the
68  C              wave to travel a distance DX, where DX is the width of the region  C              wave to travel a distance DX, where DX is the width of the region
69  C              near which d(phi)/dx is small.  C              near which d(phi)/dx is small.
70    C
71    C JBG 4/10/03: Fixed phase speed at western boundary (as suggested by
72    C              Dale Durran in his MWR paper). Fixed value (in m/s) is
73    C              passed in as variable CFIX in data.obcs.
74    C              also now allow choice of Orlanski or fixed wavespeed
75    C              (by means of new booleans useFixedCEast and
76    C              useFixedCWest) without having to recompile each time
77    C
78    
79  C     == Routine arguments ==  C     == Routine arguments ==
80        INTEGER bi, bj        INTEGER bi, bj
# Line 76  C     == Routine arguments == Line 87  C     == Routine arguments ==
87        INTEGER myThid        INTEGER myThid
88    
89  #ifdef ALLOW_ORLANSKI  #ifdef ALLOW_ORLANSKI
90    #ifdef ALLOW_OBCS_EAST
91    
92  C     == Local variables ==  C     == Local variables ==
93        INTEGER J, K, I_obc        INTEGER J, K, I_obc
# Line 87  C     == Local variables == Line 99  C     == Local variables ==
99        /* cvelTimeScale is averaging period for phase speed in sec. */        /* cvelTimeScale is averaging period for phase speed in sec. */
100    
101        fracCVEL = deltaT/cvelTimeScale /* fraction of new phase speed used*/        fracCVEL = deltaT/cvelTimeScale /* fraction of new phase speed used*/
102        f1 = fracCVEL /* don't change this. Set cvelTimeScale */        f1 = fracCVEL /* dont change this. Set cvelTimeScale */
103        f2 = 1.0-fracCVEL   /* don't change this. set cvelTimeScale */        f2 = 1.0-fracCVEL   /* dont change this. set cvelTimeScale */
104    
105  C     Eastern OB (Orlanski Radiation Condition)  C     Eastern OB (Orlanski Radiation Condition)
106        DO K=1,Nr        DO K=1,Nr
107           DO J=1-Oly,sNy+Oly           DO J=1-OLy,sNy+OLy
108              I_obc=OB_Ie(J,bi,bj)              I_obc=OB_Ie(J,bi,bj)
109              IF (I_obc.ne.0) THEN              IF ( I_obc.NE.OB_indexNone ) THEN
110  C              uVel  C              uVel
111                 IF ((UE_STORE_2(J,K,bi,bj).eq.0.).and.                 IF ((UE_STORE_2(J,K,bi,bj).eq.0.).and.
112       &            (UE_STORE_3(J,K,bi,bj).eq.0.)) THEN       &            (UE_STORE_3(J,K,bi,bj).eq.0.)) THEN
# Line 108  C              uVel Line 120  C              uVel
120                 ELSEIF (CL.gt.CMAX) THEN                 ELSEIF (CL.gt.CMAX) THEN
121                    CL=CMAX                    CL=CMAX
122                 ENDIF                 ENDIF
123                 CVEL_UE(J,K,bi,bj) = f1*(CL*dxF(I_obc-2,J,bi,bj)/deltaT)+                 IF (useFixedCEast) THEN
124       &                f2*CVEL_UE(J,K,bi,bj)  C                Fixed phase speed (ignoring all of that painstakingly
125    C                saved data...)
126                     CVEL_UE(J,K,bi,bj) = CFIX
127                   ELSE
128                     CVEL_UE(J,K,bi,bj) = f1*(CL*dxF(I_obc-2,J,bi,bj)/deltaT
129         &              )+f2*CVEL_UE(J,K,bi,bj)
130                   ENDIF
131  C              update OBC to next timestep  C              update OBC to next timestep
132                 OBEu(J,K,bi,bj)=uVel(I_obc,J,K,bi,bj)-                 OBEu(J,K,bi,bj)=uVel(I_obc,J,K,bi,bj)-
133       &           CVEL_UE(J,K,bi,bj)*(deltaT/dxF(I_obc-1,J,bi,bj))*       &           CVEL_UE(J,K,bi,bj)*(deltaT*recip_dxF(I_obc-1,J,bi,bj))*
134       &           (ab1*(uVel(I_obc,J,K,bi,bj)-uVel(I_obc-1,J,K,bi,bj)) +       &           (ab1*(uVel(I_obc,J,K,bi,bj)-uVel(I_obc-1,J,K,bi,bj)) +
135       &           ab2*(UE_STORE_4(J,K,bi,bj)-UE_STORE_1(J,K,bi,bj)))       &           ab2*(UE_STORE_4(J,K,bi,bj)-UE_STORE_1(J,K,bi,bj)))
136  C              vVel  C              vVel
# Line 122  C              vVel Line 140  C              vVel
140                 ELSE                 ELSE
141                    CL=-(vVel(I_obc-1,J,K,bi,bj)-VE_STORE_1(J,K,bi,bj))/                    CL=-(vVel(I_obc-1,J,K,bi,bj)-VE_STORE_1(J,K,bi,bj))/
142       &          (ab1*VE_STORE_2(J,K,bi,bj) + ab2*VE_STORE_3(J,K,bi,bj))       &          (ab1*VE_STORE_2(J,K,bi,bj) + ab2*VE_STORE_3(J,K,bi,bj))
143                 ENDIF                             ENDIF
144                 IF (CL.lt.0.) THEN                 IF (CL.lt.0.) THEN
145                    CL=0.                    CL=0.
146                 ELSEIF (CL.gt.CMAX) THEN                 ELSEIF (CL.gt.CMAX) THEN
147                    CL=CMAX                    CL=CMAX
148                 ENDIF                 ENDIF
149                 CVEL_VE(J,K,bi,bj) = f1*(CL*dxV(I_obc-1,J,bi,bj)/deltaT)+                 IF (useFixedCEast) THEN
150       &                f2*CVEL_VE(J,K,bi,bj)  C                Fixed phase speed (ignoring all of that painstakingly
151    C                saved data...)
152                     CVEL_VE(J,K,bi,bj) = CFIX
153                   ELSE
154                     CVEL_VE(J,K,bi,bj) = f1*(CL*dxV(I_obc-1,J,bi,bj)
155         $                 /deltaT)+f2*CVEL_VE(J,K,bi,bj)
156                   ENDIF
157  C              update OBC to next timestep  C              update OBC to next timestep
158                 OBEv(J,K,bi,bj)=vVel(I_obc,J,K,bi,bj)-                 OBEv(J,K,bi,bj)=vVel(I_obc,J,K,bi,bj)-
159       &           CVEL_VE(J,K,bi,bj)*(deltaT/dxV(I_obc,J,bi,bj))*       &           CVEL_VE(J,K,bi,bj)*(deltaT*recip_dxV(I_obc,J,bi,bj))*
160       &           (ab1*(vVel(I_obc,J,K,bi,bj)-vVel(I_obc-1,J,K,bi,bj)) +       &           (ab1*(vVel(I_obc,J,K,bi,bj)-vVel(I_obc-1,J,K,bi,bj)) +
161       &           ab2*(VE_STORE_4(J,K,bi,bj)-VE_STORE_1(J,K,bi,bj)))                   &           ab2*(VE_STORE_4(J,K,bi,bj)-VE_STORE_1(J,K,bi,bj)))
162  C              Temperature  C              Temperature
163                 IF ((TE_STORE_2(J,K,bi,bj).eq.0.).and.                 IF ((TE_STORE_2(J,K,bi,bj).eq.0.).and.
164       &            (TE_STORE_3(J,K,bi,bj).eq.0.)) THEN       &            (TE_STORE_3(J,K,bi,bj).eq.0.)) THEN
# Line 142  C              Temperature Line 166  C              Temperature
166                 ELSE                 ELSE
167                    CL=-(theta(I_obc-1,J,K,bi,bj)-TE_STORE_1(J,K,bi,bj))/                    CL=-(theta(I_obc-1,J,K,bi,bj)-TE_STORE_1(J,K,bi,bj))/
168       &          (ab1*TE_STORE_2(J,K,bi,bj) + ab2*TE_STORE_3(J,K,bi,bj))       &          (ab1*TE_STORE_2(J,K,bi,bj) + ab2*TE_STORE_3(J,K,bi,bj))
169                 ENDIF                 ENDIF
170                 IF (CL.lt.0.) THEN                 IF (CL.lt.0.) THEN
171                    CL=0.                    CL=0.
172                 ELSEIF (CL.gt.CMAX) THEN                 ELSEIF (CL.gt.CMAX) THEN
173                    CL=CMAX                    CL=CMAX
174                 ENDIF                 ENDIF
175                 CVEL_TE(J,K,bi,bj) = f1*(CL*dxC(I_obc-1,J,bi,bj)/deltaT)+                 IF (useFixedCEast) THEN
176       &                f2*CVEL_TE(J,K,bi,bj)  C                Fixed phase speed (ignoring all of that painstakingly
177    C                saved data...)
178                     CVEL_TE(J,K,bi,bj) = CFIX
179                   ELSE
180                     CVEL_TE(J,K,bi,bj) = f1*(CL*dxC(I_obc-1,J,bi,bj)
181         $                 /deltaT)+f2*CVEL_TE(J,K,bi,bj)
182                   ENDIF
183  C              update OBC to next timestep  C              update OBC to next timestep
184                 OBEt(J,K,bi,bj)=theta(I_obc,J,K,bi,bj)-                 OBEt(J,K,bi,bj)=theta(I_obc,J,K,bi,bj)-
185       &           CVEL_TE(J,K,bi,bj)*(deltaT/dxC(I_obc,J,bi,bj))*       &           CVEL_TE(J,K,bi,bj)*(deltaT*recip_dxC(I_obc,J,bi,bj))*
186       &           (ab1*(theta(I_obc,J,K,bi,bj)-theta(I_obc-1,J,K,bi,bj))+       &           (ab1*(theta(I_obc,J,K,bi,bj)-theta(I_obc-1,J,K,bi,bj))+
187       &           ab2*(TE_STORE_4(J,K,bi,bj)-TE_STORE_1(J,K,bi,bj)))       &           ab2*(TE_STORE_4(J,K,bi,bj)-TE_STORE_1(J,K,bi,bj)))
188  C              Salinity  C              Salinity
189                 IF ((SE_STORE_2(J,K,bi,bj).eq.0.).and.                 IF ((SE_STORE_2(J,K,bi,bj).eq.0.).and.
# Line 162  C              Salinity Line 192  C              Salinity
192                 ELSE                 ELSE
193                    CL=-(salt(I_obc-1,J,K,bi,bj)-SE_STORE_1(J,K,bi,bj))/                    CL=-(salt(I_obc-1,J,K,bi,bj)-SE_STORE_1(J,K,bi,bj))/
194       &          (ab1*SE_STORE_2(J,K,bi,bj) + ab2*SE_STORE_3(J,K,bi,bj))       &          (ab1*SE_STORE_2(J,K,bi,bj) + ab2*SE_STORE_3(J,K,bi,bj))
195                 ENDIF                 ENDIF
196                 IF (CL.lt.0.) THEN                 IF (CL.lt.0.) THEN
197                    CL=0.                    CL=0.
198                 ELSEIF (CL.gt.CMAX) THEN                 ELSEIF (CL.gt.CMAX) THEN
199                    CL=CMAX                    CL=CMAX
200                 ENDIF                 ENDIF
201                 CVEL_SE(J,K,bi,bj) = f1*(CL*dxC(I_obc-1,J,bi,bj)/deltaT)+                 IF (useFixedCEast) THEN
202       &                f2*CVEL_SE(J,K,bi,bj)  C                Fixed phase speed (ignoring all of that painstakingly
203    C                saved data...)
204                     CVEL_SE(J,K,bi,bj) = CFIX
205                   ELSE
206                     CVEL_SE(J,K,bi,bj) = f1*(CL*dxC(I_obc-1,J,bi,bj)
207         $                 /deltaT)+f2*CVEL_SE(J,K,bi,bj)
208                   ENDIF
209  C              update OBC to next timestep  C              update OBC to next timestep
210                 OBEs(J,K,bi,bj)=salt(I_obc,J,K,bi,bj)-                 OBEs(J,K,bi,bj)=salt(I_obc,J,K,bi,bj)-
211       &           CVEL_SE(J,K,bi,bj)*(deltaT/dxC(I_obc,J,bi,bj))*       &           CVEL_SE(J,K,bi,bj)*(deltaT*recip_dxC(I_obc,J,bi,bj))*
212       &           (ab1*(salt(I_obc,J,K,bi,bj)-salt(I_obc-1,J,K,bi,bj))+       &           (ab1*(salt(I_obc,J,K,bi,bj)-salt(I_obc-1,J,K,bi,bj))+
213       &           ab2*(SE_STORE_4(J,K,bi,bj)-SE_STORE_1(J,K,bi,bj)))       &           ab2*(SE_STORE_4(J,K,bi,bj)-SE_STORE_1(J,K,bi,bj)))
 C              wVel  
214  #ifdef ALLOW_NONHYDROSTATIC  #ifdef ALLOW_NONHYDROSTATIC
215                    IF ((WE_STORE_2(J,K,bi,bj).eq.0.).and.               IF ( nonHydrostatic ) THEN
216       &               (WE_STORE_3(J,K,bi,bj).eq.0.)) THEN  C              wVel
217                       CL=0.                 IF ((WE_STORE_2(J,K,bi,bj).eq.0.).and.
218                    ELSE       &            (WE_STORE_3(J,K,bi,bj).eq.0.)) THEN
219                      CL=-(wVel(I_obc-1,J,K,bi,bj)-WE_STORE_1(J,K,bi,bj))/                    CL=0.
220       &             (ab1*WE_STORE_2(J,K,bi,bj)+ab2*WE_STORE_3(J,K,bi,bj))                 ELSE
221                    ENDIF                    CL=-(wVel(I_obc-1,J,K,bi,bj)-WE_STORE_1(J,K,bi,bj))/
222                    IF (CL.lt.0.) THEN       &          (ab1*WE_STORE_2(J,K,bi,bj)+ab2*WE_STORE_3(J,K,bi,bj))
223                       CL=0.                 ENDIF
224                    ELSEIF (CL.gt.CMAX) THEN                 IF (CL.lt.0.) THEN
225                       CL=CMAX                    CL=0.
226                    ENDIF                 ELSEIF (CL.gt.CMAX) THEN
227                    CVEL_WE(J,K,bi,bj)=f1*(CL*dxC(I_obc-1,J,bi,bj)/deltaT)                    CL=CMAX
228                   ENDIF
229                   IF (useFixedCEast) THEN
230    C                Fixed phase speed (ignoring all of that painstakingly
231    C                saved data...)
232                     CVEL_WE(J,K,bi,bj) = CFIX
233                   ELSE
234                     CVEL_WE(J,K,bi,bj)=f1*(CL*dxC(I_obc-1,J,bi,bj)/deltaT)
235       &                   + f2*CVEL_WE(J,K,bi,bj)       &                   + f2*CVEL_WE(J,K,bi,bj)
236  C                 update OBC to next timestep                 ENDIF
237                    OBEw(J,K,bi,bj)=wVel(I_obc,J,K,bi,bj)-  C              update OBC to next timestep
238       &             CVEL_WE(J,K,bi,bj)*(deltaT/dxC(I_obc,J,bi,bj))*                 OBEw(J,K,bi,bj)=wVel(I_obc,J,K,bi,bj)-
239       &             (ab1*(wVel(I_obc,J,K,bi,bj)-wVel(I_obc-1,J,K,bi,bj))+       &           CVEL_WE(J,K,bi,bj)*(deltaT*recip_dxC(I_obc,J,bi,bj))*
240       &             ab2*(WE_STORE_4(J,K,bi,bj)-WE_STORE_1(J,K,bi,bj)))       &           (ab1*(wVel(I_obc,J,K,bi,bj)-wVel(I_obc-1,J,K,bi,bj))+
241  #endif       &           ab2*(WE_STORE_4(J,K,bi,bj)-WE_STORE_1(J,K,bi,bj)))
242                 ENDIF
243    #endif /* ALLOW_NONHYDROSTATIC */
244  C              update/save storage arrays  C              update/save storage arrays
245  C              uVel  C              uVel
246  C              copy t-1 to t-2 array  C              copy t-1 to t-2 array
# Line 230  C              copy (current time) t to Line 274  C              copy (current time) t to
274       &         salt(I_obc-2,J,K,bi,bj)       &         salt(I_obc-2,J,K,bi,bj)
275                 SE_STORE_1(J,K,bi,bj)=salt(I_obc-1,J,K,bi,bj)                 SE_STORE_1(J,K,bi,bj)=salt(I_obc-1,J,K,bi,bj)
276                 SE_STORE_4(J,K,bi,bj)=salt(I_obc,J,K,bi,bj)                 SE_STORE_4(J,K,bi,bj)=salt(I_obc,J,K,bi,bj)
 C              wVel  
277  #ifdef ALLOW_NONHYDROSTATIC  #ifdef ALLOW_NONHYDROSTATIC
278                 IF ( nonHydrostatic ) THEN
279    C              wVel
280  C              copy t-1 to t-2 array  C              copy t-1 to t-2 array
281                 WE_STORE_3(J,K,bi,bj)=WE_STORE_2(J,K,bi,bj)                 WE_STORE_3(J,K,bi,bj)=WE_STORE_2(J,K,bi,bj)
282  C              copy (current time) t to t-1 arrays  C              copy (current time) t to t-1 arrays
# Line 239  C              copy (current time) t to Line 284  C              copy (current time) t to
284       &         wVel(I_obc-2,J,K,bi,bj)       &         wVel(I_obc-2,J,K,bi,bj)
285                 WE_STORE_1(J,K,bi,bj)=wVel(I_obc-1,J,K,bi,bj)                 WE_STORE_1(J,K,bi,bj)=wVel(I_obc-1,J,K,bi,bj)
286                 WE_STORE_4(J,K,bi,bj)=wVel(I_obc,J,K,bi,bj)                 WE_STORE_4(J,K,bi,bj)=wVel(I_obc,J,K,bi,bj)
287  #endif               ENDIF
288    #endif /* ALLOW_NONHYDROSTATIC */
289              ENDIF              ENDIF
290           ENDDO           ENDDO
291        ENDDO        ENDDO
292    
293    #endif
294  #endif /* ALLOW_ORLANSKI */  #endif /* ALLOW_ORLANSKI */
295        RETURN        RETURN
296        END        END

Legend:
Removed from v.1.3.6.1  
changed lines
  Added in v.1.13

  ViewVC Help
Powered by ViewVC 1.1.22