/[MITgcm]/MITgcm/model/src/ini_masks_etc.F
ViewVC logotype

Contents of /MITgcm/model/src/ini_masks_etc.F

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


Revision 1.42 - (show annotations) (download)
Sun Jun 14 21:45:12 2009 UTC (14 years, 11 months ago) by jmc
Branch: MAIN
CVS Tags: checkpoint61q, checkpoint61r
Changes since 1.41: +2 -6 lines
remove unnecessary BARRIER

1 C $Header: /u/gcmpack/MITgcm/model/src/ini_masks_etc.F,v 1.41 2009/05/12 19:54:28 jmc Exp $
2 C $Name: $
3
4 #include "PACKAGES_CONFIG.h"
5 #include "CPP_OPTIONS.h"
6
7 CBOP
8 C !ROUTINE: INI_MASKS_ETC
9 C !INTERFACE:
10 SUBROUTINE INI_MASKS_ETC( myThid )
11 C !DESCRIPTION: \bv
12 C *==========================================================*
13 C | SUBROUTINE INI_MASKS_ETC
14 C | o Initialise masks and topography factors
15 C *==========================================================*
16 C | These arrays are used throughout the code and describe
17 C | the topography of the domain through masks (0s and 1s)
18 C | and fractional height factors (0<hFac<1). The latter
19 C | distinguish between the lopped-cell and full-step
20 C | topographic representations.
21 C *==========================================================*
22 C \ev
23
24 C !USES:
25 IMPLICIT NONE
26 C === Global variables ===
27 #include "SIZE.h"
28 #include "EEPARAMS.h"
29 #include "PARAMS.h"
30 #include "GRID.h"
31 #include "SURFACE.h"
32 #ifdef ALLOW_EXCH2
33 # include "W2_EXCH2_SIZE.h"
34 # include "W2_EXCH2_TOPOLOGY.h"
35 #endif /* ALLOW_EXCH2 */
36
37 C !INPUT/OUTPUT PARAMETERS:
38 C == Routine arguments ==
39 C myThid :: Number of this instance of INI_MASKS_ETC
40 INTEGER myThid
41
42 C !LOCAL VARIABLES:
43 C == Local variables ==
44 C bi,bj :: tile indices
45 C I,J,K :: Loop counters
46 C tmpfld :: Temporary array used to compute & write Total Depth
47 _RS tmpfld(1-OLx:sNx+OLx,1-OLy:sNy+OLy,nSx,nSy)
48 INTEGER bi, bj
49 INTEGER I, J, K
50 _RL hFacCtmp
51 _RL hFacMnSz
52 _RL tileArea(nSx,nSy), threadArea
53 C put tileArea in (local) common block to print from master-thread:
54 COMMON / LOCAL_INI_MASKS_ETC / tileArea
55 CHARACTER*(MAX_LEN_MBUF) msgBuf
56 CEOP
57
58 C- Calculate lopping factor hFacC : over-estimate the part inside of the domain
59 C taking into account the lower_R Boundary (Bathymetrie / Top of Atmos)
60 DO bj=myByLo(myThid), myByHi(myThid)
61 DO bi=myBxLo(myThid), myBxHi(myThid)
62 DO K=1, Nr
63 hFacMnSz=max( hFacMin, min(hFacMinDr*recip_drF(k),1. _d 0) )
64 DO J=1-Oly,sNy+Oly
65 DO I=1-Olx,sNx+Olx
66 C o Non-dimensional distance between grid bound. and domain lower_R bound.
67 hFacCtmp = (rF(K)-R_low(I,J,bi,bj))*recip_drF(K)
68 C o Select between, closed, open or partial (0,1,0-1)
69 hFacCtmp=min( max( hFacCtmp, 0. _d 0) , 1. _d 0)
70 C o Impose minimum fraction and/or size (dimensional)
71 IF (hFacCtmp.LT.hFacMnSz) THEN
72 IF (hFacCtmp.LT.hFacMnSz*0.5) THEN
73 hFacC(I,J,K,bi,bj)=0.
74 ELSE
75 hFacC(I,J,K,bi,bj)=hFacMnSz
76 ENDIF
77 ELSE
78 hFacC(I,J,K,bi,bj)=hFacCtmp
79 ENDIF
80 ENDDO
81 ENDDO
82 ENDDO
83
84 C- Re-calculate lower-R Boundary position, taking into account hFacC
85 DO J=1-Oly,sNy+Oly
86 DO I=1-Olx,sNx+Olx
87 R_low(I,J,bi,bj) = rF(1)
88 DO K=Nr,1,-1
89 R_low(I,J,bi,bj) = R_low(I,J,bi,bj)
90 & - drF(k)*hFacC(I,J,K,bi,bj)
91 ENDDO
92 ENDDO
93 ENDDO
94 C - end bi,bj loops.
95 ENDDO
96 ENDDO
97
98 C- Calculate lopping factor hFacC : Remove part outside of the domain
99 C taking into account the Reference (=at rest) Surface Position Ro_surf
100 DO bj=myByLo(myThid), myByHi(myThid)
101 DO bi=myBxLo(myThid), myBxHi(myThid)
102 DO K=1, Nr
103 hFacMnSz=max( hFacMin, min(hFacMinDr*recip_drF(k),1. _d 0) )
104 DO J=1-Oly,sNy+Oly
105 DO I=1-Olx,sNx+Olx
106 C o Non-dimensional distance between grid boundary and model surface
107 hFacCtmp = (rF(k)-Ro_surf(I,J,bi,bj))*recip_drF(K)
108 C o Reduce the previous fraction : substract the outside part.
109 hFacCtmp = hFacC(I,J,K,bi,bj) - max( hFacCtmp, 0. _d 0)
110 C o set to zero if empty Column :
111 hFacCtmp = max( hFacCtmp, 0. _d 0)
112 C o Impose minimum fraction and/or size (dimensional)
113 IF (hFacCtmp.LT.hFacMnSz) THEN
114 IF (hFacCtmp.LT.hFacMnSz*0.5) THEN
115 hFacC(I,J,K,bi,bj)=0.
116 ELSE
117 hFacC(I,J,K,bi,bj)=hFacMnSz
118 ENDIF
119 ELSE
120 hFacC(I,J,K,bi,bj)=hFacCtmp
121 ENDIF
122 ENDDO
123 ENDDO
124 ENDDO
125 ENDDO
126 ENDDO
127
128 #ifdef ALLOW_SHELFICE
129 IF ( useShelfIce ) THEN
130 C-- Modify lopping factor hFacC : Remove part outside of the domain
131 C taking into account the Reference (=at rest) Surface Position Ro_shelfIce
132 CALL SHELFICE_UPDATE_MASKS(
133 I rF, recip_drF,
134 U hFacC,
135 I myThid )
136 ENDIF
137 #endif /* ALLOW_SHELFICE */
138
139 C- Re-calculate Reference surface position, taking into account hFacC
140 C initialize Total column fluid thickness and surface k index
141 C Note: if no fluid (continent) ==> ksurf = Nr+1
142 DO bj=myByLo(myThid), myByHi(myThid)
143 DO bi=myBxLo(myThid), myBxHi(myThid)
144 DO J=1-Oly,sNy+Oly
145 DO I=1-Olx,sNx+Olx
146 tmpfld(I,J,bi,bj) = 0.
147 ksurfC(I,J,bi,bj) = Nr+1
148 maskH(I,J,bi,bj) = 0.
149 Ro_surf(I,J,bi,bj) = R_low(I,J,bi,bj)
150 DO K=Nr,1,-1
151 Ro_surf(I,J,bi,bj) = Ro_surf(I,J,bi,bj)
152 & + drF(k)*hFacC(I,J,K,bi,bj)
153 IF (hFacC(I,J,K,bi,bj).NE.0.) THEN
154 ksurfC(I,J,bi,bj) = k
155 maskH(I,J,bi,bj) = 1.
156 tmpfld(I,J,bi,bj) = tmpfld(I,J,bi,bj) + 1.
157 ENDIF
158 ENDDO
159 kLowC(I,J,bi,bj) = 0
160 DO K= 1, Nr
161 IF (hFacC(I,J,K,bi,bj).NE.0) THEN
162 kLowC(I,J,bi,bj) = K
163 ENDIF
164 ENDDO
165 ENDDO
166 ENDDO
167 C - end bi,bj loops.
168 ENDDO
169 ENDDO
170
171 C CALL PLOT_FIELD_XYRS( tmpfld,
172 C & 'Model Depths K Index' , 1, myThid )
173 CALL PLOT_FIELD_XYRS(R_low,
174 & 'Model R_low (ini_masks_etc)', 1, myThid)
175 CALL PLOT_FIELD_XYRS(Ro_surf,
176 & 'Model Ro_surf (ini_masks_etc)', 1, myThid)
177
178 C Calculate quantities derived from XY depth map
179 threadArea = 0. _d 0
180 DO bj = myByLo(myThid), myByHi(myThid)
181 DO bi = myBxLo(myThid), myBxHi(myThid)
182 DO j=1-Oly,sNy+Oly
183 DO i=1-Olx,sNx+Olx
184 C Total fluid column thickness (r_unit) :
185 c Rcolumn(i,j,bi,bj)= Ro_surf(i,j,bi,bj) - R_low(i,j,bi,bj)
186 tmpfld(i,j,bi,bj) = Ro_surf(i,j,bi,bj) - R_low(i,j,bi,bj)
187 C Inverse of fluid column thickness (1/r_unit)
188 IF ( tmpfld(i,j,bi,bj) .LE. 0. ) THEN
189 recip_Rcol(i,j,bi,bj) = 0.
190 ELSE
191 recip_Rcol(i,j,bi,bj) = 1. _d 0 / tmpfld(i,j,bi,bj)
192 ENDIF
193 ENDDO
194 ENDDO
195 C- Compute the domain Area:
196 tileArea(bi,bj) = 0. _d 0
197 DO j=1,sNy
198 DO i=1,sNx
199 tileArea(bi,bj) = tileArea(bi,bj)
200 & + rA(i,j,bi,bj)*maskH(i,j,bi,bj)
201 ENDDO
202 ENDDO
203 threadArea = threadArea + tileArea(bi,bj)
204 ENDDO
205 ENDDO
206 C _EXCH_XY_RS( recip_Rcol, myThid )
207 #ifdef ALLOW_AUTODIFF_TAMC
208 C_jmc: apply GLOBAL_SUM to thread-local variable (not in common block)
209 _GLOBAL_SUM_RL( threadArea, myThid )
210 #else
211 CALL GLOBAL_SUM_TILE_RL( tileArea, threadArea, myThid )
212 #endif
213 _BEGIN_MASTER( myThid )
214 globalArea = threadArea
215 C- list empty tiles:
216 msgBuf(1:1) = ' '
217 DO bj = 1,nSy
218 DO bi = 1,nSx
219 IF ( tileArea(bi,bj).EQ.0. _d 0 ) THEN
220 #ifdef ALLOW_EXCH2
221 WRITE(msgBuf,'(A,I6,A,I6,A)')
222 & 'Empty tile: #', W2_myTileList(bi), ' (bi=', bi,' )'
223 #else
224 WRITE(msgBuf,'(A,I6,I6)') 'Empty tile bi,bj=', bi, bj
225 #endif
226 CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,
227 & SQUEEZE_RIGHT, myThid )
228 ENDIF
229 ENDDO
230 ENDDO
231 IF ( msgBuf(1:1).NE.' ' ) THEN
232 WRITE(msgBuf,'(A)') ' '
233 CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,
234 & SQUEEZE_RIGHT, myThid )
235 ENDIF
236 _END_MASTER( myThid )
237
238 C hFacW and hFacS (at U and V points)
239 DO bj=myByLo(myThid), myByHi(myThid)
240 DO bi=myBxLo(myThid), myBxHi(myThid)
241 DO K=1, Nr
242 DO J=1-Oly,sNy+Oly
243 hFacW(1-OLx,J,K,bi,bj)= 0.
244 DO I=2-Olx,sNx+Olx
245 hFacW(I,J,K,bi,bj)=
246 & MIN(hFacC(I,J,K,bi,bj),hFacC(I-1,J,K,bi,bj))
247 ENDDO
248 ENDDO
249 DO I=1-Olx,sNx+Olx
250 hFacS(I,1-OLy,K,bi,bj)= 0.
251 ENDDO
252 DO J=2-Oly,sNy+oly
253 DO I=1-Olx,sNx+Olx
254 hFacS(I,J,K,bi,bj)=
255 & MIN(hFacC(I,J,K,bi,bj),hFacC(I,J-1,K,bi,bj))
256 ENDDO
257 ENDDO
258 ENDDO
259 ENDDO
260 ENDDO
261 CALL EXCH_UV_XYZ_RS(hFacW,hFacS,.FALSE.,myThid)
262 C The following block allows thin walls representation of non-periodic
263 C boundaries such as happen on the lat-lon grid at the N/S poles.
264 C We should really supply a flag for doing this.
265 DO bj=myByLo(myThid), myByHi(myThid)
266 DO bi=myBxLo(myThid), myBxHi(myThid)
267 DO K=1, Nr
268 DO J=1-Oly,sNy+Oly
269 DO I=1-Olx,sNx+Olx
270 IF (dyG(I,J,bi,bj).EQ.0.) hFacW(I,J,K,bi,bj)=0.
271 IF (dxG(I,J,bi,bj).EQ.0.) hFacS(I,J,K,bi,bj)=0.
272 ENDDO
273 ENDDO
274 ENDDO
275 ENDDO
276 ENDDO
277
278 #ifdef ALLOW_NONHYDROSTATIC
279 C rLow & reference rSurf at Western & Southern edges (U and V points)
280 DO bj=myByLo(myThid), myByHi(myThid)
281 DO bi=myBxLo(myThid), myBxHi(myThid)
282 I = 1-OlX
283 DO J=1-Oly,sNy+Oly
284 rLowW (i,j,bi,bj) = 0.
285 rSurfW(i,j,bi,bj) = 0.
286 ENDDO
287 J = 1-Oly
288 DO I=1-Olx,sNx+Olx
289 rLowS (i,j,bi,bj) = 0.
290 rSurfS(i,j,bi,bj) = 0.
291 ENDDO
292 DO J=1-Oly,sNy+Oly
293 DO I=2-Olx,sNx+Olx
294 rSurfW(i,j,bi,bj) =
295 & MIN( Ro_surf(i-1,j,bi,bj), Ro_surf(i,j,bi,bj) )
296 rLowW(i,j,bi,bj) =
297 & MAX( R_low(i-1,j,bi,bj), R_low(i,j,bi,bj) )
298 ENDDO
299 ENDDO
300 DO J=2-Oly,sNy+Oly
301 DO I=1-Olx,sNx+Olx
302 rSurfS(i,j,bi,bj) =
303 & MIN( Ro_surf(i,j-1,bi,bj), Ro_surf(i,j,bi,bj) )
304 rLowS(i,j,bi,bj) =
305 & MAX( R_low(i,j-1,bi,bj), R_low(i,j,bi,bj) )
306 ENDDO
307 ENDDO
308 ENDDO
309 ENDDO
310 CALL EXCH_UV_XY_RS( rSurfW, rSurfS, .FALSE., myThid )
311 CALL EXCH_UV_XY_RS( rLowW, rLowS, .FALSE., myThid )
312 #endif /* ALLOW_NONHYDROSTATIC */
313
314 C- Write to disk: Total Column Thickness & hFac(C,W,S):
315 C This I/O is now done in write_grid.F
316 c CALL WRITE_FLD_XY_RS( 'Depth',' ',tmpfld,0,myThid)
317 c CALL WRITE_FLD_XYZ_RS( 'hFacC',' ',hFacC,0,myThid)
318 c CALL WRITE_FLD_XYZ_RS( 'hFacW',' ',hFacW,0,myThid)
319 c CALL WRITE_FLD_XYZ_RS( 'hFacS',' ',hFacS,0,myThid)
320
321 _BARRIER
322 CALL PLOT_FIELD_XYZRS( hFacC, 'hFacC' , Nr, 1, myThid )
323 CALL PLOT_FIELD_XYZRS( hFacW, 'hFacW' , Nr, 1, myThid )
324 CALL PLOT_FIELD_XYZRS( hFacS, 'hFacS' , Nr, 1, myThid )
325
326 C Masks and reciprocals of hFac[CWS]
327 DO bj = myByLo(myThid), myByHi(myThid)
328 DO bi = myBxLo(myThid), myBxHi(myThid)
329 DO K=1,Nr
330 DO J=1-Oly,sNy+Oly
331 DO I=1-Olx,sNx+Olx
332 IF (hFacC(I,J,K,bi,bj) .NE. 0. ) THEN
333 recip_hFacC(I,J,K,bi,bj) = 1. _d 0 / hFacC(I,J,K,bi,bj)
334 maskC(I,J,K,bi,bj) = 1.
335 ELSE
336 recip_hFacC(I,J,K,bi,bj) = 0.
337 maskC(I,J,K,bi,bj) = 0.
338 ENDIF
339 IF (hFacW(I,J,K,bi,bj) .NE. 0. ) THEN
340 recip_hFacW(I,J,K,bi,bj) = 1. _d 0 / hFacW(I,J,K,bi,bj)
341 maskW(I,J,K,bi,bj) = 1.
342 ELSE
343 recip_hFacW(I,J,K,bi,bj) = 0.
344 maskW(I,J,K,bi,bj) = 0.
345 ENDIF
346 IF (hFacS(I,J,K,bi,bj) .NE. 0. ) THEN
347 recip_hFacS(I,J,K,bi,bj) = 1. _d 0 / hFacS(I,J,K,bi,bj)
348 maskS(I,J,K,bi,bj) = 1.
349 ELSE
350 recip_hFacS(I,J,K,bi,bj) = 0.
351 maskS(I,J,K,bi,bj) = 0.
352 ENDIF
353 ENDDO
354 ENDDO
355 ENDDO
356 C- Calculate surface k index for interface W & S (U & V points)
357 DO J=1-Oly,sNy+Oly
358 DO I=1-Olx,sNx+Olx
359 ksurfW(I,J,bi,bj) = Nr+1
360 ksurfS(I,J,bi,bj) = Nr+1
361 DO k=Nr,1,-1
362 IF (hFacW(I,J,K,bi,bj).NE.0.) ksurfW(I,J,bi,bj) = k
363 IF (hFacS(I,J,K,bi,bj).NE.0.) ksurfS(I,J,bi,bj) = k
364 ENDDO
365 ENDDO
366 ENDDO
367 C - end bi,bj loops.
368 ENDDO
369 ENDDO
370
371 C Calculate recipricols grid lengths
372 DO bj = myByLo(myThid), myByHi(myThid)
373 DO bi = myBxLo(myThid), myBxHi(myThid)
374 DO J=1-Oly,sNy+Oly
375 DO I=1-Olx,sNx+Olx
376 IF ( dxG(I,J,bi,bj) .NE. 0. )
377 & recip_dxG(I,J,bi,bj)=1. _d 0/dxG(I,J,bi,bj)
378 IF ( dyG(I,J,bi,bj) .NE. 0. )
379 & recip_dyG(I,J,bi,bj)=1. _d 0/dyG(I,J,bi,bj)
380 IF ( dxC(I,J,bi,bj) .NE. 0. )
381 & recip_dxC(I,J,bi,bj)=1. _d 0/dxC(I,J,bi,bj)
382 IF ( dyC(I,J,bi,bj) .NE. 0. )
383 & recip_dyC(I,J,bi,bj)=1. _d 0/dyC(I,J,bi,bj)
384 IF ( dxF(I,J,bi,bj) .NE. 0. )
385 & recip_dxF(I,J,bi,bj)=1. _d 0/dxF(I,J,bi,bj)
386 IF ( dyF(I,J,bi,bj) .NE. 0. )
387 & recip_dyF(I,J,bi,bj)=1. _d 0/dyF(I,J,bi,bj)
388 IF ( dxV(I,J,bi,bj) .NE. 0. )
389 & recip_dxV(I,J,bi,bj)=1. _d 0/dxV(I,J,bi,bj)
390 IF ( dyU(I,J,bi,bj) .NE. 0. )
391 & recip_dyU(I,J,bi,bj)=1. _d 0/dyU(I,J,bi,bj)
392 IF ( rA(I,J,bi,bj) .NE. 0. )
393 & recip_rA(I,J,bi,bj)=1. _d 0/rA(I,J,bi,bj)
394 IF ( rAs(I,J,bi,bj) .NE. 0. )
395 & recip_rAs(I,J,bi,bj)=1. _d 0/rAs(I,J,bi,bj)
396 IF ( rAw(I,J,bi,bj) .NE. 0. )
397 & recip_rAw(I,J,bi,bj)=1. _d 0/rAw(I,J,bi,bj)
398 IF ( rAz(I,J,bi,bj) .NE. 0. )
399 & recip_rAz(I,J,bi,bj)=1. _d 0/rAz(I,J,bi,bj)
400 ENDDO
401 ENDDO
402 ENDDO
403 ENDDO
404
405 c #ifdef ALLOW_NONHYDROSTATIC
406 C-- Calculate "recip_hFacU" = reciprocal hfac distance/volume for W cells
407 C NOTE: not used ; computed locally in CALC_GW
408 c #endif
409
410 RETURN
411 END

  ViewVC Help
Powered by ViewVC 1.1.22