/[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.30 - (show annotations) (download)
Wed Jul 20 22:31:47 2005 UTC (18 years, 10 months ago) by jmc
Branch: MAIN
CVS Tags: checkpoint57m_post, checkpoint57s_post, checkpoint57y_post, checkpoint57r_post, checkpoint58, checkpoint57n_post, checkpoint57z_post, checkpoint57t_post, checkpoint57v_post, checkpoint57y_pre, checkpoint57p_post, checkpint57u_post, checkpoint57q_post, checkpoint57o_post, checkpoint57w_post, checkpoint57x_post
Changes since 1.29: +12 -1 lines
compute Domain Integrated horizontal area (globalArea)

1 C $Header: /u/gcmpack/MITgcm/model/src/ini_masks_etc.F,v 1.29 2004/05/13 15:40:53 adcroft 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
33 C !INPUT/OUTPUT PARAMETERS:
34 C == Routine arguments ==
35 C myThid - Number of this instance of INI_MASKS_ETC
36 INTEGER myThid
37
38 C !LOCAL VARIABLES:
39 C == Local variables in common ==
40 C tmpfld - Temporary array used to compute & write Total Depth
41 C has to be in common for multi threading
42 COMMON / LOCAL_INI_MASKS_ETC / tmpfld
43 _RS tmpfld(1-OLx:sNx+OLx,1-OLy:sNy+OLy,nSx,nSy)
44 C == Local variables ==
45 C bi,bj - Loop counters
46 C I,J,K
47 INTEGER bi, bj
48 INTEGER I, J, K
49 #ifdef ALLOW_NONHYDROSTATIC
50 INTEGER Km1
51 _RL hFacUpper,hFacLower
52 #endif
53 _RL hFacCtmp
54 _RL hFacMnSz
55 _RL tileArea
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
126 C- Re-calculate Reference surface position, taking into account hFacC
127 C initialize Total column fluid thickness and surface k index
128 C Note: if no fluid (continent) ==> ksurf = Nr+1
129 DO J=1-Oly,sNy+Oly
130 DO I=1-Olx,sNx+Olx
131 tmpfld(I,J,bi,bj) = 0.
132 ksurfC(I,J,bi,bj) = Nr+1
133 maskH(i,j,bi,bj) = 0.
134 Ro_surf(I,J,bi,bj) = R_low(I,J,bi,bj)
135 DO K=Nr,1,-1
136 Ro_surf(I,J,bi,bj) = Ro_surf(I,J,bi,bj)
137 & + drF(k)*hFacC(I,J,K,bi,bj)
138 IF (hFacC(I,J,K,bi,bj).NE.0.) THEN
139 ksurfC(I,J,bi,bj) = k
140 maskH(i,j,bi,bj) = 1.
141 tmpfld(i,j,bi,bj) = tmpfld(i,j,bi,bj) + 1.
142 ENDIF
143 ENDDO
144 kLowC(I,J,bi,bj) = 0
145 DO K= 1, Nr
146 IF (hFacC(I,J,K,bi,bj).NE.0) THEN
147 kLowC(I,J,bi,bj) = K
148 ENDIF
149 ENDDO
150 ENDDO
151 ENDDO
152 C - end bi,bj loops.
153 ENDDO
154 ENDDO
155
156 C CALL PLOT_FIELD_XYRS( tmpfld,
157 C & 'Model Depths K Index' , 1, myThid )
158 CALL PLOT_FIELD_XYRS(R_low,
159 & 'Model R_low (ini_masks_etc)', 1, myThid)
160 CALL PLOT_FIELD_XYRS(Ro_surf,
161 & 'Model Ro_surf (ini_masks_etc)', 1, myThid)
162
163 C Calculate quantities derived from XY depth map
164 globalArea = 0. _d 0
165 DO bj = myByLo(myThid), myByHi(myThid)
166 DO bi = myBxLo(myThid), myBxHi(myThid)
167 DO j=1-Oly,sNy+Oly
168 DO i=1-Olx,sNx+Olx
169 C Total fluid column thickness (r_unit) :
170 c Rcolumn(i,j,bi,bj)= Ro_surf(i,j,bi,bj) - R_low(i,j,bi,bj)
171 tmpfld(i,j,bi,bj) = Ro_surf(i,j,bi,bj) - R_low(i,j,bi,bj)
172 C Inverse of fluid column thickness (1/r_unit)
173 IF ( tmpfld(i,j,bi,bj) .LE. 0. ) THEN
174 recip_Rcol(i,j,bi,bj) = 0.
175 ELSE
176 recip_Rcol(i,j,bi,bj) = 1. / tmpfld(i,j,bi,bj)
177 ENDIF
178 ENDDO
179 ENDDO
180 C- Compute the domain Area:
181 tileArea = 0. _d 0
182 DO j=1,sNy
183 DO i=1,sNx
184 tileArea = tileArea + rA(i,j,bi,bj)*maskH(i,j,bi,bj)
185 ENDDO
186 ENDDO
187 globalArea = globalArea + tileArea
188 ENDDO
189 ENDDO
190 C _EXCH_XY_R4( recip_Rcol, myThid )
191 _GLOBAL_SUM_R8( globalArea, myThid )
192
193 C hFacW and hFacS (at U and V points)
194 DO bj=myByLo(myThid), myByHi(myThid)
195 DO bi=myBxLo(myThid), myBxHi(myThid)
196 DO K=1, Nr
197 DO J=1-Oly,sNy+Oly
198 DO I=2-Olx,sNx+Olx
199 hFacW(I,J,K,bi,bj)=
200 & MIN(hFacC(I,J,K,bi,bj),hFacC(I-1,J,K,bi,bj))
201 ENDDO
202 ENDDO
203 DO J=2-Oly,sNy+oly
204 DO I=1-Olx,sNx+Olx
205 hFacS(I,J,K,bi,bj)=
206 & MIN(hFacC(I,J,K,bi,bj),hFacC(I,J-1,K,bi,bj))
207 ENDDO
208 ENDDO
209 ENDDO
210 ENDDO
211 ENDDO
212 CALL EXCH_UV_XYZ_RS(hFacW,hFacS,.FALSE.,myThid)
213 C The following block allows thin walls representation of non-periodic
214 C boundaries such as happen on the lat-lon grid at the N/S poles.
215 C We should really supply a flag for doing this.
216 DO bj=myByLo(myThid), myByHi(myThid)
217 DO bi=myBxLo(myThid), myBxHi(myThid)
218 DO K=1, Nr
219 DO J=1-Oly,sNy+Oly
220 DO I=1-Olx,sNx+Olx
221 IF (DYG(I,J,bi,bj).EQ.0.) hFacW(I,J,K,bi,bj)=0.
222 IF (DXG(I,J,bi,bj).EQ.0.) hFacS(I,J,K,bi,bj)=0.
223 ENDDO
224 ENDDO
225 ENDDO
226 ENDDO
227 ENDDO
228
229 C- Write to disk: Total Column Thickness & hFac(C,W,S):
230 _BARRIER
231 c _BEGIN_MASTER( myThid )
232 C This I/O is now done in write_grid.F
233 C CALL MDSWRITEFIELD( 'Depth', writeBinaryPrec, .TRUE.,
234 C & 'RS', 1, tmpfld, 1, -1, myThid )
235 c CALL WRITE_FLD_XY_RS( 'Depth',' ',tmpfld,0,myThid)
236 c CALL WRITE_FLD_XYZ_RS( 'hFacC',' ',hFacC,0,myThid)
237 c CALL WRITE_FLD_XYZ_RS( 'hFacW',' ',hFacW,0,myThid)
238 c CALL WRITE_FLD_XYZ_RS( 'hFacS',' ',hFacS,0,myThid)
239 c _END_MASTER(myThid)
240
241 CALL PLOT_FIELD_XYZRS( hFacC, 'hFacC' , Nr, 1, myThid )
242 CALL PLOT_FIELD_XYZRS( hFacW, 'hFacW' , Nr, 1, myThid )
243 CALL PLOT_FIELD_XYZRS( hFacS, 'hFacS' , Nr, 1, myThid )
244
245 C Masks and reciprocals of hFac[CWS]
246 DO bj = myByLo(myThid), myByHi(myThid)
247 DO bi = myBxLo(myThid), myBxHi(myThid)
248 DO K=1,Nr
249 DO J=1-Oly,sNy+Oly
250 DO I=1-Olx,sNx+Olx
251 IF (HFacC(I,J,K,bi,bj) .NE. 0. ) THEN
252 recip_HFacC(I,J,K,bi,bj) = 1. / HFacC(I,J,K,bi,bj)
253 maskC(I,J,K,bi,bj) = 1.
254 ELSE
255 recip_HFacC(I,J,K,bi,bj) = 0.
256 maskC(I,J,K,bi,bj) = 0.
257 ENDIF
258 IF (HFacW(I,J,K,bi,bj) .NE. 0. ) THEN
259 recip_HFacW(I,J,K,bi,bj) = 1. / HFacW(I,J,K,bi,bj)
260 maskW(I,J,K,bi,bj) = 1.
261 ELSE
262 recip_HFacW(I,J,K,bi,bj) = 0.
263 maskW(I,J,K,bi,bj) = 0.
264 ENDIF
265 IF (HFacS(I,J,K,bi,bj) .NE. 0. ) THEN
266 recip_HFacS(I,J,K,bi,bj) = 1. / HFacS(I,J,K,bi,bj)
267 maskS(I,J,K,bi,bj) = 1.
268 ELSE
269 recip_HFacS(I,J,K,bi,bj) = 0.
270 maskS(I,J,K,bi,bj) = 0.
271 ENDIF
272 ENDDO
273 ENDDO
274 ENDDO
275 C- Calculate surface k index for interface W & S (U & V points)
276 DO J=1-Oly,sNy+Oly
277 DO I=1-Olx,sNx+Olx
278 ksurfW(I,J,bi,bj) = Nr+1
279 ksurfS(I,J,bi,bj) = Nr+1
280 DO k=Nr,1,-1
281 IF (hFacW(I,J,K,bi,bj).NE.0.) ksurfW(I,J,bi,bj) = k
282 IF (hFacS(I,J,K,bi,bj).NE.0.) ksurfS(I,J,bi,bj) = k
283 ENDDO
284 ENDDO
285 ENDDO
286 C - end bi,bj loops.
287 ENDDO
288 ENDDO
289 C _EXCH_XYZ_R4(recip_HFacC , myThid )
290 C _EXCH_XYZ_R4(recip_HFacW , myThid )
291 C _EXCH_XYZ_R4(recip_HFacS , myThid )
292 C _EXCH_XYZ_R4(maskW , myThid )
293 C _EXCH_XYZ_R4(maskS , myThid )
294
295 C Calculate recipricols grid lengths
296 DO bj = myByLo(myThid), myByHi(myThid)
297 DO bi = myBxLo(myThid), myBxHi(myThid)
298 DO J=1-Oly,sNy+Oly
299 DO I=1-Olx,sNx+Olx
300 IF ( dxG(I,J,bi,bj) .NE. 0. )
301 & recip_dxG(I,J,bi,bj)=1.d0/dxG(I,J,bi,bj)
302 IF ( dyG(I,J,bi,bj) .NE. 0. )
303 & recip_dyG(I,J,bi,bj)=1.d0/dyG(I,J,bi,bj)
304 IF ( dxC(I,J,bi,bj) .NE. 0. )
305 & recip_dxC(I,J,bi,bj)=1.d0/dxC(I,J,bi,bj)
306 IF ( dyC(I,J,bi,bj) .NE. 0. )
307 & recip_dyC(I,J,bi,bj)=1.d0/dyC(I,J,bi,bj)
308 IF ( dxF(I,J,bi,bj) .NE. 0. )
309 & recip_dxF(I,J,bi,bj)=1.d0/dxF(I,J,bi,bj)
310 IF ( dyF(I,J,bi,bj) .NE. 0. )
311 & recip_dyF(I,J,bi,bj)=1.d0/dyF(I,J,bi,bj)
312 IF ( dxV(I,J,bi,bj) .NE. 0. )
313 & recip_dxV(I,J,bi,bj)=1.d0/dxV(I,J,bi,bj)
314 IF ( dyU(I,J,bi,bj) .NE. 0. )
315 & recip_dyU(I,J,bi,bj)=1.d0/dyU(I,J,bi,bj)
316 IF ( rA(I,J,bi,bj) .NE. 0. )
317 & recip_rA(I,J,bi,bj)=1.d0/rA(I,J,bi,bj)
318 IF ( rAs(I,J,bi,bj) .NE. 0. )
319 & recip_rAs(I,J,bi,bj)=1.d0/rAs(I,J,bi,bj)
320 IF ( rAw(I,J,bi,bj) .NE. 0. )
321 & recip_rAw(I,J,bi,bj)=1.d0/rAw(I,J,bi,bj)
322 IF ( rAz(I,J,bi,bj) .NE. 0. )
323 & recip_rAz(I,J,bi,bj)=1.d0/rAz(I,J,bi,bj)
324 ENDDO
325 ENDDO
326 ENDDO
327 ENDDO
328 C Do not need these since above denominators are valid over full range
329 C _EXCH_XY_R4(recip_dxG, myThid )
330 C _EXCH_XY_R4(recip_dyG, myThid )
331 C _EXCH_XY_R4(recip_dxC, myThid )
332 C _EXCH_XY_R4(recip_dyC, myThid )
333 C _EXCH_XY_R4(recip_dxF, myThid )
334 C _EXCH_XY_R4(recip_dyF, myThid )
335 C _EXCH_XY_R4(recip_dxV, myThid )
336 C _EXCH_XY_R4(recip_dyU, myThid )
337 C _EXCH_XY_R4(recip_rAw, myThid )
338 C _EXCH_XY_R4(recip_rAs, myThid )
339
340 #ifdef ALLOW_NONHYDROSTATIC
341 C-- Calculate the reciprocal hfac distance/volume for W cells
342 DO bj = myByLo(myThid), myByHi(myThid)
343 DO bi = myBxLo(myThid), myBxHi(myThid)
344 DO K=1,Nr
345 Km1=max(K-1,1)
346 hFacUpper=drF(Km1)/(drF(Km1)+drF(K))
347 IF (Km1.EQ.K) hFacUpper=0.
348 hFacLower=drF(K)/(drF(Km1)+drF(K))
349 DO J=1-Oly,sNy+Oly
350 DO I=1-Olx,sNx+Olx
351 IF (hFacC(I,J,K,bi,bj).NE.0.) THEN
352 IF (hFacC(I,J,K,bi,bj).LE.0.5) THEN
353 recip_hFacU(I,J,K,bi,bj)=
354 & hFacUpper+hFacLower*hFacC(I,J,K,bi,bj)
355 ELSE
356 recip_hFacU(I,J,K,bi,bj)=1.
357 ENDIF
358 ELSE
359 recip_hFacU(I,J,K,bi,bj)=0.
360 ENDIF
361 IF (recip_hFacU(I,J,K,bi,bj).NE.0.)
362 & recip_hFacU(I,J,K,bi,bj)=1./recip_hFacU(I,J,K,bi,bj)
363 ENDDO
364 ENDDO
365 ENDDO
366 ENDDO
367 ENDDO
368 C _EXCH_XY_R4(recip_hFacU, myThid )
369 #endif
370 C
371 RETURN
372 END

  ViewVC Help
Powered by ViewVC 1.1.22