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

Diff of /MITgcm/verification/internal_wave/code/obcs_calc.F

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

revision 1.1 by adcroft, Wed Jan 31 23:31:52 2001 UTC revision 1.1.2.1 by adcroft, Wed Jan 31 23:31:52 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    #include "GRID.h"
40          _RL obTimeScale,Uinflow,rampTime2
41          _RL vertStructWst(Nr)
42          _RL mz,strat,kx
43          _RL tmpsum
44    
45    C Vertical mode number
46          mz=1.0
47    C Stratification
48          strat = 1.0 _d -6 / (gravity*tAlpha)
49    
50    C Create a vertical structure function with zero mean
51          tmpsum=0.
52          do K=1,Nr
53           vertStructWst(K)=cos(mz*PI* (rC(K)/rF(Nr+1)) )
54           tmpsum=tmpsum+vertStructWst(K)*drF(K)
55          enddo
56          tmpsum=tmpsum/rF(Nr+1)
57          do K=1,Nr
58           vertStructWst(K)=vertStructWst(K)-tmpsum
59          enddo
60    c
61          obTimeScale = 44567.0
62           kx=mz*2.*pi/400.0*sqrt((2.0*pi*2.0*pi/(obTimeScale*obTimeScale)
63         & - f0*f0)/(1.0 _d -6
64         & - 2.0*pi*2.0*pi/(obTimeScale*obTimeScale)))
65          Uinflow = 0.024
66          rampTime2 = 4*44567.0
67    
68    
69    C     Eastern OB
70          IF (useOrlanskiEast) THEN
71            CALL ORLANSKI_EAST(
72         &          bi, bj, futureTime,
73         &          uVel, vVel, wVel, theta, salt,
74         &          myThid )
75          ELSE
76            DO K=1,Nr
77              DO J=1-Oly,sNy+Oly
78                OBEu(J,K,bi,bj)=0.
79                OBEv(J,K,bi,bj)=0.
80                OBEt(J,K,bi,bj)=tRef(K)
81                OBEs(J,K,bi,bj)=sRef(K)
82    #ifdef ALLOW_NONHYDROSTATIC
83                OBEw(J,K,bi,bj)=0.
84    #endif
85              ENDDO
86            ENDDO
87          ENDIF
88    
89    C     Western OB
90          IF (useOrlanskiWest) THEN
91            CALL ORLANSKI_WEST(
92         &          bi, bj, futureTime,
93         &          uVel, vVel, wVel, theta, salt,
94         &          myThid )
95          ELSE
96            DO K=1,Nr
97              DO J=1-Oly,sNy+Oly
98              OBWu(J,K,bi,bj)=0.
99         &       +Uinflow
100         &       *vertStructWst(K)
101         &       *sin(2.*PI*futureTime/obTimeScale)
102         &       *(exp(futureTime/rampTime2)
103         &   - exp(-futureTime/rampTime2))
104         &   /(exp(futureTime/rampTime2)
105         &  + exp(-futureTime/rampTime2))
106         &   *cos(kx*(3-2-0.5)*delX(1))
107              OBWv(J,K,bi,bj)=0.
108         &       +Uinflow
109         &       *f0/(2.0*PI/obTimeScale)
110         &       *vertStructWst(K)
111         &       *cos(2.*PI*futureTime/obTimeScale )
112         & * (exp(futureTime/rampTime2)
113         &   - exp(-futureTime/rampTime2))
114         &   /(exp(futureTime/rampTime2)
115         &  + exp(-futureTime/rampTime2))
116              OBWt(J,K,bi,bj)=tRef(K)
117         & + Uinflow*sin(mz*PI*(float(k)-0.5)/float(Nr))
118         & * sin(2.0*PI*futureTime/obTimeScale)
119         & *sqrt(strat/(tAlpha*gravity))
120         & *sqrt(2.0*PI/obTimeScale*2.0*PI/obTimeScale - f0*f0)
121         & /(2.0*PI/obTimeScale)
122         & * (exp(futureTime/rampTime2)
123         &   - exp(-futureTime/rampTime2))
124         &   /(exp(futureTime/rampTime2)
125         &  + exp(-futureTime/rampTime2))
126    #ifdef ALLOW_NONHYDROSTATIC
127              OBWw(J,K,bi,bj)=-Uinflow
128         & *sqrt(2.0*PI/obTimeScale*2.0*PI/obTimeScale - f0*f0)
129         & /sqrt(strat*strat - 2.0*PI/obTimeScale*2.0*PI/obTimeScale)
130         & *sin(mz*PI*(float(k)-0.5)/float(Nr))
131         &       *cos(2.*PI*futureTime/obTimeScale)
132         &       *(exp(futureTime/rampTime2)
133         &   - exp(-futureTime/rampTime2))
134         &   /(exp(futureTime/rampTime2)
135         &  + exp(-futureTime/rampTime2))
136    #endif
137              ENDDO
138            ENDDO
139          ENDIF
140    
141    C         Northern OB, template for forcing
142          IF (useOrlanskiNorth) THEN
143            CALL ORLANSKI_NORTH(
144         &          bi, bj, futureTime,
145         &          uVel, vVel, wVel, theta, salt,
146         &          myThid )
147          ELSE
148            DO K=1,Nr
149              DO I=1-Olx,sNx+Olx
150                OBNv(I,K,bi,bj)=0.
151                OBNu(I,K,bi,bj)=0.
152                OBNt(I,K,bi,bj)=tRef(K)
153                OBNs(I,K,bi,bj)=sRef(K)
154    #ifdef ALLOW_NONHYDROSTATIC
155                OBNw(I,K,bi,bj)=0.
156    #endif
157              ENDDO
158            ENDDO
159          ENDIF
160    
161    C         Southern OB, template for forcing
162          IF (useOrlanskiSouth) THEN  
163            CALL ORLANSKI_SOUTH(
164         &          bi, bj, futureTime,
165         &          uVel, vVel, wVel, theta, salt,
166         &          myThid )
167          ELSE
168            DO K=1,Nr
169              DO I=1-Olx,sNx+Olx
170                OBSu(I,K,bi,bj)=0.
171                OBSv(I,K,bi,bj)=0.
172                OBSt(I,K,bi,bj)=tRef(K)
173                OBSs(I,K,bi,bj)=sRef(K)
174    #ifdef ALLOW_NONHYDROSTATIC
175                OBSw(I,K,bi,bj)=0.
176    #endif
177              ENDDO
178            ENDDO
179          ENDIF
180    
181    #endif /* ALLOW_OBCS */
182          RETURN
183          END

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

  ViewVC Help
Powered by ViewVC 1.1.22