/[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.3 - (hide annotations) (download)
Mon Feb 5 15:45:47 2001 UTC (23 years, 3 months ago) by adcroft
Branch: MAIN
CVS Tags: checkpoint36, checkpoint35
Changes since 1.2: +39 -25 lines
Split Orlanski parameters out of first namelist onto OBCS_PARM02.

1 adcroft 1.3 C $Header: /u/gcmpack/models/MITgcmUV/pkg/obcs/obcs_calc.F,v 1.2 2001/02/02 21:36:30 adcroft Exp $
2     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 adcroft 1.3 ENDIF
58 adcroft 1.2 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 adcroft 1.3 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 adcroft 1.2 #ifdef ALLOW_NONHYDROSTATIC
78 adcroft 1.3 OBWw(J,K,bi,bj)=0.
79 adcroft 1.2 #endif
80 adcroft 1.3 ENDIF
81 adcroft 1.2 ENDDO
82     ENDDO
83     ENDIF
84    
85 adcroft 1.3 C Northern OB
86 adcroft 1.2 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 adcroft 1.3 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 adcroft 1.2 #ifdef ALLOW_NONHYDROSTATIC
101 adcroft 1.3 OBNw(I,K,bi,bj)=0.
102 adcroft 1.2 #endif
103 adcroft 1.3 ENDIF
104 adcroft 1.2 ENDDO
105     ENDDO
106     ENDIF
107    
108 adcroft 1.3 C Southern OB
109     #ifdef ALLOW_ORLANSKI
110 adcroft 1.2 IF (useOrlanskiSouth) THEN
111     CALL ORLANSKI_SOUTH(
112     & bi, bj, futureTime,
113     & uVel, vVel, wVel, theta, salt,
114     & myThid )
115     ELSE
116 adcroft 1.3 #endif
117 adcroft 1.2 DO K=1,Nr
118     DO I=1-Olx,sNx+Olx
119 adcroft 1.3 J_obc=OB_Js(I,bi,bj)
120     IF (J_obc.ne.0) THEN
121     OBSu(I,K,bi,bj)=0.
122     OBSv(I,K,bi,bj)=0.
123     OBSt(I,K,bi,bj)=tRef(K)
124     OBSs(I,K,bi,bj)=sRef(K)
125 adcroft 1.2 #ifdef ALLOW_NONHYDROSTATIC
126 adcroft 1.3 OBSw(I,K,bi,bj)=0.
127 adcroft 1.2 #endif
128 adcroft 1.3 ENDIF
129 adcroft 1.2 ENDDO
130     ENDDO
131     ENDIF
132    
133     #endif /* ALLOW_OBCS */
134     RETURN
135     END

  ViewVC Help
Powered by ViewVC 1.1.22