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

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

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

revision 1.1 by adcroft, Tue Jan 30 21:03:00 2001 UTC revision 1.2 by adcroft, Fri Feb 2 21:36:30 2001 UTC
# Line 0  Line 1 
1    C $Header$
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
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                OBEu(J,K,bi,bj)=0.
49                OBEv(J,K,bi,bj)=0.
50                OBEt(J,K,bi,bj)=tRef(K)
51                OBEs(J,K,bi,bj)=sRef(K)
52    #ifdef ALLOW_NONHYDROSTATIC
53                OBEw(J,K,bi,bj)=0.
54    #endif
55              ENDDO
56            ENDDO
57          ENDIF
58    
59    C     Western OB
60          IF (useOrlanskiWest) THEN
61            CALL ORLANSKI_WEST(
62         &          bi, bj, futureTime,
63         &          uVel, vVel, wVel, theta, salt,
64         &          myThid )
65          ELSE
66            DO K=1,Nr
67              DO J=1-Oly,sNy+Oly
68                OBWu(J,K,bi,bj)=0.
69                OBWv(J,K,bi,bj)=0.
70                OBWt(J,K,bi,bj)=tRef(K)
71                OBWs(J,K,bi,bj)=sRef(K)
72    #ifdef ALLOW_NONHYDROSTATIC
73                OBWw(J,K,bi,bj)=0.
74    #endif
75              ENDDO
76            ENDDO
77          ENDIF
78    
79    C         Northern OB, template for forcing
80          IF (useOrlanskiNorth) THEN
81            CALL ORLANSKI_NORTH(
82         &          bi, bj, futureTime,
83         &          uVel, vVel, wVel, theta, salt,
84         &          myThid )
85          ELSE
86            DO K=1,Nr
87              DO I=1-Olx,sNx+Olx
88                OBNv(I,K,bi,bj)=0.
89                OBNu(I,K,bi,bj)=0.
90                OBNt(I,K,bi,bj)=tRef(K)
91                OBNs(I,K,bi,bj)=sRef(K)
92    #ifdef ALLOW_NONHYDROSTATIC
93                OBNw(I,K,bi,bj)=0.
94    #endif
95              ENDDO
96            ENDDO
97          ENDIF
98    
99    C         Southern OB, template for forcing
100          IF (useOrlanskiSouth) THEN  
101            CALL ORLANSKI_SOUTH(
102         &          bi, bj, futureTime,
103         &          uVel, vVel, wVel, theta, salt,
104         &          myThid )
105          ELSE
106            DO K=1,Nr
107              DO I=1-Olx,sNx+Olx
108                OBSu(I,K,bi,bj)=0.
109                OBSv(I,K,bi,bj)=0.
110                OBSt(I,K,bi,bj)=tRef(K)
111                OBSs(I,K,bi,bj)=sRef(K)
112    #ifdef ALLOW_NONHYDROSTATIC
113                OBSw(I,K,bi,bj)=0.
114    #endif
115              ENDDO
116            ENDDO
117          ENDIF
118    
119    #endif /* ALLOW_OBCS */
120          RETURN
121          END

Legend:
Removed from v.1.1  
changed lines
  Added in v.1.2

  ViewVC Help
Powered by ViewVC 1.1.22