/[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.25 - (show annotations) (download)
Thu Nov 8 16:36:12 2001 UTC (22 years, 6 months ago) by jmc
Branch: MAIN
CVS Tags: checkpoint44e_post, checkpoint46g_pre, checkpoint46f_post, checkpoint44f_post, checkpoint46b_post, checkpoint43a-release1mods, chkpt44d_post, checkpoint44e_pre, checkpoint46d_pre, release1-branch_tutorials, checkpoint45d_post, chkpt44a_post, checkpoint44h_pre, checkpoint46a_post, chkpt44c_pre, checkpoint45a_post, checkpoint44g_post, checkpoint46e_pre, checkpoint45b_post, checkpoint46b_pre, release1-branch-end, release1_final_v1, checkpoint46c_pre, checkpoint46, checkpoint44b_post, checkpoint46a_pre, checkpoint45c_post, checkpoint44h_post, chkpt44a_pre, checkpoint46c_post, checkpoint46e_post, checkpoint44b_pre, checkpoint44, checkpoint45, chkpt44c_post, checkpoint44f_pre, checkpoint46d_post, release1-branch_branchpoint
Branch point for: release1_final, release1-branch
Changes since 1.24: +3 -1 lines
add a 2D full-column mask

1 C $Header: /u/gcmpack/models/MITgcmUV/model/src/ini_masks_etc.F,v 1.24 2001/09/26 18:09:15 cnh Exp $
2 C $Name: $
3
4 #include "CPP_OPTIONS.h"
5
6 CBOP
7 C !ROUTINE: INI_MASKS_ETC
8 C !INTERFACE:
9 SUBROUTINE INI_MASKS_ETC( myThid )
10 C !DESCRIPTION: \bv
11 C *==========================================================*
12 C | SUBROUTINE INI_MASKS_ETC
13 C | o Initialise masks and topography factors
14 C *==========================================================*
15 C | These arrays are used throughout the code and describe
16 C | the topography of the domain through masks (0s and 1s)
17 C | and fractional height factors (0<hFac<1). The latter
18 C | distinguish between the lopped-cell and full-step
19 C | topographic representations.
20 C *==========================================================*
21 C \ev
22
23 C !USES:
24 IMPLICIT NONE
25 C === Global variables ===
26 #include "SIZE.h"
27 #include "EEPARAMS.h"
28 #include "PARAMS.h"
29 #include "GRID.h"
30 #include "SURFACE.h"
31
32 C !INPUT/OUTPUT PARAMETERS:
33 C == Routine arguments ==
34 C myThid - Number of this instance of INI_MASKS_ETC
35 INTEGER myThid
36
37 C !LOCAL VARIABLES:
38 C == Local variables in common ==
39 C tmpfld - Temporary array used to compute & write Total Depth
40 C has to be in common for multi threading
41 COMMON / LOCAL_INI_MASKS_ETC / tmpfld
42 _RS tmpfld(1-OLx:sNx+OLx,1-OLy:sNy+OLy,nSx,nSy)
43 C == Local variables ==
44 C bi,bj - Loop counters
45 C I,J,K
46 INTEGER bi, bj
47 INTEGER I, J, K
48 #ifdef ALLOW_NONHYDROSTATIC
49 INTEGER Km1
50 _RL hFacUpper,hFacLower
51 #endif
52 _RL hFacCtmp
53 _RL hFacMnSz
54 CEOP
55
56 C- Calculate lopping factor hFacC : over-estimate the part inside of the domain
57 C taking into account the lower_R Boundary (Bathymetrie / Top of Atmos)
58 DO bj=myByLo(myThid), myByHi(myThid)
59 DO bi=myBxLo(myThid), myBxHi(myThid)
60 DO K=1, Nr
61 hFacMnSz=max( hFacMin, min(hFacMinDr*recip_drF(k),1. _d 0) )
62 DO J=1-Oly,sNy+Oly
63 DO I=1-Olx,sNx+Olx
64 C o Non-dimensional distance between grid bound. and domain lower_R bound.
65 hFacCtmp = (rF(K)-R_low(I,J,bi,bj))*recip_drF(K)
66 C o Select between, closed, open or partial (0,1,0-1)
67 hFacCtmp=min( max( hFacCtmp, 0. _d 0) , 1. _d 0)
68 C o Impose minimum fraction and/or size (dimensional)
69 IF (hFacCtmp.LT.hFacMnSz) THEN
70 IF (hFacCtmp.LT.hFacMnSz*0.5) THEN
71 hFacC(I,J,K,bi,bj)=0.
72 ELSE
73 hFacC(I,J,K,bi,bj)=hFacMnSz
74 ENDIF
75 ELSE
76 hFacC(I,J,K,bi,bj)=hFacCtmp
77 ENDIF
78 ENDDO
79 ENDDO
80 ENDDO
81
82 C- Re-calculate lower-R Boundary position, taking into account hFacC
83 DO J=1-Oly,sNy+Oly
84 DO I=1-Olx,sNx+Olx
85 R_low(I,J,bi,bj) = rF(1)
86 DO K=Nr,1,-1
87 R_low(I,J,bi,bj) = R_low(I,J,bi,bj)
88 & - drF(k)*hFacC(I,J,K,bi,bj)
89 ENDDO
90 ENDDO
91 ENDDO
92 C - end bi,bj loops.
93 ENDDO
94 ENDDO
95
96 C- Calculate lopping factor hFacC : Remove part outside of the domain
97 C taking into account the Reference (=at rest) Surface Position Ro_surf
98 DO bj=myByLo(myThid), myByHi(myThid)
99 DO bi=myBxLo(myThid), myBxHi(myThid)
100 DO K=1, Nr
101 hFacMnSz=max( hFacMin, min(hFacMinDr*recip_drF(k),1. _d 0) )
102 DO J=1-Oly,sNy+Oly
103 DO I=1-Olx,sNx+Olx
104 C o Non-dimensional distance between grid boundary and model surface
105 hFacCtmp = (rF(k)-Ro_surf(I,J,bi,bj))*recip_drF(K)
106 C o Reduce the previous fraction : substract the outside part.
107 hFacCtmp = hFacC(I,J,K,bi,bj) - max( hFacCtmp, 0. _d 0)
108 C o set to zero if empty Column :
109 hFacCtmp = max( hFacCtmp, 0. _d 0)
110 C o Impose minimum fraction and/or size (dimensional)
111 IF (hFacCtmp.LT.hFacMnSz) THEN
112 IF (hFacCtmp.LT.hFacMnSz*0.5) THEN
113 hFacC(I,J,K,bi,bj)=0.
114 ELSE
115 hFacC(I,J,K,bi,bj)=hFacMnSz
116 ENDIF
117 ELSE
118 hFacC(I,J,K,bi,bj)=hFacCtmp
119 ENDIF
120 ENDDO
121 ENDDO
122 ENDDO
123
124 C- Re-calculate Reference surface position, taking into account hFacC
125 C initialize Total column fluid thickness and surface k index
126 C Note: if no fluid (continent) ==> ksurf = Nr+1
127 DO J=1-Oly,sNy+Oly
128 DO I=1-Olx,sNx+Olx
129 tmpfld(I,J,bi,bj) = 0.
130 ksurfC(I,J,bi,bj) = Nr+1
131 maskH(i,j,bi,bj) = 0.
132 Ro_surf(I,J,bi,bj) = R_low(I,J,bi,bj)
133 DO K=Nr,1,-1
134 Ro_surf(I,J,bi,bj) = Ro_surf(I,J,bi,bj)
135 & + drF(k)*hFacC(I,J,K,bi,bj)
136 IF (hFacC(I,J,K,bi,bj).NE.0.) THEN
137 ksurfC(I,J,bi,bj) = k
138 maskH(i,j,bi,bj) = 1.
139 tmpfld(i,j,bi,bj) = tmpfld(i,j,bi,bj) + 1.
140 ENDIF
141 ENDDO
142 ENDDO
143 ENDDO
144 C - end bi,bj loops.
145 ENDDO
146 ENDDO
147
148 C CALL PLOT_FIELD_XYRS( tmpfld,
149 C & 'Model Depths K Index' , 1, myThid )
150 CALL PLOT_FIELD_XYRS(R_low,
151 & 'Model R_low (ini_masks_etc)', 1, myThid)
152 CALL PLOT_FIELD_XYRS(Ro_surf,
153 & 'Model Ro_surf (ini_masks_etc)', 1, myThid)
154
155 C Calculate quantities derived from XY depth map
156 DO bj = myByLo(myThid), myByHi(myThid)
157 DO bi = myBxLo(myThid), myBxHi(myThid)
158 DO j=1-Oly,sNy+Oly
159 DO i=1-Olx,sNx+Olx
160 C Total fluid column thickness (r_unit) :
161 c Rcolumn(i,j,bi,bj)= Ro_surf(i,j,bi,bj) - R_low(i,j,bi,bj)
162 tmpfld(i,j,bi,bj) = Ro_surf(i,j,bi,bj) - R_low(i,j,bi,bj)
163 C Inverse of fluid column thickness (1/r_unit)
164 IF ( tmpfld(i,j,bi,bj) .LE. 0. ) THEN
165 recip_Rcol(i,j,bi,bj) = 0.
166 ELSE
167 recip_Rcol(i,j,bi,bj) = 1. / tmpfld(i,j,bi,bj)
168 ENDIF
169 ENDDO
170 ENDDO
171 ENDDO
172 ENDDO
173 C _EXCH_XY_R4( recip_Rcol, myThid )
174
175 C hFacW and hFacS (at U and V points)
176 DO bj=myByLo(myThid), myByHi(myThid)
177 DO bi=myBxLo(myThid), myBxHi(myThid)
178 DO K=1, Nr
179 DO J=1,sNy
180 DO I=1,sNx
181 hFacW(I,J,K,bi,bj)=
182 & MIN(hFacC(I,J,K,bi,bj),hFacC(I-1,J,K,bi,bj))
183 hFacS(I,J,K,bi,bj)=
184 & MIN(hFacC(I,J,K,bi,bj),hFacC(I,J-1,K,bi,bj))
185 ENDDO
186 ENDDO
187 ENDDO
188 ENDDO
189 ENDDO
190 CALL EXCH_UV_XYZ_RS(hFacW,hFacS,.FALSE.,myThid)
191 C The following block allows thin walls representation of non-periodic
192 C boundaries such as happen on the lat-lon grid at the N/S poles.
193 C We should really supply a flag for doing this.
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=1-Olx,sNx+Olx
199 IF (DYG(I,J,bi,bj).EQ.0.) hFacW(I,J,K,bi,bj)=0.
200 IF (DXG(I,J,bi,bj).EQ.0.) hFacS(I,J,K,bi,bj)=0.
201 ENDDO
202 ENDDO
203 ENDDO
204 ENDDO
205 ENDDO
206
207 C- Write to disk: Total Column Thickness & hFac(C,W,S):
208 _BARRIER
209 _BEGIN_MASTER( myThid )
210 C CALL MDSWRITEFIELD( 'Depth', writeBinaryPrec, .TRUE.,
211 C & 'RS', 1, tmpfld, 1, -1, myThid )
212 CALL WRITE_FLD_XY_RS( 'Depth',' ',tmpfld,0,myThid)
213 CALL WRITE_FLD_XYZ_RS( 'hFacC',' ',hFacC,0,myThid)
214 CALL WRITE_FLD_XYZ_RS( 'hFacW',' ',hFacW,0,myThid)
215 CALL WRITE_FLD_XYZ_RS( 'hFacS',' ',hFacS,0,myThid)
216 _END_MASTER(myThid)
217
218 CALL PLOT_FIELD_XYZRS( hFacC, 'hFacC' , Nr, 1, myThid )
219 CALL PLOT_FIELD_XYZRS( hFacW, 'hFacW' , Nr, 1, myThid )
220 CALL PLOT_FIELD_XYZRS( hFacS, 'hFacS' , Nr, 1, myThid )
221
222 C Masks and reciprocals of hFac[CWS]
223 DO bj = myByLo(myThid), myByHi(myThid)
224 DO bi = myBxLo(myThid), myBxHi(myThid)
225 DO K=1,Nr
226 DO J=1-Oly,sNy+Oly
227 DO I=1-Olx,sNx+Olx
228 IF (HFacC(I,J,K,bi,bj) .NE. 0. ) THEN
229 recip_HFacC(I,J,K,bi,bj) = 1. / HFacC(I,J,K,bi,bj)
230 maskC(I,J,K,bi,bj) = 1.
231 ELSE
232 recip_HFacC(I,J,K,bi,bj) = 0.
233 maskC(I,J,K,bi,bj) = 0.
234 ENDIF
235 IF (HFacW(I,J,K,bi,bj) .NE. 0. ) THEN
236 recip_HFacW(I,J,K,bi,bj) = 1. / HFacW(I,J,K,bi,bj)
237 maskW(I,J,K,bi,bj) = 1.
238 ELSE
239 recip_HFacW(I,J,K,bi,bj) = 0.
240 maskW(I,J,K,bi,bj) = 0.
241 ENDIF
242 IF (HFacS(I,J,K,bi,bj) .NE. 0. ) THEN
243 recip_HFacS(I,J,K,bi,bj) = 1. / HFacS(I,J,K,bi,bj)
244 maskS(I,J,K,bi,bj) = 1.
245 ELSE
246 recip_HFacS(I,J,K,bi,bj) = 0.
247 maskS(I,J,K,bi,bj) = 0.
248 ENDIF
249 ENDDO
250 ENDDO
251 ENDDO
252 C- Calculate surface k index for interface W & S (U & V points)
253 DO J=1-Oly,sNy+Oly
254 DO I=1-Olx,sNx+Olx
255 ksurfW(I,J,bi,bj) = Nr+1
256 ksurfS(I,J,bi,bj) = Nr+1
257 DO k=Nr,1,-1
258 IF (hFacW(I,J,K,bi,bj).NE.0.) ksurfW(I,J,bi,bj) = k
259 IF (hFacS(I,J,K,bi,bj).NE.0.) ksurfS(I,J,bi,bj) = k
260 ENDDO
261 ENDDO
262 ENDDO
263 C - end bi,bj loops.
264 ENDDO
265 ENDDO
266 C _EXCH_XYZ_R4(recip_HFacC , myThid )
267 C _EXCH_XYZ_R4(recip_HFacW , myThid )
268 C _EXCH_XYZ_R4(recip_HFacS , myThid )
269 C _EXCH_XYZ_R4(maskW , myThid )
270 C _EXCH_XYZ_R4(maskS , myThid )
271
272 C Calculate recipricols grid lengths
273 DO bj = myByLo(myThid), myByHi(myThid)
274 DO bi = myBxLo(myThid), myBxHi(myThid)
275 DO J=1-Oly,sNy+Oly
276 DO I=1-Olx,sNx+Olx
277 IF ( dxG(I,J,bi,bj) .NE. 0. )
278 & recip_dxG(I,J,bi,bj)=1.d0/dxG(I,J,bi,bj)
279 IF ( dyG(I,J,bi,bj) .NE. 0. )
280 & recip_dyG(I,J,bi,bj)=1.d0/dyG(I,J,bi,bj)
281 IF ( dxC(I,J,bi,bj) .NE. 0. )
282 & recip_dxC(I,J,bi,bj)=1.d0/dxC(I,J,bi,bj)
283 IF ( dyC(I,J,bi,bj) .NE. 0. )
284 & recip_dyC(I,J,bi,bj)=1.d0/dyC(I,J,bi,bj)
285 IF ( dxF(I,J,bi,bj) .NE. 0. )
286 & recip_dxF(I,J,bi,bj)=1.d0/dxF(I,J,bi,bj)
287 IF ( dyF(I,J,bi,bj) .NE. 0. )
288 & recip_dyF(I,J,bi,bj)=1.d0/dyF(I,J,bi,bj)
289 IF ( dxV(I,J,bi,bj) .NE. 0. )
290 & recip_dxV(I,J,bi,bj)=1.d0/dxV(I,J,bi,bj)
291 IF ( dyU(I,J,bi,bj) .NE. 0. )
292 & recip_dyU(I,J,bi,bj)=1.d0/dyU(I,J,bi,bj)
293 IF ( rA(I,J,bi,bj) .NE. 0. )
294 & recip_rA(I,J,bi,bj)=1.d0/rA(I,J,bi,bj)
295 IF ( rAs(I,J,bi,bj) .NE. 0. )
296 & recip_rAs(I,J,bi,bj)=1.d0/rAs(I,J,bi,bj)
297 IF ( rAw(I,J,bi,bj) .NE. 0. )
298 & recip_rAw(I,J,bi,bj)=1.d0/rAw(I,J,bi,bj)
299 IF ( rAz(I,J,bi,bj) .NE. 0. )
300 & recip_rAz(I,J,bi,bj)=1.d0/rAz(I,J,bi,bj)
301 ENDDO
302 ENDDO
303 ENDDO
304 ENDDO
305 C Do not need these since above denominators are valid over full range
306 C _EXCH_XY_R4(recip_dxG, myThid )
307 C _EXCH_XY_R4(recip_dyG, myThid )
308 C _EXCH_XY_R4(recip_dxC, myThid )
309 C _EXCH_XY_R4(recip_dyC, myThid )
310 C _EXCH_XY_R4(recip_dxF, myThid )
311 C _EXCH_XY_R4(recip_dyF, myThid )
312 C _EXCH_XY_R4(recip_dxV, myThid )
313 C _EXCH_XY_R4(recip_dyU, myThid )
314 C _EXCH_XY_R4(recip_rAw, myThid )
315 C _EXCH_XY_R4(recip_rAs, myThid )
316
317 #ifdef ALLOW_NONHYDROSTATIC
318 C-- Calculate the reciprocal hfac distance/volume for W cells
319 DO bj = myByLo(myThid), myByHi(myThid)
320 DO bi = myBxLo(myThid), myBxHi(myThid)
321 DO K=1,Nr
322 Km1=max(K-1,1)
323 hFacUpper=drF(Km1)/(drF(Km1)+drF(K))
324 IF (Km1.EQ.K) hFacUpper=0.
325 hFacLower=drF(K)/(drF(Km1)+drF(K))
326 DO J=1-Oly,sNy+Oly
327 DO I=1-Olx,sNx+Olx
328 IF (hFacC(I,J,K,bi,bj).NE.0.) THEN
329 IF (hFacC(I,J,K,bi,bj).LE.0.5) THEN
330 recip_hFacU(I,J,K,bi,bj)=
331 & hFacUpper+hFacLower*hFacC(I,J,K,bi,bj)
332 ELSE
333 recip_hFacU(I,J,K,bi,bj)=1.
334 ENDIF
335 ELSE
336 recip_hFacU(I,J,K,bi,bj)=0.
337 ENDIF
338 IF (recip_hFacU(I,J,K,bi,bj).NE.0.)
339 & recip_hFacU(I,J,K,bi,bj)=1./recip_hFacU(I,J,K,bi,bj)
340 ENDDO
341 ENDDO
342 ENDDO
343 ENDDO
344 ENDDO
345 C _EXCH_XY_R4(recip_hFacU, myThid )
346 #endif
347 C
348 RETURN
349 END

  ViewVC Help
Powered by ViewVC 1.1.22