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

Contents of /MITgcm/verification/internal_wave/code/set_obcs.F

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


Revision 1.1 - (show annotations) (download)
Thu Jun 29 19:29:04 2000 UTC (24 years, 3 months ago) by adcroft
Branch: MAIN
CVS Tags: checkpoint33, branch-atmos-merge-phase5, branch-atmos-merge-phase4, branch-atmos-merge-phase7, branch-atmos-merge-phase6, branch-atmos-merge-phase1, branch-atmos-merge-phase3, checkpoint34, branch-atmos-merge-zonalfilt, branch-atmos-merge-shapiro, checkpoint30, checkpoint32, branch-atmos-merge-start, branch-atmos-merge-phase2, checkpoint31
Branch point for: branch-atmos-merge
Added new example for testing OBCs.

1 C $Header: $
2
3 #include "CPP_OPTIONS.h"
4
5 SUBROUTINE SET_OBCS( K, bi, bj, myCurrentTime, myThid )
6 C /==========================================================\
7 C | SUBROUTINE SET_OBCS |
8 C | o Set boundary conditions at open boundaries |
9 C |==========================================================|
10 C | |
11 C | Specific OBCs for internal wave problem. |
12 C | slegg@whoi.edu |
13 C | |
14 C \==========================================================/
15 IMPLICIT NONE
16
17 C === Global variables ===
18 #include "SIZE.h"
19 #include "EEPARAMS.h"
20 #include "PARAMS.h"
21 #include "DYNVARS.h"
22 #include "GRID.h"
23 #include "OBCS.h"
24
25 C == Routine arguments ==
26 C myThid - Number of this instance of INI_DEPTHS
27 INTEGER K, bi, bj
28 _RL myCurrentTime
29 INTEGER myThid
30
31 #ifdef ALLOW_OBCS
32
33 C == Local variables ==
34 C xG, yG - Global coordinate location.
35 C zG
36 C zUpper - Work arrays for upper and lower
37 C zLower cell-face heights.
38 C phi - Temporary scalar
39 C iG, jG - Global coordinate index
40 C bi,bj - Loop counters
41 C zUpper - Temporary arrays holding z coordinates of
42 C zLower upper and lower faces.
43 C I,i,K
44 INTEGER iG, jG
45 INTEGER I, J
46 _RL obTimeScale,Uinflow,rampTime2
47 _RL vertStructWst(Nr)
48 _RL mz,strat,kx
49 _RL tmpsum
50 _RL CVEL
51 _RL ab05, ab15
52
53 C Vertical mode number
54 mz=1.0
55 C Stratification
56 strat = 1.0 _d -6 / (gravity*tAlpha)
57
58 C Create a vertical structure function with zero mean
59 tmpsum=0.
60 do J=1,Nr
61 vertStructWst(J)=cos(mz*PI* (rC(J)/rF(Nr+1)) )
62 tmpsum=tmpsum+vertStructWst(J)*drF(J)
63 enddo
64 tmpsum=tmpsum/rF(Nr+1)
65 do J=1,Nr
66 vertStructWst(J)=vertStructWst(J)-tmpsum
67 enddo
68 c
69 obTimeScale = 44567.0
70 kx=mz*2.*pi/400.0*sqrt((2.0*pi*2.0*pi/(obTimeScale*obTimeScale)
71 & - f0*f0)/(1.0 _d -6
72 & - 2.0*pi*2.0*pi/(obTimeScale*obTimeScale)))
73 Uinflow = 0.024
74 rampTime2 = 4*44567.0
75
76 C Eastern boundary
77 DO J=1-Oly,sNy+Oly
78 IF (OB_Ie(J,bi,bj).NE.0) THEN
79 OBEu(J,K,bi,bj)=0.
80 OBEv(J,K,bi,bj)=0.
81 OBEt(J,K,bi,bj)=tRef(K)
82 #ifdef ALLOW_NONHYDROSTATIC
83 OBEw(J,K,bi,bj)=0.
84 #endif
85 ENDIF
86 ENDDO
87
88
89 C Western boundary
90 DO J=1-Oly,sNy+Oly
91 IF (OB_Iw(J,bi,bj).NE.0) THEN
92 OBWu(J,K,bi,bj)=0.
93 & +Uinflow
94 & *vertStructWst(K)
95 & *sin(2.*PI*myCurrentTime/obTimeScale)
96 & *(exp(myCurrentTime/rampTime2)
97 & - exp(-myCurrentTime/rampTime2))
98 & /(exp(myCurrentTime/rampTime2)
99 & + exp(-myCurrentTime/rampTime2))
100 & *cos(kx*(3-2-0.5)*delX(1))
101 OBWv(J,K,bi,bj)=0.
102 & +Uinflow
103 & *f0/(2.0*PI/obTimeScale)
104 & *vertStructWst(K)
105 & *cos(2.*PI*myCurrentTime/obTimeScale )
106 & * (exp(myCurrentTime/rampTime2)
107 & - exp(-myCurrentTime/rampTime2))
108 & /(exp(myCurrentTime/rampTime2)
109 & + exp(-myCurrentTime/rampTime2))
110 OBWt(J,K,bi,bj)=tRef(K)
111 & + Uinflow*sin(mz*PI*(float(k)-0.5)/float(Nr))
112 & * sin(2.0*PI*myCurrentTime/obTimeScale)
113 & *sqrt(strat/(tAlpha*gravity))
114 & *sqrt(2.0*PI/obTimeScale*2.0*PI/obTimeScale - f0*f0)
115 & /(2.0*PI/obTimeScale)
116 & * (exp(myCurrentTime/rampTime2)
117 & - exp(-myCurrentTime/rampTime2))
118 & /(exp(myCurrentTime/rampTime2)
119 & + exp(-myCurrentTime/rampTime2))
120 #ifdef ALLOW_NONHYDROSTATIC
121 OBWw(J,K,bi,bj)=-Uinflow
122 & *sqrt(2.0*PI/obTimeScale*2.0*PI/obTimeScale - f0*f0)
123 & /sqrt(strat*strat - 2.0*PI/obTimeScale*2.0*PI/obTimeScale)
124 & *sin(mz*PI*(float(k)-0.5)/float(Nr))
125 & *cos(2.*PI*myCurrentTime/obTimeScale)
126 & *(exp(myCurrentTime/rampTime2)
127 & - exp(-myCurrentTime/rampTime2))
128 & /(exp(myCurrentTime/rampTime2)
129 & + exp(-myCurrentTime/rampTime2))
130
131 #endif
132 ENDIF
133 ENDDO
134
135 C Northern boundary
136 DO I=1-Olx,sNx+Olx
137 IF (OB_Jn(I,bi,bj).NE.0) THEN
138 OBNu(I,K,bi,bj)=0.
139 OBNv(I,K,bi,bj)=0.
140 OBNt(I,K,bi,bj)=tRef(K)
141 #ifdef ALLOW_NONHYDROSTATIC
142 OBNw(I,K,bi,bj)=0.
143 #endif
144 ENDIF
145 ENDDO
146
147 C Southern boundary
148 DO I=1-Olx,sNx+Olx
149 IF (OB_Js(I,bi,bj).NE.0) THEN
150 OBSu(I,K,bi,bj)=0.
151 OBSv(I,K,bi,bj)=0.
152 OBSt(I,K,bi,bj)=tRef(K)
153 #ifdef ALLOW_NONHYDROSTATIC
154 OBSw(I,K,bi,bj)=0.
155 #endif
156 ENDIF
157 ENDDO
158
159 #endif
160 RETURN
161 END

  ViewVC Help
Powered by ViewVC 1.1.22