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

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

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


Revision 1.4 - (show annotations) (download)
Wed Feb 28 14:48:25 2001 UTC (23 years, 2 months ago) by adcroft
Branch: MAIN
CVS Tags: checkpoint43a-release1mods, checkpoint40pre3, checkpoint40pre1, checkpoint40pre7, checkpoint40pre6, checkpoint40pre9, checkpoint40pre8, release1_b1, checkpoint43, checkpoint38, checkpoint40pre2, release1-branch_tutorials, checkpoint40pre4, pre38tag1, release1-branch-end, c37_adj, pre38-close, checkpoint39, checkpoint37, checkpoint40pre5, release1_beta1, checkpoint42, checkpoint40, checkpoint41, checkpoint44, release1-branch_branchpoint
Branch point for: release1-branch, release1, ecco-branch, pre38, release1_coupled
Changes since 1.3: +1 -3 lines
Removed superfluous #ifdef (spk).

1 C $Header: /u/u0/gcmpack/models/MITgcmUV/pkg/obcs/obcs_calc.F,v 1.3 2001/02/05 15:45:47 adcroft Exp $
2 C $Name: $
3
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 INTEGER I, J , K, I_obc, J_obc
38
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 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 #ifdef ALLOW_NONHYDROSTATIC
55 OBEw(J,K,bi,bj)=0.
56 #endif
57 ENDIF
58 ENDDO
59 ENDDO
60 ENDIF
61
62 C Western OB
63 IF (useOrlanskiWest) THEN
64 CALL ORLANSKI_WEST(
65 & bi, bj, futureTime,
66 & uVel, vVel, wVel, theta, salt,
67 & myThid )
68 ELSE
69 DO K=1,Nr
70 DO J=1-Oly,sNy+Oly
71 I_obc=OB_Iw(J,bi,bj)
72 IF (I_obc.ne.0) THEN
73 OBWu(J,K,bi,bj)=0.
74 OBWv(J,K,bi,bj)=0.
75 OBWt(J,K,bi,bj)=tRef(K)
76 OBWs(J,K,bi,bj)=sRef(K)
77 #ifdef ALLOW_NONHYDROSTATIC
78 OBWw(J,K,bi,bj)=0.
79 #endif
80 ENDIF
81 ENDDO
82 ENDDO
83 ENDIF
84
85 C Northern OB
86 IF (useOrlanskiNorth) THEN
87 CALL ORLANSKI_NORTH(
88 & bi, bj, futureTime,
89 & uVel, vVel, wVel, theta, salt,
90 & myThid )
91 ELSE
92 DO K=1,Nr
93 DO I=1-Olx,sNx+Olx
94 J_obc=OB_Jn(I,bi,bj)
95 IF (J_obc.ne.0) THEN
96 OBNv(I,K,bi,bj)=0.
97 OBNu(I,K,bi,bj)=0.
98 OBNt(I,K,bi,bj)=tRef(K)
99 OBNs(I,K,bi,bj)=sRef(K)
100 #ifdef ALLOW_NONHYDROSTATIC
101 OBNw(I,K,bi,bj)=0.
102 #endif
103 ENDIF
104 ENDDO
105 ENDDO
106 ENDIF
107
108 C Southern OB
109 IF (useOrlanskiSouth) THEN
110 CALL ORLANSKI_SOUTH(
111 & bi, bj, futureTime,
112 & uVel, vVel, wVel, theta, salt,
113 & myThid )
114 ELSE
115 DO K=1,Nr
116 DO I=1-Olx,sNx+Olx
117 J_obc=OB_Js(I,bi,bj)
118 IF (J_obc.ne.0) THEN
119 OBSu(I,K,bi,bj)=0.
120 OBSv(I,K,bi,bj)=0.
121 OBSt(I,K,bi,bj)=tRef(K)
122 OBSs(I,K,bi,bj)=sRef(K)
123 #ifdef ALLOW_NONHYDROSTATIC
124 OBSw(I,K,bi,bj)=0.
125 #endif
126 ENDIF
127 ENDDO
128 ENDDO
129 ENDIF
130
131 #endif /* ALLOW_OBCS */
132 RETURN
133 END

  ViewVC Help
Powered by ViewVC 1.1.22