/[MITgcm]/MITgcm/pkg/obcs/obcs_init_variables.F
ViewVC logotype

Annotation of /MITgcm/pkg/obcs/obcs_init_variables.F

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


Revision 1.20 - (hide annotations) (download)
Tue May 30 22:45:34 2006 UTC (18 years, 1 month ago) by mlosch
Branch: MAIN
CVS Tags: checkpoint59, checkpoint58f_post, checkpoint58y_post, checkpoint58t_post, checkpoint58m_post, checkpoint58w_post, checkpoint58o_post, checkpoint58p_post, checkpoint58q_post, checkpoint58r_post, checkpoint58n_post, checkpoint59e, checkpoint59d, checkpoint59g, checkpoint59f, checkpoint59a, checkpoint59c, checkpoint59b, checkpoint59h, checkpoint58k_post, checkpoint58v_post, checkpoint58l_post, checkpoint58g_post, checkpoint58x_post, checkpoint58h_post, checkpoint58j_post, checkpoint58i_post, checkpoint58u_post, checkpoint58s_post
Changes since 1.19: +5 -1 lines
o make obcs initialisation of ptracers visible to taf

1 mlosch 1.20 C $Header: /u/gcmpack/MITgcm/pkg/obcs/obcs_init_variables.F,v 1.19 2005/12/15 17:15:36 jmc Exp $
2 adcroft 1.3 C $Name: $
3 adcroft 1.2
4     #include "OBCS_OPTIONS.h"
5    
6     SUBROUTINE OBCS_INIT_VARIABLES( myThid )
7     C /==========================================================\
8     C | SUBROUTINE OBCS_INIT_VARIABLES |
9     C | o Initialise OBCs variable data |
10     C |==========================================================|
11     C | |
12     C \==========================================================/
13     IMPLICIT NONE
14    
15     C === Global variables ===
16     #include "SIZE.h"
17     #include "EEPARAMS.h"
18     #include "PARAMS.h"
19     #include "DYNVARS.h"
20     #include "OBCS.h"
21 jmc 1.17 #ifdef ALLOW_PTRACERS
22 mlosch 1.14 #include "PTRACERS_SIZE.h"
23     #include "PTRACERS.h"
24     #include "OBCS_PTRACERS.h"
25     #endif /* ALLOW_PTRACERS */
26 adcroft 1.2
27     C == Routine arguments ==
28     C myThid - Number of this instance of INI_DEPTHS
29     INTEGER myThid
30    
31     #ifdef ALLOW_OBCS
32    
33     C == Local variables ==
34     INTEGER bi, bj
35     INTEGER I, J, K
36 adcroft 1.9 CHARACTER*(10) suff
37     INTEGER prec
38 mlosch 1.14 #ifdef ALLOW_PTRACERS
39     INTEGER iTracer
40     #endif /* ALLOW_PTRACERS */
41 adcroft 1.2
42 adcroft 1.12 #ifdef ALLOW_DEBUG
43     IF (debugMode) CALL DEBUG_ENTER('OBCS_INIT_VARIABLES',myThid)
44     #endif
45    
46 adcroft 1.2 DO bj = myByLo(myThid), myByHi(myThid)
47     DO bi = myBxLo(myThid), myBxHi(myThid)
48    
49     DO K=1,Nr
50     DO I=1-Olx,sNx+Olx
51 heimbach 1.10 #ifdef ALLOW_OBCS_NORTH
52     OBNu(I,K,bi,bj)=0. _d 0
53     OBNv(I,K,bi,bj)=0. _d 0
54     OBNt(I,K,bi,bj)=0. _d 0
55     OBNs(I,K,bi,bj)=0. _d 0
56     # ifdef ALLOW_NONHYDROSTATIC
57     OBNw(I,K,bi,bj)=0. _d 0
58     # endif
59     # ifdef ALLOW_OBCS_PRESCRIBE
60     OBNu0(I,K,bi,bj)=0. _d 0
61     OBNv0(I,K,bi,bj)=0. _d 0
62     OBNt0(I,K,bi,bj)=0. _d 0
63     OBNs0(I,K,bi,bj)=0. _d 0
64     OBNu1(I,K,bi,bj)=0. _d 0
65     OBNv1(I,K,bi,bj)=0. _d 0
66     OBNt1(I,K,bi,bj)=0. _d 0
67     OBNs1(I,K,bi,bj)=0. _d 0
68     # endif
69     #endif /* ALLOW_OBCS_NORTH */
70    
71     #ifdef ALLOW_OBCS_SOUTH
72     OBSu(I,K,bi,bj)=0. _d 0
73     OBSv(I,K,bi,bj)=0. _d 0
74     OBSt(I,K,bi,bj)=0. _d 0
75     OBSs(I,K,bi,bj)=0. _d 0
76     # ifdef ALLOW_NONHYDROSTATIC
77     OBSw(I,K,bi,bj)=0. _d 0
78     # endif
79     # ifdef ALLOW_OBCS_PRESCRIBE
80     OBSu0(I,K,bi,bj)=0. _d 0
81     OBSv0(I,K,bi,bj)=0. _d 0
82     OBSt0(I,K,bi,bj)=0. _d 0
83     OBSs0(I,K,bi,bj)=0. _d 0
84     OBSu1(I,K,bi,bj)=0. _d 0
85     OBSv1(I,K,bi,bj)=0. _d 0
86     OBSt1(I,K,bi,bj)=0. _d 0
87     OBSs1(I,K,bi,bj)=0. _d 0
88     # endif
89     #endif /* ALLOW_OBCS_SOUTH */
90 adcroft 1.2 ENDDO
91 heimbach 1.10
92 adcroft 1.2 DO J=1-Oly,sNy+Oly
93 heimbach 1.10 #ifdef ALLOW_OBCS_EAST
94     OBEu(J,K,bi,bj)=0. _d 0
95     OBEv(J,K,bi,bj)=0. _d 0
96     OBEt(J,K,bi,bj)=0. _d 0
97     OBEs(J,K,bi,bj)=0. _d 0
98     # ifdef ALLOW_NONHYDROSTATIC
99     OBEw(J,K,bi,bj)=0. _d 0
100     # endif
101     # ifdef ALLOW_OBCS_PRESCRIBE
102     OBEu0(J,K,bi,bj)=0. _d 0
103     OBEv0(J,K,bi,bj)=0. _d 0
104     OBEt0(J,K,bi,bj)=0. _d 0
105     OBEs0(J,K,bi,bj)=0. _d 0
106     OBEu1(J,K,bi,bj)=0. _d 0
107     OBEv1(J,K,bi,bj)=0. _d 0
108     OBEt1(J,K,bi,bj)=0. _d 0
109     OBEs1(J,K,bi,bj)=0. _d 0
110     # endif
111     #endif /* ALLOW_OBCS_EAST */
112    
113     #ifdef ALLOW_OBCS_WEST
114     OBWu(J,K,bi,bj)=0. _d 0
115     OBWv(J,K,bi,bj)=0. _d 0
116     OBWt(J,K,bi,bj)=0. _d 0
117     OBWs(J,K,bi,bj)=0. _d 0
118     # ifdef ALLOW_NONHYDROSTATIC
119     OBWw(J,K,bi,bj)=0. _d 0
120     # endif
121     # ifdef ALLOW_OBCS_PRESCRIBE
122     OBWu0(J,K,bi,bj)=0. _d 0
123     OBWv0(J,K,bi,bj)=0. _d 0
124     OBWt0(J,K,bi,bj)=0. _d 0
125     OBWs0(J,K,bi,bj)=0. _d 0
126     OBWu1(J,K,bi,bj)=0. _d 0
127     OBWv1(J,K,bi,bj)=0. _d 0
128     OBWt1(J,K,bi,bj)=0. _d 0
129     OBWs1(J,K,bi,bj)=0. _d 0
130     # endif
131     #endif /* ALLOW_OBCS_WEST */
132 adcroft 1.2 ENDDO
133     ENDDO
134 jmc 1.5
135 mlosch 1.14 #ifdef ALLOW_PTRACERS
136 mlosch 1.20 #ifndef ALLOW_AUTODIFF_TAMC
137 mlosch 1.16 IF ( usePTRACERS ) THEN
138 mlosch 1.20 #endif
139 mlosch 1.16 DO iTracer=1,PTRACERS_numInUse
140     DO K=1,Nr
141     DO I=1-Olx,sNx+Olx
142 mlosch 1.14 #ifdef ALLOW_OBCS_NORTH
143 mlosch 1.16 OBNptr (I,K,bi,bj,iTracer)=0. _d 0
144 mlosch 1.14 # ifdef ALLOW_OBCS_PRESCRIBE
145 mlosch 1.16 OBNptr0(I,K,bi,bj,iTracer)=0. _d 0
146     OBNptr1(I,K,bi,bj,iTracer)=0. _d 0
147 mlosch 1.14 # endif
148     #endif /* ALLOW_OBCS_NORTH */
149 mlosch 1.16
150 mlosch 1.14 #ifdef ALLOW_OBCS_SOUTH
151 mlosch 1.16 OBSptr (I,K,bi,bj,iTracer)=0. _d 0
152 mlosch 1.14 # ifdef ALLOW_OBCS_PRESCRIBE
153 mlosch 1.16 OBSptr0(I,K,bi,bj,iTracer)=0. _d 0
154     OBSptr1(I,K,bi,bj,iTracer)=0. _d 0
155 mlosch 1.14 # endif
156     #endif /* ALLOW_OBCS_SOUTH */
157 mlosch 1.16 ENDDO
158    
159     DO J=1-Oly,sNy+Oly
160 mlosch 1.14 #ifdef ALLOW_OBCS_EAST
161 mlosch 1.16 OBEptr (J,K,bi,bj,iTracer)=0. _d 0
162 mlosch 1.14 # ifdef ALLOW_OBCS_PRESCRIBE
163 mlosch 1.16 OBEptr0(J,K,bi,bj,iTracer)=0. _d 0
164     OBEptr1(J,K,bi,bj,iTracer)=0. _d 0
165 mlosch 1.14 # endif
166     #endif /* ALLOW_OBCS_EAST */
167 mlosch 1.16
168 mlosch 1.14 #ifdef ALLOW_OBCS_WEST
169 mlosch 1.16 OBWptr (J,K,bi,bj,iTracer)=0. _d 0
170 mlosch 1.14 # ifdef ALLOW_OBCS_PRESCRIBE
171 mlosch 1.16 OBWptr0(J,K,bi,bj,iTracer)=0. _d 0
172     OBWptr1(J,K,bi,bj,iTracer)=0. _d 0
173 mlosch 1.14 # endif
174     #endif /* ALLOW_OBCS_WEST */
175 mlosch 1.16 ENDDO
176 mlosch 1.14 ENDDO
177     ENDDO
178 mlosch 1.20 #ifndef ALLOW_AUTODIFF_TAMC
179 mlosch 1.16 ENDIF
180 mlosch 1.20 #endif
181 mlosch 1.14 #endif /* ALLOW_PTRACERS */
182    
183 jmc 1.5 #ifdef NONLIN_FRSURF
184     DO I=1-Olx,sNx+Olx
185     OBNeta(I,bi,bj)=0.
186     OBSeta(I,bi,bj)=0.
187     ENDDO
188     DO J=1-Oly,sNy+Oly
189     OBEeta(J,bi,bj)=0.
190     OBWeta(J,bi,bj)=0.
191     ENDDO
192     #endif /* NONLIN_FRSURF */
193 adcroft 1.2
194     #ifdef ALLOW_ORLANSKI
195     IF (useOrlanskiNorth.OR.useOrlanskiSouth.OR.
196     & useOrlanskiEast.OR.useOrlanskiWest) THEN
197 adcroft 1.12 #ifdef ALLOW_DEBUG
198     IF (debugMode) CALL DEBUG_CALL('ORLANSKI_INIT',myThid)
199     #endif
200 adcroft 1.2 CALL ORLANSKI_INIT(bi, bj, myThid)
201     ENDIF
202     #endif /* ALLOW_ORLANSKI */
203 adcroft 1.3
204     ENDDO
205     ENDDO
206 jmc 1.7
207 adcroft 1.9 C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
208     C jmc: here is the logical place to read OBCS-pickup files
209     C but a) without Orlanski: pass the test 1+1=2 without reading pickup.
210     C b) with Orlanski: 1+1=2 fail even with this bit of code
211     IF ( nIter0.NE.0 ) THEN
212     prec = precFloat64
213     IF (pickupSuff.EQ.' ') THEN
214     WRITE(suff,'(I10.10)') nIter0
215     ELSE
216     WRITE(suff,'(A10)') pickupSuff
217     ENDIF
218     c CALL OBCS_READ_CHECKPOINT(prec, nIter0, suff, myThid)
219     ENDIF
220     C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
221    
222 mlosch 1.18 C-- Load/compute OBCS values in all cases, although these values are
223     C-- only used for initialisation and never for restart:
224 adcroft 1.12 #ifdef ALLOW_DEBUG
225     IF (debugMode) CALL DEBUG_CALL('OBCS_CALC',myThid)
226     #endif
227 adcroft 1.2 DO bj = myByLo(myThid), myByHi(myThid)
228     DO bi = myBxLo(myThid), myBxHi(myThid)
229 jmc 1.6 CALL OBCS_CALC( bi, bj, startTime, nIter0,
230 adcroft 1.2 & uVel, vVel, wVel, theta, salt, myThid )
231 heimbach 1.10 ENDDO
232     ENDDO
233    
234 mlosch 1.15 IF ( startTime .EQ. baseTime .AND. nIter0 .EQ. 0
235     & .AND. pickupSuff .EQ. ' ' ) THEN
236 jmc 1.17 C-- Apply OBCS values to initial conditions for consistency
237     C (but initial conditions only)
238 adcroft 1.12 #ifdef ALLOW_DEBUG
239 mlosch 1.15 IF (debugMode)
240     & CALL DEBUG_CALL('OBCS_APPLY_UV + OBCS_APPLY_TS',myThid)
241 adcroft 1.12 #endif
242 mlosch 1.15 DO bj = myByLo(myThid), myByHi(myThid)
243     DO bi = myBxLo(myThid), myBxHi(myThid)
244     DO K=1,Nr
245     CALL OBCS_APPLY_UV( bi, bj, k, uVel, vVel, myThid )
246     CALL OBCS_APPLY_TS( bi, bj, k, theta, salt, myThid )
247     ENDDO
248     ENDDO
249     ENDDO
250 mlosch 1.18 IF (useOBCSprescribe) THEN
251     C After applying the boundary conditions exchange the 3D-fields.
252     C This is only necessary of the boudnary values have been read
253     C from a file.
254     #ifdef ALLOW_DEBUG
255     IF (debugMode)
256     & CALL DEBUG_CALL('EXCHANGES in OBCS_INIT_VARIABLES',myThid)
257     #endif
258     CALL EXCH_UV_XYZ_RL(uVel,vVel,.TRUE.,myThid)
259     _EXCH_XYZ_R8( theta, myThid )
260     _EXCH_XYZ_R8( salt , myThid )
261     ENDIF
262     C endif start from rest
263     ENDIF
264 mlosch 1.14 #ifdef ALLOW_PTRACERS
265 mlosch 1.15 C repeat everything for passive tracers
266 mlosch 1.18 IF ( usePTRACERS ) THEN
267     C catch the case when we do start from a pickup for dynamics variables
268     C but initialise ptracers differently
269     IF ( nIter0 .EQ. PTRACERS_Iter0 ) THEN
270 mlosch 1.15 #ifdef ALLOW_DEBUG
271     IF (debugMode)
272     & CALL DEBUG_CALL('OBCS_APPLY_PTRACER',myThid)
273     #endif
274     DO iTracer=1,PTRACERS_numInUse
275     DO bj = myByLo(myThid), myByHi(myThid)
276     DO bi = myBxLo(myThid), myBxHi(myThid)
277     DO K=1,Nr
278     CALL OBCS_APPLY_PTRACER(
279     I bi, bj, K, iTracer,
280 mlosch 1.18 U ptracer(1-Olx,1-Oly,K,bi,bj,iTracer),
281 mlosch 1.15 I myThid )
282     ENDDO
283     ENDDO
284 mlosch 1.14 ENDDO
285 mlosch 1.15 ENDDO
286 mlosch 1.18 IF (useOBCSprescribe) THEN
287 mlosch 1.11 C After applying the boundary conditions exchange the 3D-fields.
288     C This is only necessary of the boudnary values have been read
289     C from a file.
290 adcroft 1.12 #ifdef ALLOW_DEBUG
291 mlosch 1.18 IF (debugMode) CALL DEBUG_CALL(
292     & 'PTRACERS EXCHANGES in OBCS_INIT_VARIABLES',myThid)
293 adcroft 1.12 #endif
294 jmc 1.19 CALL PTRACERS_FIELDS_BLOCKING_EXCH( myThid )
295 mlosch 1.18 ENDIF
296     C endif start from rest
297 mlosch 1.15 ENDIF
298 mlosch 1.18 C endif usePTRACERS
299     ENDIF
300 mlosch 1.15 #endif /* ALLOW_PTRACERS */
301 mlosch 1.11
302 adcroft 1.2 #endif /* ALLOW_OBCS */
303 heimbach 1.10
304 adcroft 1.12 #ifdef ALLOW_DEBUG
305     IF (debugMode) CALL DEBUG_LEAVE('OBCS_INIT_VARIABLES',myThid)
306     #endif
307 adcroft 1.2 RETURN
308     END

  ViewVC Help
Powered by ViewVC 1.1.22