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

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

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


Revision 1.5 - (hide annotations) (download)
Wed Jan 30 04:22:31 2002 UTC (22 years, 3 months ago) by jmc
Branch: MAIN
CVS Tags: chkpt44a_post, chkpt44c_pre, checkpoint44b_post, chkpt44a_pre, checkpoint44b_pre
Changes since 1.4: +13 -1 lines
NonLin_FreeSurf implemented with OBC (but not yet radiative OBC).

1 jmc 1.5 C $Header: /u/gcmpack/models/MITgcmUV/pkg/obcs/obcs_calc.F,v 1.4 2001/02/28 14:48:25 adcroft Exp $
2 adcroft 1.3 C $Name: $
3 adcroft 1.2
4     #include "OBCS_OPTIONS.h"
5    
6     SUBROUTINE OBCS_CALC( bi, bj, futureTime,
7     & uVel, vVel, wVel, theta, salt,
8     & myThid )
9     C /==========================================================\
10     C | SUBROUTINE OBCS_CALC |
11     C | o Calculate future boundary data at open boundaries |
12     C | at time = futureTime |
13     C |==========================================================|
14     C | |
15     C \==========================================================/
16     IMPLICIT NONE
17    
18     C === Global variables ===
19     #include "SIZE.h"
20     #include "EEPARAMS.h"
21     #include "PARAMS.h"
22     #include "OBCS.h"
23    
24     C == Routine arguments ==
25     INTEGER bi, bj
26     _RL futureTime
27     _RL uVel (1-OLx:sNx+OLx,1-OLy:sNy+OLy,Nr,nSx,nSy)
28     _RL vVel (1-OLx:sNx+OLx,1-OLy:sNy+OLy,Nr,nSx,nSy)
29     _RL wVel (1-OLx:sNx+OLx,1-OLy:sNy+OLy,Nr,nSx,nSy)
30     _RL theta(1-OLx:sNx+OLx,1-OLy:sNy+OLy,Nr,nSx,nSy)
31     _RL salt (1-OLx:sNx+OLx,1-OLy:sNy+OLy,Nr,nSx,nSy)
32     INTEGER myThid
33    
34     #ifdef ALLOW_OBCS
35    
36     C == Local variables ==
37 adcroft 1.3 INTEGER I, J , K, I_obc, J_obc
38 adcroft 1.2
39     C Eastern OB
40     IF (useOrlanskiEast) THEN
41     CALL ORLANSKI_EAST(
42     & bi, bj, futureTime,
43     & uVel, vVel, wVel, theta, salt,
44     & myThid )
45     ELSE
46     DO K=1,Nr
47     DO J=1-Oly,sNy+Oly
48 adcroft 1.3 I_obc=OB_Ie(J,bi,bj)
49     IF (I_obc.ne.0) THEN
50     OBEu(J,K,bi,bj)=0.
51     OBEv(J,K,bi,bj)=0.
52     OBEt(J,K,bi,bj)=tRef(K)
53     OBEs(J,K,bi,bj)=sRef(K)
54 adcroft 1.2 #ifdef ALLOW_NONHYDROSTATIC
55 adcroft 1.3 OBEw(J,K,bi,bj)=0.
56 adcroft 1.2 #endif
57 jmc 1.5 #ifdef NONLIN_FRSURF
58     OBEeta(J,bi,bj)=0.
59     #endif
60 adcroft 1.3 ENDIF
61 adcroft 1.2 ENDDO
62     ENDDO
63     ENDIF
64    
65     C Western OB
66     IF (useOrlanskiWest) THEN
67     CALL ORLANSKI_WEST(
68     & bi, bj, futureTime,
69     & uVel, vVel, wVel, theta, salt,
70     & myThid )
71     ELSE
72     DO K=1,Nr
73     DO J=1-Oly,sNy+Oly
74 adcroft 1.3 I_obc=OB_Iw(J,bi,bj)
75     IF (I_obc.ne.0) THEN
76     OBWu(J,K,bi,bj)=0.
77     OBWv(J,K,bi,bj)=0.
78     OBWt(J,K,bi,bj)=tRef(K)
79     OBWs(J,K,bi,bj)=sRef(K)
80 adcroft 1.2 #ifdef ALLOW_NONHYDROSTATIC
81 adcroft 1.3 OBWw(J,K,bi,bj)=0.
82 adcroft 1.2 #endif
83 jmc 1.5 #ifdef NONLIN_FRSURF
84     OBWeta(J,bi,bj)=0.
85     #endif
86 adcroft 1.3 ENDIF
87 adcroft 1.2 ENDDO
88     ENDDO
89     ENDIF
90    
91 adcroft 1.3 C Northern OB
92 adcroft 1.2 IF (useOrlanskiNorth) THEN
93     CALL ORLANSKI_NORTH(
94     & bi, bj, futureTime,
95     & uVel, vVel, wVel, theta, salt,
96     & myThid )
97     ELSE
98     DO K=1,Nr
99     DO I=1-Olx,sNx+Olx
100 adcroft 1.3 J_obc=OB_Jn(I,bi,bj)
101     IF (J_obc.ne.0) THEN
102     OBNv(I,K,bi,bj)=0.
103     OBNu(I,K,bi,bj)=0.
104     OBNt(I,K,bi,bj)=tRef(K)
105     OBNs(I,K,bi,bj)=sRef(K)
106 adcroft 1.2 #ifdef ALLOW_NONHYDROSTATIC
107 adcroft 1.3 OBNw(I,K,bi,bj)=0.
108 adcroft 1.2 #endif
109 jmc 1.5 #ifdef NONLIN_FRSURF
110     OBNeta(I,bi,bj)=0.
111     #endif
112 adcroft 1.3 ENDIF
113 adcroft 1.2 ENDDO
114     ENDDO
115     ENDIF
116    
117 adcroft 1.3 C Southern OB
118 adcroft 1.2 IF (useOrlanskiSouth) THEN
119     CALL ORLANSKI_SOUTH(
120     & bi, bj, futureTime,
121     & uVel, vVel, wVel, theta, salt,
122     & myThid )
123     ELSE
124     DO K=1,Nr
125     DO I=1-Olx,sNx+Olx
126 adcroft 1.3 J_obc=OB_Js(I,bi,bj)
127     IF (J_obc.ne.0) THEN
128     OBSu(I,K,bi,bj)=0.
129     OBSv(I,K,bi,bj)=0.
130     OBSt(I,K,bi,bj)=tRef(K)
131     OBSs(I,K,bi,bj)=sRef(K)
132 adcroft 1.2 #ifdef ALLOW_NONHYDROSTATIC
133 adcroft 1.3 OBSw(I,K,bi,bj)=0.
134 jmc 1.5 #endif
135     #ifdef NONLIN_FRSURF
136     OBSeta(I,bi,bj)=0.
137 adcroft 1.2 #endif
138 adcroft 1.3 ENDIF
139 adcroft 1.2 ENDDO
140     ENDDO
141     ENDIF
142    
143     #endif /* ALLOW_OBCS */
144     RETURN
145     END

  ViewVC Help
Powered by ViewVC 1.1.22