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

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

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


Revision 1.8 - (hide annotations) (download)
Tue May 24 20:34:01 2011 UTC (12 years, 11 months ago) by jmc
Branch: MAIN
CVS Tags: checkpoint62z, checkpoint62y, checkpoint63, checkpoint63d, checkpoint63e, checkpoint63f, checkpoint63a, checkpoint63b, checkpoint63c
Changes since 1.7: +4 -2 lines
updated after splitting "OBCS.h" into 4 separated header files.

1 jmc 1.8 C $Header: /u/gcmpack/MITgcm/verification/internal_wave/code/obcs_calc.F,v 1.7 2011/02/28 16:31:36 jmc Exp $
2 adcroft 1.3 C $Name: $
3 adcroft 1.2
4     #include "OBCS_OPTIONS.h"
5    
6 jahn 1.6 SUBROUTINE OBCS_CALC( futureTime, futureIter,
7 jmc 1.7 & uVel, vVel, wVel, theta, salt,
8 adcroft 1.2 & myThid )
9 jmc 1.7 C *==========================================================*
10     C | SUBROUTINE OBCS_CALC
11     C | o Calculate future boundary data at open boundaries
12     C | at time = futureTime
13     C *==========================================================*
14 adcroft 1.2 IMPLICIT NONE
15    
16     C === Global variables ===
17     #include "SIZE.h"
18     #include "EEPARAMS.h"
19     #include "PARAMS.h"
20 jmc 1.7 #include "GRID.h"
21 jmc 1.8 #include "OBCS_PARAMS.h"
22     #include "OBCS_GRID.h"
23     #include "OBCS_FIELDS.h"
24 mlosch 1.5 #include "EOS.h"
25 adcroft 1.2
26     C == Routine arguments ==
27 jmc 1.4 INTEGER futureIter
28 adcroft 1.2 _RL futureTime
29     _RL uVel (1-OLx:sNx+OLx,1-OLy:sNy+OLy,Nr,nSx,nSy)
30     _RL vVel (1-OLx:sNx+OLx,1-OLy:sNy+OLy,Nr,nSx,nSy)
31     _RL wVel (1-OLx:sNx+OLx,1-OLy:sNy+OLy,Nr,nSx,nSy)
32     _RL theta(1-OLx:sNx+OLx,1-OLy:sNy+OLy,Nr,nSx,nSy)
33     _RL salt (1-OLx:sNx+OLx,1-OLy:sNy+OLy,Nr,nSx,nSy)
34     INTEGER myThid
35    
36     #ifdef ALLOW_OBCS
37    
38     C == Local variables ==
39 jahn 1.6 INTEGER bi, bj
40 adcroft 1.2 INTEGER I, J ,K
41     _RL obTimeScale,Uinflow,rampTime2
42     _RL vertStructWst(Nr)
43     _RL mz,strat,kx
44     _RL tmpsum
45    
46 jmc 1.7 C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
47    
48     #ifdef ALLOW_DEBUG
49     IF (debugMode) CALL DEBUG_ENTER('OBCS_CALC',myThid)
50     #endif
51    
52 adcroft 1.2 C Vertical mode number
53 adcroft 1.3 mz=1.0 _d 0
54 adcroft 1.2 C Stratification
55     strat = 1.0 _d -6 / (gravity*tAlpha)
56    
57     C Create a vertical structure function with zero mean
58     tmpsum=0.
59     do K=1,Nr
60     vertStructWst(K)=cos(mz*PI* (rC(K)/rF(Nr+1)) )
61     tmpsum=tmpsum+vertStructWst(K)*drF(K)
62     enddo
63     tmpsum=tmpsum/rF(Nr+1)
64     do K=1,Nr
65     vertStructWst(K)=vertStructWst(K)-tmpsum
66     enddo
67     c
68 adcroft 1.3 obTimeScale = 44567.0 _d 0
69     kx=mz*2. _d 0*pi/400.0 _d 0
70     & *sqrt((2.0 _d 0*pi*2.0 _d 0*pi/(obTimeScale*obTimeScale)
71 adcroft 1.2 & - f0*f0)/(1.0 _d -6
72 adcroft 1.3 & - 2.0 _d 0*pi*2.0 _d 0*pi/(obTimeScale*obTimeScale)))
73     Uinflow = 0.024 _d 0
74     C *NOTE* I have commented out the ramp function below
75     C just to speed things up. You will probably want to use it
76     C for smoother looking solutions.
77     rampTime2 = 4. _d 0*44567.0 _d 0
78 adcroft 1.2
79 jahn 1.6 DO bj=myByLo(myThid),myByHi(myThid)
80     DO bi=myBxLo(myThid),myBxHi(myThid)
81 adcroft 1.2
82     C Eastern OB
83     IF (useOrlanskiEast) THEN
84     CALL ORLANSKI_EAST(
85 jmc 1.7 & bi, bj, futureTime,
86     & uVel, vVel, wVel, theta, salt,
87 adcroft 1.2 & myThid )
88     ELSE
89     DO K=1,Nr
90     DO J=1-Oly,sNy+Oly
91     OBEu(J,K,bi,bj)=0.
92     OBEv(J,K,bi,bj)=0.
93     OBEt(J,K,bi,bj)=tRef(K)
94     OBEs(J,K,bi,bj)=sRef(K)
95     #ifdef ALLOW_NONHYDROSTATIC
96     OBEw(J,K,bi,bj)=0.
97     #endif
98     ENDDO
99     ENDDO
100     ENDIF
101    
102     C Western OB
103     IF (useOrlanskiWest) THEN
104     CALL ORLANSKI_WEST(
105 jmc 1.7 & bi, bj, futureTime,
106     & uVel, vVel, wVel, theta, salt,
107 adcroft 1.2 & myThid )
108     ELSE
109     DO K=1,Nr
110     DO J=1-Oly,sNy+Oly
111 adcroft 1.3 OBWu(J,K,bi,bj)=0. _d 0
112 adcroft 1.2 & +Uinflow
113     & *vertStructWst(K)
114 adcroft 1.3 & *sin(2. _d 0*PI*futureTime/obTimeScale)
115     c & *(exp(futureTime/rampTime2)
116     c & - exp(-futureTime/rampTime2))
117     c & /(exp(futureTime/rampTime2)
118     c & + exp(-futureTime/rampTime2))
119     & *cos(kx*(3. _d 0-2. _d 0-0.5 _d 0)*delX(1))
120     OBWv(J,K,bi,bj)=0. _d 0
121 adcroft 1.2 & +Uinflow
122 adcroft 1.3 & *f0/(2.0 _d 0*PI/obTimeScale)
123 adcroft 1.2 & *vertStructWst(K)
124 adcroft 1.3 & *cos(2. _d 0*PI*futureTime/obTimeScale )
125 adcroft 1.2 & * (exp(futureTime/rampTime2)
126     & - exp(-futureTime/rampTime2))
127     & /(exp(futureTime/rampTime2)
128     & + exp(-futureTime/rampTime2))
129     OBWt(J,K,bi,bj)=tRef(K)
130 adcroft 1.3 & + Uinflow*sin(mz*PI*(float(k)-0.5 _d 0)/float(Nr))
131     & * sin(2.0 _d 0*PI*futureTime/obTimeScale)
132 adcroft 1.2 & *sqrt(strat/(tAlpha*gravity))
133 adcroft 1.3 & *sqrt(2.0 _d 0*PI/obTimeScale*2.0*PI/obTimeScale - f0*f0)
134     & /(2.0 _d 0*PI/obTimeScale)
135     c & * (exp(futureTime/rampTime2)
136     c & - exp(-futureTime/rampTime2))
137     c & /(exp(futureTime/rampTime2)
138     c & + exp(-futureTime/rampTime2))
139 adcroft 1.2 #ifdef ALLOW_NONHYDROSTATIC
140     OBWw(J,K,bi,bj)=-Uinflow
141 adcroft 1.3 & *sqrt(2.0 _d 0*PI/obTimeScale*2.0 _d 0*PI/obTimeScale - f0*f0)
142     & /sqrt(strat*strat -
143     & 2.0 _d 0*PI/obTimeScale*2.0 _d 0*PI/obTimeScale)
144     & *sin(mz*PI*(float(k)-0.5 _d 0)/float(Nr))
145     & *cos(2. _d 0*PI*futureTime/obTimeScale)
146     c & *(exp(futureTime/rampTime2)
147     c & - exp(-futureTime/rampTime2))
148     c & /(exp(futureTime/rampTime2)
149     c & + exp(-futureTime/rampTime2))
150 adcroft 1.2 #endif
151     ENDDO
152     ENDDO
153     ENDIF
154    
155     C Northern OB, template for forcing
156     IF (useOrlanskiNorth) THEN
157     CALL ORLANSKI_NORTH(
158 jmc 1.7 & bi, bj, futureTime,
159     & uVel, vVel, wVel, theta, salt,
160 adcroft 1.2 & myThid )
161     ELSE
162     DO K=1,Nr
163     DO I=1-Olx,sNx+Olx
164     OBNv(I,K,bi,bj)=0.
165     OBNu(I,K,bi,bj)=0.
166     OBNt(I,K,bi,bj)=tRef(K)
167     OBNs(I,K,bi,bj)=sRef(K)
168     #ifdef ALLOW_NONHYDROSTATIC
169     OBNw(I,K,bi,bj)=0.
170     #endif
171     ENDDO
172     ENDDO
173     ENDIF
174    
175     C Southern OB, template for forcing
176 jmc 1.7 IF (useOrlanskiSouth) THEN
177 adcroft 1.2 CALL ORLANSKI_SOUTH(
178 jmc 1.7 & bi, bj, futureTime,
179     & uVel, vVel, wVel, theta, salt,
180 adcroft 1.2 & myThid )
181     ELSE
182     DO K=1,Nr
183     DO I=1-Olx,sNx+Olx
184     OBSu(I,K,bi,bj)=0.
185     OBSv(I,K,bi,bj)=0.
186     OBSt(I,K,bi,bj)=tRef(K)
187     OBSs(I,K,bi,bj)=sRef(K)
188     #ifdef ALLOW_NONHYDROSTATIC
189     OBSw(I,K,bi,bj)=0.
190     #endif
191     ENDDO
192     ENDDO
193     ENDIF
194    
195 jahn 1.6 C-- end bi,bj loops.
196     ENDDO
197 jmc 1.7 ENDDO
198    
199     #ifdef ALLOW_OBCS_BALANCE
200     IF ( useOBCSbalance ) THEN
201     CALL OBCS_BALANCE_FLOW( futureTime, futureIter, myThid )
202     ENDIF
203     #endif /* ALLOW_OBCS_BALANCE */
204 jahn 1.6
205 jmc 1.7 #ifdef ALLOW_DEBUG
206     IF (debugMode) CALL DEBUG_LEAVE('OBCS_CALC',myThid)
207     #endif
208 adcroft 1.2 #endif /* ALLOW_OBCS */
209 jmc 1.7
210 adcroft 1.2 RETURN
211     END

  ViewVC Help
Powered by ViewVC 1.1.22