/[MITgcm]/MITgcm/verification/aim.5l_Equatorial_Channel/code/ini_depths.F
ViewVC logotype

Annotation of /MITgcm/verification/aim.5l_Equatorial_Channel/code/ini_depths.F

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


Revision 1.8 - (hide annotations) (download)
Tue Dec 10 03:05:33 2002 UTC (21 years, 4 months ago) by jmc
Branch: MAIN
CVS Tags: checkpoint47e_post, checkpoint47c_post, checkpoint48e_post, checkpoint48i_post, checkpoint50, checkpoint48b_post, checkpoint48c_pre, checkpoint47d_pre, checkpoint48d_pre, checkpoint47i_post, checkpoint47d_post, checkpoint48d_post, checkpoint48f_post, checkpoint48h_post, checkpoint47g_post, checkpoint48a_post, checkpoint47j_post, branch-exfmods-tag, checkpoint48c_post, checkpoint47f_post, checkpoint48, checkpoint49, checkpoint47h_post, checkpoint48g_post
Branch point for: branch-exfmods-curt
Changes since 1.7: +4 -2 lines
  update after changing the standard version

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

  ViewVC Help
Powered by ViewVC 1.1.22