/[MITgcm]/MITgcm/verification/exp4/code/obcs_calc.F
ViewVC logotype

Annotation of /MITgcm/verification/exp4/code/obcs_calc.F

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


Revision 1.3 - (hide annotations) (download)
Wed Mar 27 23:17:39 2002 UTC (22 years, 3 months ago) by jmc
Branch: MAIN
Changes since 1.2: +16 -2 lines
 allow to test OBCS with NLFS

1 jmc 1.3 C $Header: /u/gcmpack/MITgcm/verification/exp4/code/obcs_calc.F,v 1.2 2001/02/02 21:36:33 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     INTEGER I, J ,K
38     _RL recip_TimeScale,Uinflow
39 jmc 1.3 _RL EtaBC
40 adcroft 1.2 c
41     recip_TimeScale=0./2000.
42     Uinflow = 0.25
43 jmc 1.3 EtaBC = 0.
44 adcroft 1.2
45     C Eastern OB
46     IF (useOrlanskiEast) THEN
47     #ifdef ALLOW_ORLANSKI
48     CALL ORLANSKI_EAST(
49     & bi, bj, futureTime,
50     & uVel, vVel, wVel, theta, salt,
51     & myThid )
52     #endif
53     ELSE
54     DO K=1,Nr
55     DO J=1-Oly,sNy+Oly
56     OBEu(J,K,bi,bj)=Uinflow
57     & *cos(2.*PI*futureTime*recip_TimeScale)
58     & *max(futureTime*recip_TimeScale,1.)
59     OBEv(J,K,bi,bj)=0.
60     OBEt(J,K,bi,bj)=tRef(K)
61     OBEs(J,K,bi,bj)=sRef(K)
62     #ifdef ALLOW_NONHYDROSTATIC
63     OBEw(J,K,bi,bj)=0.
64     #endif
65 jmc 1.3 #ifdef NONLIN_FRSURF
66     OBEeta(J,bi,bj)=EtaBC
67     #endif
68 adcroft 1.2 ENDDO
69     ENDDO
70     ENDIF
71    
72     C Western OB
73     IF (useOrlanskiWest) THEN
74     #ifdef ALLOW_ORLANSKI
75     CALL ORLANSKI_WEST(
76     & bi, bj, futureTime,
77     & uVel, vVel, wVel, theta, salt,
78     & myThid )
79     #endif
80     ELSE
81     DO K=1,Nr
82     DO J=1-Oly,sNy+Oly
83     OBWu(J,K,bi,bj)=Uinflow
84     & *cos(2.*PI*futureTime*recip_TimeScale)
85     & *max(futureTime*recip_TimeScale,1.)
86     OBWv(J,K,bi,bj)=0.
87     OBWt(J,K,bi,bj)=tRef(K)
88     OBWs(J,K,bi,bj)=sRef(K)
89     #ifdef ALLOW_NONHYDROSTATIC
90     OBWw(J,K,bi,bj)=0.
91     #endif
92 jmc 1.3 #ifdef NONLIN_FRSURF
93     OBWeta(J,bi,bj)=EtaBC
94     #endif
95 adcroft 1.2 ENDDO
96     ENDDO
97     ENDIF
98    
99     C Northern OB, template for forcing
100     IF (useOrlanskiNorth) THEN
101     #ifdef ALLOW_ORLANSKI
102     CALL ORLANSKI_NORTH(
103     & bi, bj, futureTime,
104     & uVel, vVel, wVel, theta, salt,
105     & myThid )
106     #endif
107     ELSE
108     DO K=1,Nr
109     DO I=1-Olx,sNx+Olx
110     OBNu(I,K,bi,bj)=Uinflow
111     & *cos(2.*PI*futureTime*recip_TimeScale)
112     & *max(futureTime*recip_TimeScale,1.)
113     OBNv(I,K,bi,bj)=0.
114     OBNt(I,K,bi,bj)=tRef(K)
115     OBNs(I,K,bi,bj)=sRef(K)
116     #ifdef ALLOW_NONHYDROSTATIC
117     OBNw(I,K,bi,bj)=0.
118     #endif
119 jmc 1.3 #ifdef NONLIN_FRSURF
120     OBNeta(I,bi,bj)=0.
121     #endif
122 adcroft 1.2 ENDDO
123     ENDDO
124     ENDIF
125    
126     C Southern OB, template for forcing
127     IF (useOrlanskiSouth) THEN
128     #ifdef ALLOW_ORLANSKI
129     CALL ORLANSKI_SOUTH(
130     & bi, bj, futureTime,
131     & uVel, vVel, wVel, theta, salt,
132     & myThid )
133     #endif
134     ELSE
135     DO K=1,Nr
136     DO I=1-Olx,sNx+Olx
137     OBSu(I,K,bi,bj)=Uinflow
138     & *cos(2.*PI*futureTime*recip_TimeScale)
139     & *max(futureTime*recip_TimeScale,1.)
140     OBSv(I,K,bi,bj)=0.
141     OBSt(I,K,bi,bj)=tRef(K)
142     OBSs(I,K,bi,bj)=sRef(K)
143     #ifdef ALLOW_NONHYDROSTATIC
144     OBSw(I,K,bi,bj)=0.
145 jmc 1.3 #endif
146     #ifdef NONLIN_FRSURF
147     OBSeta(I,bi,bj)=0.
148 adcroft 1.2 #endif
149     ENDDO
150     ENDDO
151     ENDIF
152    
153     #endif /* ALLOW_OBCS */
154     RETURN
155     END

  ViewVC Help
Powered by ViewVC 1.1.22