/[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.3 - (show annotations) (download)
Wed Feb 7 16:51:19 2001 UTC (23 years, 2 months ago) by adcroft
Branch: MAIN
CVS Tags: HEAD
Changes since 1.2: +2 -2 lines
FILE REMOVED
Deleted old OBCS code.

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

  ViewVC Help
Powered by ViewVC 1.1.22