/[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.29 - (show annotations) (download)
Thu May 13 15:40:53 2004 UTC (20 years ago) by adcroft
Branch: MAIN
CVS Tags: checkpoint57g_pre, checkpoint57b_post, checkpoint57g_post, checkpoint56b_post, checkpoint54d_post, checkpoint54e_post, checkpoint57d_post, checkpoint57i_post, checkpoint55, checkpoint54, checkpoint57, checkpoint56, checkpoint54f_post, checkpoint55i_post, checkpoint57l_post, checkpoint55c_post, checkpoint57f_post, checkpoint53d_post, checkpoint57a_post, checkpoint57h_pre, checkpoint54b_post, checkpoint57h_post, checkpoint55g_post, checkpoint57c_post, checkpoint55d_post, checkpoint54a_pre, checkpoint53c_post, checkpoint55d_pre, checkpoint57c_pre, checkpoint55j_post, checkpoint54a_post, checkpoint55h_post, checkpoint57e_post, checkpoint55b_post, checkpoint55f_post, checkpoint53g_post, eckpoint57e_pre, checkpoint56a_post, checkpoint53f_post, checkpoint57h_done, checkpoint57j_post, checkpoint57f_pre, checkpoint53b_pre, checkpoint56c_post, checkpoint57a_pre, checkpoint55a_post, checkpoint57k_post, checkpoint53b_post, checkpoint53d_pre, checkpoint55e_post, checkpoint54c_post
Changes since 1.28: +8 -7 lines
Slight re-arrangment to satisfy JMC opinions on file names!
 o ini_mnc_io.F has been split and replaced by
     ini_model_io.F - responsible for setting units/flags for model-state i/o
     write_grid.F   - responsible for writing the grid variables to file
 o the passing of flags to MDSIO has been moved from ini_parms to ini_model_io
 o ini_depths and ini_masks_etc no longer do I/O which is now in write_grid

1 C $Header: /u/gcmpack/MITgcm/model/src/ini_masks_etc.F,v 1.28 2004/01/08 15:28:45 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 CEOP
56
57 C- Calculate lopping factor hFacC : over-estimate the part inside of the domain
58 C taking into account the lower_R Boundary (Bathymetrie / Top of Atmos)
59 DO bj=myByLo(myThid), myByHi(myThid)
60 DO bi=myBxLo(myThid), myBxHi(myThid)
61 DO K=1, Nr
62 hFacMnSz=max( hFacMin, min(hFacMinDr*recip_drF(k),1. _d 0) )
63 DO J=1-Oly,sNy+Oly
64 DO I=1-Olx,sNx+Olx
65 C o Non-dimensional distance between grid bound. and domain lower_R bound.
66 hFacCtmp = (rF(K)-R_low(I,J,bi,bj))*recip_drF(K)
67 C o Select between, closed, open or partial (0,1,0-1)
68 hFacCtmp=min( max( hFacCtmp, 0. _d 0) , 1. _d 0)
69 C o Impose minimum fraction and/or size (dimensional)
70 IF (hFacCtmp.LT.hFacMnSz) THEN
71 IF (hFacCtmp.LT.hFacMnSz*0.5) THEN
72 hFacC(I,J,K,bi,bj)=0.
73 ELSE
74 hFacC(I,J,K,bi,bj)=hFacMnSz
75 ENDIF
76 ELSE
77 hFacC(I,J,K,bi,bj)=hFacCtmp
78 ENDIF
79 ENDDO
80 ENDDO
81 ENDDO
82
83 C- Re-calculate lower-R Boundary position, taking into account hFacC
84 DO J=1-Oly,sNy+Oly
85 DO I=1-Olx,sNx+Olx
86 R_low(I,J,bi,bj) = rF(1)
87 DO K=Nr,1,-1
88 R_low(I,J,bi,bj) = R_low(I,J,bi,bj)
89 & - drF(k)*hFacC(I,J,K,bi,bj)
90 ENDDO
91 ENDDO
92 ENDDO
93 C - end bi,bj loops.
94 ENDDO
95 ENDDO
96
97 C- Calculate lopping factor hFacC : Remove part outside of the domain
98 C taking into account the Reference (=at rest) Surface Position Ro_surf
99 DO bj=myByLo(myThid), myByHi(myThid)
100 DO bi=myBxLo(myThid), myBxHi(myThid)
101 DO K=1, Nr
102 hFacMnSz=max( hFacMin, min(hFacMinDr*recip_drF(k),1. _d 0) )
103 DO J=1-Oly,sNy+Oly
104 DO I=1-Olx,sNx+Olx
105 C o Non-dimensional distance between grid boundary and model surface
106 hFacCtmp = (rF(k)-Ro_surf(I,J,bi,bj))*recip_drF(K)
107 C o Reduce the previous fraction : substract the outside part.
108 hFacCtmp = hFacC(I,J,K,bi,bj) - max( hFacCtmp, 0. _d 0)
109 C o set to zero if empty Column :
110 hFacCtmp = max( hFacCtmp, 0. _d 0)
111 C o Impose minimum fraction and/or size (dimensional)
112 IF (hFacCtmp.LT.hFacMnSz) THEN
113 IF (hFacCtmp.LT.hFacMnSz*0.5) THEN
114 hFacC(I,J,K,bi,bj)=0.
115 ELSE
116 hFacC(I,J,K,bi,bj)=hFacMnSz
117 ENDIF
118 ELSE
119 hFacC(I,J,K,bi,bj)=hFacCtmp
120 ENDIF
121 ENDDO
122 ENDDO
123 ENDDO
124
125 C- Re-calculate Reference surface position, taking into account hFacC
126 C initialize Total column fluid thickness and surface k index
127 C Note: if no fluid (continent) ==> ksurf = Nr+1
128 DO J=1-Oly,sNy+Oly
129 DO I=1-Olx,sNx+Olx
130 tmpfld(I,J,bi,bj) = 0.
131 ksurfC(I,J,bi,bj) = Nr+1
132 maskH(i,j,bi,bj) = 0.
133 Ro_surf(I,J,bi,bj) = R_low(I,J,bi,bj)
134 DO K=Nr,1,-1
135 Ro_surf(I,J,bi,bj) = Ro_surf(I,J,bi,bj)
136 & + drF(k)*hFacC(I,J,K,bi,bj)
137 IF (hFacC(I,J,K,bi,bj).NE.0.) THEN
138 ksurfC(I,J,bi,bj) = k
139 maskH(i,j,bi,bj) = 1.
140 tmpfld(i,j,bi,bj) = tmpfld(i,j,bi,bj) + 1.
141 ENDIF
142 ENDDO
143 kLowC(I,J,bi,bj) = 0
144 DO K= 1, Nr
145 IF (hFacC(I,J,K,bi,bj).NE.0) THEN
146 kLowC(I,J,bi,bj) = K
147 ENDIF
148 ENDDO
149 ENDDO
150 ENDDO
151 C - end bi,bj loops.
152 ENDDO
153 ENDDO
154
155 C CALL PLOT_FIELD_XYRS( tmpfld,
156 C & 'Model Depths K Index' , 1, myThid )
157 CALL PLOT_FIELD_XYRS(R_low,
158 & 'Model R_low (ini_masks_etc)', 1, myThid)
159 CALL PLOT_FIELD_XYRS(Ro_surf,
160 & 'Model Ro_surf (ini_masks_etc)', 1, myThid)
161
162 C Calculate quantities derived from XY depth map
163 DO bj = myByLo(myThid), myByHi(myThid)
164 DO bi = myBxLo(myThid), myBxHi(myThid)
165 DO j=1-Oly,sNy+Oly
166 DO i=1-Olx,sNx+Olx
167 C Total fluid column thickness (r_unit) :
168 c Rcolumn(i,j,bi,bj)= Ro_surf(i,j,bi,bj) - R_low(i,j,bi,bj)
169 tmpfld(i,j,bi,bj) = Ro_surf(i,j,bi,bj) - R_low(i,j,bi,bj)
170 C Inverse of fluid column thickness (1/r_unit)
171 IF ( tmpfld(i,j,bi,bj) .LE. 0. ) THEN
172 recip_Rcol(i,j,bi,bj) = 0.
173 ELSE
174 recip_Rcol(i,j,bi,bj) = 1. / tmpfld(i,j,bi,bj)
175 ENDIF
176 ENDDO
177 ENDDO
178 ENDDO
179 ENDDO
180 C _EXCH_XY_R4( recip_Rcol, myThid )
181
182 C hFacW and hFacS (at U and V points)
183 DO bj=myByLo(myThid), myByHi(myThid)
184 DO bi=myBxLo(myThid), myBxHi(myThid)
185 DO K=1, Nr
186 DO J=1-Oly,sNy+Oly
187 DO I=2-Olx,sNx+Olx
188 hFacW(I,J,K,bi,bj)=
189 & MIN(hFacC(I,J,K,bi,bj),hFacC(I-1,J,K,bi,bj))
190 ENDDO
191 ENDDO
192 DO J=2-Oly,sNy+oly
193 DO I=1-Olx,sNx+Olx
194 hFacS(I,J,K,bi,bj)=
195 & MIN(hFacC(I,J,K,bi,bj),hFacC(I,J-1,K,bi,bj))
196 ENDDO
197 ENDDO
198 ENDDO
199 ENDDO
200 ENDDO
201 CALL EXCH_UV_XYZ_RS(hFacW,hFacS,.FALSE.,myThid)
202 C The following block allows thin walls representation of non-periodic
203 C boundaries such as happen on the lat-lon grid at the N/S poles.
204 C We should really supply a flag for doing this.
205 DO bj=myByLo(myThid), myByHi(myThid)
206 DO bi=myBxLo(myThid), myBxHi(myThid)
207 DO K=1, Nr
208 DO J=1-Oly,sNy+Oly
209 DO I=1-Olx,sNx+Olx
210 IF (DYG(I,J,bi,bj).EQ.0.) hFacW(I,J,K,bi,bj)=0.
211 IF (DXG(I,J,bi,bj).EQ.0.) hFacS(I,J,K,bi,bj)=0.
212 ENDDO
213 ENDDO
214 ENDDO
215 ENDDO
216 ENDDO
217
218 C- Write to disk: Total Column Thickness & hFac(C,W,S):
219 _BARRIER
220 c _BEGIN_MASTER( myThid )
221 C This I/O is now done in write_grid.F
222 C CALL MDSWRITEFIELD( 'Depth', writeBinaryPrec, .TRUE.,
223 C & 'RS', 1, tmpfld, 1, -1, myThid )
224 c CALL WRITE_FLD_XY_RS( 'Depth',' ',tmpfld,0,myThid)
225 c CALL WRITE_FLD_XYZ_RS( 'hFacC',' ',hFacC,0,myThid)
226 c CALL WRITE_FLD_XYZ_RS( 'hFacW',' ',hFacW,0,myThid)
227 c CALL WRITE_FLD_XYZ_RS( 'hFacS',' ',hFacS,0,myThid)
228 c _END_MASTER(myThid)
229
230 CALL PLOT_FIELD_XYZRS( hFacC, 'hFacC' , Nr, 1, myThid )
231 CALL PLOT_FIELD_XYZRS( hFacW, 'hFacW' , Nr, 1, myThid )
232 CALL PLOT_FIELD_XYZRS( hFacS, 'hFacS' , Nr, 1, myThid )
233
234 C Masks and reciprocals of hFac[CWS]
235 DO bj = myByLo(myThid), myByHi(myThid)
236 DO bi = myBxLo(myThid), myBxHi(myThid)
237 DO K=1,Nr
238 DO J=1-Oly,sNy+Oly
239 DO I=1-Olx,sNx+Olx
240 IF (HFacC(I,J,K,bi,bj) .NE. 0. ) THEN
241 recip_HFacC(I,J,K,bi,bj) = 1. / HFacC(I,J,K,bi,bj)
242 maskC(I,J,K,bi,bj) = 1.
243 ELSE
244 recip_HFacC(I,J,K,bi,bj) = 0.
245 maskC(I,J,K,bi,bj) = 0.
246 ENDIF
247 IF (HFacW(I,J,K,bi,bj) .NE. 0. ) THEN
248 recip_HFacW(I,J,K,bi,bj) = 1. / HFacW(I,J,K,bi,bj)
249 maskW(I,J,K,bi,bj) = 1.
250 ELSE
251 recip_HFacW(I,J,K,bi,bj) = 0.
252 maskW(I,J,K,bi,bj) = 0.
253 ENDIF
254 IF (HFacS(I,J,K,bi,bj) .NE. 0. ) THEN
255 recip_HFacS(I,J,K,bi,bj) = 1. / HFacS(I,J,K,bi,bj)
256 maskS(I,J,K,bi,bj) = 1.
257 ELSE
258 recip_HFacS(I,J,K,bi,bj) = 0.
259 maskS(I,J,K,bi,bj) = 0.
260 ENDIF
261 ENDDO
262 ENDDO
263 ENDDO
264 C- Calculate surface k index for interface W & S (U & V points)
265 DO J=1-Oly,sNy+Oly
266 DO I=1-Olx,sNx+Olx
267 ksurfW(I,J,bi,bj) = Nr+1
268 ksurfS(I,J,bi,bj) = Nr+1
269 DO k=Nr,1,-1
270 IF (hFacW(I,J,K,bi,bj).NE.0.) ksurfW(I,J,bi,bj) = k
271 IF (hFacS(I,J,K,bi,bj).NE.0.) ksurfS(I,J,bi,bj) = k
272 ENDDO
273 ENDDO
274 ENDDO
275 C - end bi,bj loops.
276 ENDDO
277 ENDDO
278 C _EXCH_XYZ_R4(recip_HFacC , myThid )
279 C _EXCH_XYZ_R4(recip_HFacW , myThid )
280 C _EXCH_XYZ_R4(recip_HFacS , myThid )
281 C _EXCH_XYZ_R4(maskW , myThid )
282 C _EXCH_XYZ_R4(maskS , myThid )
283
284 C Calculate recipricols grid lengths
285 DO bj = myByLo(myThid), myByHi(myThid)
286 DO bi = myBxLo(myThid), myBxHi(myThid)
287 DO J=1-Oly,sNy+Oly
288 DO I=1-Olx,sNx+Olx
289 IF ( dxG(I,J,bi,bj) .NE. 0. )
290 & recip_dxG(I,J,bi,bj)=1.d0/dxG(I,J,bi,bj)
291 IF ( dyG(I,J,bi,bj) .NE. 0. )
292 & recip_dyG(I,J,bi,bj)=1.d0/dyG(I,J,bi,bj)
293 IF ( dxC(I,J,bi,bj) .NE. 0. )
294 & recip_dxC(I,J,bi,bj)=1.d0/dxC(I,J,bi,bj)
295 IF ( dyC(I,J,bi,bj) .NE. 0. )
296 & recip_dyC(I,J,bi,bj)=1.d0/dyC(I,J,bi,bj)
297 IF ( dxF(I,J,bi,bj) .NE. 0. )
298 & recip_dxF(I,J,bi,bj)=1.d0/dxF(I,J,bi,bj)
299 IF ( dyF(I,J,bi,bj) .NE. 0. )
300 & recip_dyF(I,J,bi,bj)=1.d0/dyF(I,J,bi,bj)
301 IF ( dxV(I,J,bi,bj) .NE. 0. )
302 & recip_dxV(I,J,bi,bj)=1.d0/dxV(I,J,bi,bj)
303 IF ( dyU(I,J,bi,bj) .NE. 0. )
304 & recip_dyU(I,J,bi,bj)=1.d0/dyU(I,J,bi,bj)
305 IF ( rA(I,J,bi,bj) .NE. 0. )
306 & recip_rA(I,J,bi,bj)=1.d0/rA(I,J,bi,bj)
307 IF ( rAs(I,J,bi,bj) .NE. 0. )
308 & recip_rAs(I,J,bi,bj)=1.d0/rAs(I,J,bi,bj)
309 IF ( rAw(I,J,bi,bj) .NE. 0. )
310 & recip_rAw(I,J,bi,bj)=1.d0/rAw(I,J,bi,bj)
311 IF ( rAz(I,J,bi,bj) .NE. 0. )
312 & recip_rAz(I,J,bi,bj)=1.d0/rAz(I,J,bi,bj)
313 ENDDO
314 ENDDO
315 ENDDO
316 ENDDO
317 C Do not need these since above denominators are valid over full range
318 C _EXCH_XY_R4(recip_dxG, myThid )
319 C _EXCH_XY_R4(recip_dyG, myThid )
320 C _EXCH_XY_R4(recip_dxC, myThid )
321 C _EXCH_XY_R4(recip_dyC, myThid )
322 C _EXCH_XY_R4(recip_dxF, myThid )
323 C _EXCH_XY_R4(recip_dyF, myThid )
324 C _EXCH_XY_R4(recip_dxV, myThid )
325 C _EXCH_XY_R4(recip_dyU, myThid )
326 C _EXCH_XY_R4(recip_rAw, myThid )
327 C _EXCH_XY_R4(recip_rAs, myThid )
328
329 #ifdef ALLOW_NONHYDROSTATIC
330 C-- Calculate the reciprocal hfac distance/volume for W cells
331 DO bj = myByLo(myThid), myByHi(myThid)
332 DO bi = myBxLo(myThid), myBxHi(myThid)
333 DO K=1,Nr
334 Km1=max(K-1,1)
335 hFacUpper=drF(Km1)/(drF(Km1)+drF(K))
336 IF (Km1.EQ.K) hFacUpper=0.
337 hFacLower=drF(K)/(drF(Km1)+drF(K))
338 DO J=1-Oly,sNy+Oly
339 DO I=1-Olx,sNx+Olx
340 IF (hFacC(I,J,K,bi,bj).NE.0.) THEN
341 IF (hFacC(I,J,K,bi,bj).LE.0.5) THEN
342 recip_hFacU(I,J,K,bi,bj)=
343 & hFacUpper+hFacLower*hFacC(I,J,K,bi,bj)
344 ELSE
345 recip_hFacU(I,J,K,bi,bj)=1.
346 ENDIF
347 ELSE
348 recip_hFacU(I,J,K,bi,bj)=0.
349 ENDIF
350 IF (recip_hFacU(I,J,K,bi,bj).NE.0.)
351 & recip_hFacU(I,J,K,bi,bj)=1./recip_hFacU(I,J,K,bi,bj)
352 ENDDO
353 ENDDO
354 ENDDO
355 ENDDO
356 ENDDO
357 C _EXCH_XY_R4(recip_hFacU, myThid )
358 #endif
359 C
360 RETURN
361 END

  ViewVC Help
Powered by ViewVC 1.1.22