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

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

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


Revision 1.49 - (hide annotations) (download)
Wed Jun 8 01:21:14 2011 UTC (12 years, 11 months ago) by jmc
Branch: MAIN
CVS Tags: checkpoint62z, checkpoint63
Changes since 1.48: +3 -3 lines
refine debugLevel criteria when printing messages

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

  ViewVC Help
Powered by ViewVC 1.1.22