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

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

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


Revision 1.42 - (show annotations) (download)
Fri Sep 12 07:22:34 2008 UTC (15 years, 8 months ago) by mlosch
Branch: MAIN
CVS Tags: checkpoint61d
Changes since 1.41: +1 -8 lines
clean up the mess:
remove call of removed subroutine shelfice_ini_depth

1 C $Header: /u/gcmpack/MITgcm/model/src/ini_depths.F,v 1.41 2008/09/10 09:19:22 mlosch Exp $
2 C $Name: $
3
4 #include "PACKAGES_CONFIG.h"
5 #include "CPP_OPTIONS.h"
6
7 CBOP
8 C !ROUTINE: INI_DEPTHS
9 C !INTERFACE:
10 SUBROUTINE INI_DEPTHS( myThid )
11 C !DESCRIPTION: \bv
12 C *==========================================================*
13 C | SUBROUTINE INI_DEPTHS
14 C | o define R_position of Lower and Surface Boundaries
15 C *==========================================================*
16 C |atmosphere orography:
17 C | define either in term of P_topo or converted from Z_topo
18 C |ocean bathymetry:
19 C | The depths of the bottom of the model is specified in
20 C | terms of an XY map with one depth for each column of
21 C | grid cells. Depths do not have to coincide with the
22 C | model levels. The model lopping algorithm makes it
23 C | possible to represent arbitrary depths.
24 C | The mode depths map also influences the models topology
25 C | By default the model domain wraps around in X and Y.
26 C | This default doubly periodic topology is "supressed"
27 C | if a depth map is defined which closes off all wrap
28 C | around flow.
29 C *==========================================================*
30 C \ev
31
32 C !USES:
33 IMPLICIT NONE
34 C === Global variables ===
35 #include "SIZE.h"
36 #include "EEPARAMS.h"
37 #include "PARAMS.h"
38 #include "GRID.h"
39 #include "SURFACE.h"
40 #ifdef ALLOW_MNC
41 # include "MNC_PARAMS.h"
42 #endif
43
44 C !INPUT/OUTPUT PARAMETERS:
45 C == Routine arguments ==
46 C myThid - Number of this instance of INI_DEPTHS
47 INTEGER myThid
48 CEndOfInterface
49
50 C !LOCAL VARIABLES:
51 C == Local variables ==
52 C iG, jG - Global coordinate index
53 C bi,bj - Tile indices
54 C I,J,K - Loop counters
55 C oldPrec - Temporary used in controlling binary input dataset precision
56 C msgBuf - Informational/error meesage buffer
57 INTEGER iG, jG
58 INTEGER bi, bj
59 INTEGER I, J
60 CHARACTER*(MAX_LEN_MBUF) msgBuf
61 CEOP
62
63 IF (usingPCoords .AND. bathyFile .NE. ' '
64 & .AND. topoFile .NE. ' ' ) THEN
65 WRITE(msgBuf,'(A,A)')
66 & 'S/R INI_DEPTHS: both bathyFile & topoFile are specified:',
67 & ' select the right one !'
68 CALL PRINT_ERROR( msgBuf , myThid)
69 STOP 'ABNORMAL END: S/R INI_DEPTHS'
70 ENDIF
71
72 C------
73 C 0) Initialize R_low and Ro_surf (define an empty domain)
74 C------
75 DO bj = myByLo(myThid), myByHi(myThid)
76 DO bi = myBxLo(myThid), myBxHi(myThid)
77 DO j=1-Oly,sNy+Oly
78 DO i=1-Olx,sNx+Olx
79 R_low(i,j,bi,bj) = 0. _d 0
80 Ro_surf(i,j,bi,bj) = 0. _d 0
81 topoZ(i,j,bi,bj) = 0. _d 0
82 ENDDO
83 ENDDO
84 ENDDO
85 ENDDO
86
87 C- Need to synchronize here before doing master-thread IO
88 _BARRIER
89
90 C------
91 C 1) Set R_low = the Lower (in r sense) boundary of the fluid column :
92 C------
93 IF (usingPCoords .OR. bathyFile .EQ. ' ') THEN
94 C- e.g., atmosphere : R_low = Top of atmosphere
95 C- ocean : R_low = Bottom
96 DO bj = myByLo(myThid), myByHi(myThid)
97 DO bi = myBxLo(myThid), myBxHi(myThid)
98 DO j=1,sNy
99 DO i=1,sNx
100 R_low(i,j,bi,bj) = rF(Nr+1)
101 ENDDO
102 ENDDO
103 ENDDO
104 ENDDO
105 ELSE
106
107 #ifdef ALLOW_MNC
108 IF (useMNC .AND. mnc_read_bathy) THEN
109 CALL MNC_CW_ADD_VNAME('bathy', 'Cen_xy_Hn__-__-', 3,4, myThid)
110 CALL MNC_FILE_CLOSE_ALL_MATCHING(bathyFile, myThid)
111 CALL MNC_CW_SET_UDIM(bathyFile, 1, myThid)
112 CALL MNC_CW_SET_CITER(bathyFile, 2, -1, -1, -1, myThid)
113 CALL MNC_CW_SET_UDIM(bathyFile, 1, myThid)
114 CALL MNC_CW_RL_R('D',bathyFile,0,0,'bathy',R_low, myThid)
115 CALL MNC_FILE_CLOSE_ALL_MATCHING(bathyFile, myThid)
116 CALL MNC_CW_DEL_VNAME('bathy', myThid)
117 ELSE
118 #endif /* ALLOW_MNC */
119 C Read the bathymetry using the mid-level I/O package read_write_rec
120 C The 0 is the "iteration" argument. The 1 is the record number.
121 CALL READ_REC_XY_RS( bathyFile, R_low, 1, 0, myThid )
122 C Read the bathymetry using the mid-level I/O package read_write_fld
123 C The 0 is the "iteration" argument. The ' ' is an empty suffix
124 c CALL READ_FLD_XY_RS( bathyFile, ' ', R_low, 0, myThid )
125 C Read the bathymetry using the low-level I/O package
126 c CALL MDSREADFIELD( bathyFile, readBinaryPrec,
127 c & 'RS', 1, R_low, 1, myThid )
128
129 #ifdef ALLOW_MNC
130 ENDIF
131 #endif /* ALLOW_MNC */
132
133
134 ENDIF
135 C- end setup R_low in the interior
136
137 C- fill in the overlap (+ BARRIER):
138 _EXCH_XY_R4(R_low, myThid )
139
140 IF ( debugLevel.GE.debLevB ) THEN
141 c PRINT *, ' Calling plot field', myThid
142 CALL PLOT_FIELD_XYRS( R_low, 'Bottom depths (ini_depths)',
143 & -1, myThid )
144 ENDIF
145 c CALL WRITE_FLD_XY_RS( 'R_low' ,' ', R_low, 0,myThid)
146
147 c---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
148
149 C------
150 C 2) Set R_surf = Surface boundary: ocean surface / ground for the atmosphere
151 C------
152
153 IF ( usingPCoords .AND. bathyFile.NE.' ' ) THEN
154 C------ read directly Po_surf from bathyFile (only for backward compatibility)
155
156 CALL READ_REC_XY_RS( bathyFile, Ro_surf, 1, 0, myThid )
157
158 ELSEIF ( topoFile.EQ.' ' ) THEN
159 C------ set default value:
160
161 DO bj = myByLo(myThid), myByHi(myThid)
162 DO bi = myBxLo(myThid), myBxHi(myThid)
163 DO j=1,sNy
164 DO i=1,sNx
165 Ro_surf(i,j,bi,bj) = Ro_SeaLevel
166 ENDDO
167 ENDDO
168 ENDDO
169 ENDDO
170
171 ELSE
172 C------ read from file:
173
174 C- read surface topography (in m) from topoFile (case topoFile.NE.' '):
175
176 CALL READ_REC_XY_RS( topoFile, topoZ, 1, 0, myThid )
177 _BARRIER
178
179 IF (buoyancyRelation .EQ. 'ATMOSPHERIC') THEN
180 C----
181 C Convert Surface Geopotential to (reference) Surface Pressure
182 C according to Tref profile, using same discretisation as in calc_phi_hyd
183 C----
184 c CALL WRITE_FLD_XY_RS( 'topo_Z',' ',topoZ,0,myThid)
185
186 CALL INI_P_GROUND( 2, topoZ,
187 O Ro_surf,
188 I myThid )
189
190 c _BARRIER
191 C This I/O is now done in write_grid.F
192 c CALL WRITE_FLD_XY_RS( 'topo_P',' ',Ro_surf,0,myThid)
193
194 ELSE
195 C----
196 C Direct Transfer to Ro_surf (e.g., to specify upper ocean boundary
197 C below an ice-shelf - NOTE - actually not yet implemented )
198 DO bj = myByLo(myThid), myByHi(myThid)
199 DO bi = myBxLo(myThid), myBxHi(myThid)
200 DO j=1,sNy
201 DO i=1,sNx
202 Ro_surf(i,j,bi,bj) = topoZ(i,j,bi,bj)
203 ENDDO
204 ENDDO
205 ENDDO
206 ENDDO
207
208 ENDIF
209
210 C------ end case "read topoFile"
211 ENDIF
212
213 C----- fill in the overlap (+ BARRIER):
214 _EXCH_XY_R4(Ro_surf, myThid )
215
216 c---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
217
218 C------
219 C 3) Close the Domain (special configuration).
220 C------
221 IF (usingPCoords) THEN
222 DO bj = myByLo(myThid), myByHi(myThid)
223 DO bi = myBxLo(myThid), myBxHi(myThid)
224 DO j=1-Oly,sNy+Oly
225 DO i=1-Olx,sNx+Olx
226 iG = myXGlobalLo-1+(bi-1)*sNx+I
227 jG = myYGlobalLo-1+(bj-1)*sNy+J
228 C Test for eastern edge
229 c IF ( iG .EQ. Nx ) Ro_surf(i,j,bi,bj) = 0.
230 C Test for northern edge
231 c IF ( jG .EQ. Ny ) Ro_surf(i,j,bi,bj) = 0.
232 IF (usingSphericalPolarGrid .AND. ABS(yC(I,J,bi,bj)).GE.90. )
233 & Ro_surf(I,J,bi,bj) = rF(Nr+1)
234 ENDDO
235 ENDDO
236 ENDDO
237 ENDDO
238 ELSE
239 DO bj = myByLo(myThid), myByHi(myThid)
240 DO bi = myBxLo(myThid), myBxHi(myThid)
241 DO j=1-Oly,sNy+Oly
242 DO i=1-Olx,sNx+Olx
243 iG = myXGlobalLo-1+(bi-1)*sNx+I
244 jG = myYGlobalLo-1+(bj-1)*sNy+J
245 C Test for eastern edge
246 c IF ( iG .EQ. Nx ) R_low(i,j,bi,bj) = 0.
247 C Test for northern edge
248 c IF ( jG .EQ. Ny ) R_low(i,j,bi,bj) = 0.
249 IF (usingSphericalPolarGrid .AND. ABS(yC(I,J,bi,bj)).GE.90. )
250 & R_low(I,J,bi,bj) = Ro_SeaLevel
251 ENDDO
252 ENDDO
253 ENDDO
254 ENDDO
255 ENDIF
256
257 IF ( debugLevel.GE.debLevB ) THEN
258 CALL PLOT_FIELD_XYRS( Ro_surf,
259 & 'Surface reference r-position (ini_depths)',
260 & -1, myThid )
261 ENDIF
262 c CALL WRITE_FLD_XY_RS('Ro_surf',' ',Ro_surf,0,myThid)
263
264 C-- Everyone else must wait for the depth to be loaded
265 C- note: might not be necessary since all single-thread IO above
266 C are followed by an EXCH (with BARRIER)
267 _BARRIER
268
269 #ifdef ALLOW_OBCS
270 IF ( useOBCS ) THEN
271 C check for inconsistent topography along boundaries and fix it
272 CALL OBCS_CHECK_TOPOGRAPHY( myThid )
273 C update the overlaps
274 _EXCH_XY_R4(R_low, myThid )
275 ENDIF
276 #endif /* ALLOW_OBCS */
277
278 RETURN
279 END

  ViewVC Help
Powered by ViewVC 1.1.22