/[MITgcm]/MITgcm/verification/advect_xz/code/ini_depths.F
ViewVC logotype

Diff of /MITgcm/verification/advect_xz/code/ini_depths.F

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

revision 1.2 by jmc, Tue Dec 10 03:07:28 2002 UTC revision 1.3 by jmc, Wed Jun 22 00:18:48 2005 UTC
# Line 9  C     !INTERFACE: Line 9  C     !INTERFACE:
9        SUBROUTINE INI_DEPTHS( myThid )        SUBROUTINE INI_DEPTHS( myThid )
10  C     !DESCRIPTION: \bv  C     !DESCRIPTION: \bv
11  C     *==========================================================*  C     *==========================================================*
12  C     | SUBROUTINE INI_DEPTHS                                      C     | SUBROUTINE INI_DEPTHS
13  C     | o define R_position of Lower and Surface Boundaries        C     | o define R_position of Lower and Surface Boundaries
14  C     *==========================================================*  C     *==========================================================*
15  C     |atmosphere orography:                                        C     |atmosphere orography:
16  C     | define either in term of P_topo or converted from Z_topo    C     | define either in term of P_topo or converted from Z_topo
17  C     |ocean bathymetry:                                            C     |ocean bathymetry:
18  C     | The depths of the bottom of the model is specified in      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        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        C     | grid cells. Depths do not have to coincide with the
21  C     | model levels. The model lopping algorithm makes it          C     | model levels. The model lopping algorithm makes it
22  C     | possible to represent arbitrary depths.                    C     | possible to represent arbitrary depths.
23  C     | The mode depths map also influences the models topology    C     | The mode depths map also influences the models topology
24  C     | By default the model domain wraps around in X and Y.        C     | By default the model domain wraps around in X and Y.
25  C     | This default doubly periodic topology is "supressed"        C     | This default doubly periodic topology is "supressed"
26  C     | if a depth map is defined which closes off all wrap        C     | if a depth map is defined which closes off all wrap
27  C     | around flow.                                                C     | around flow.
28  C     *==========================================================*  C     *==========================================================*
29  C     \ev  C     \ev
30    
# Line 46  CEndOfInterface Line 46  CEndOfInterface
46  C     !LOCAL VARIABLES:  C     !LOCAL VARIABLES:
47  C     == Local variables ==  C     == Local variables ==
48  C     iG, jG - Global coordinate index  C     iG, jG - Global coordinate index
49  C     bi,bj  - Loop counters  C     bi,bj  - Tile indices
50  C     I,J,K  C     I,J,K  - Loop counters
51  C     oldPrec - Temporary used in controlling binary input dataset precision  C     oldPrec - Temporary used in controlling binary input dataset precision
52  C     msgBuf    - Informational/error meesage buffer  C     msgBuf    - Informational/error meesage buffer
53        INTEGER iG, jG        INTEGER iG, jG
54        INTEGER bi, bj        INTEGER bi, bj
55        INTEGER  I, J        INTEGER  I, J
56        CHARACTER*(MAX_LEN_MBUF) msgBuf        CHARACTER*(MAX_LEN_MBUF) msgBuf
57  CEOP  CEOP
58    
59        IF (groundAtK1 .AND. bathyFile .NE. ' '        IF (usingPCoords .AND. bathyFile .NE. ' '
60       &               .AND. topoFile  .NE. ' ' ) THEN       &                 .AND. topoFile  .NE. ' ' ) THEN
61         WRITE(msgBuf,'(A,A)')         WRITE(msgBuf,'(A,A)')
62       &  'S/R INI_DEPTHS: both bathyFile & topoFile are specified:',       &  'S/R INI_DEPTHS: both bathyFile & topoFile are specified:',
63       &  ' select the right one !'       &  ' select the right one !'
# Line 83  C------ Line 83  C------
83  C------  C------
84  C   1) Set R_low = the Lower (in r sense) boundary of the fluid column :  C   1) Set R_low = the Lower (in r sense) boundary of the fluid column :
85  C------  C------
86        IF (groundAtK1 .OR. bathyFile .EQ. ' ') THEN        IF (usingPCoords .OR. bathyFile .EQ. ' ') THEN
87  C- e.g., atmosphere : R_low = Top of atmosphere  C- e.g., atmosphere : R_low = Top of atmosphere
88  C-            ocean : R_low = Bottom  C-            ocean : R_low = Bottom
89         DO bj = myByLo(myThid), myByHi(myThid)         DO bj = myByLo(myThid), myByHi(myThid)
# Line 92  C-            ocean : R_low = Bottom Line 92  C-            ocean : R_low = Bottom
92            DO i=1,sNx            DO i=1,sNx
93             R_low(i,j,bi,bj) = rF(Nr+1)             R_low(i,j,bi,bj) = rF(Nr+1)
94  C-- Specific modif for this experiment (advect_xz):  C-- Specific modif for this experiment (advect_xz):
95             R_low(I,J,bi,bj) = R_low(I,J,bi,bj)             R_low(I,J,bi,bj) = R_low(I,J,bi,bj)
96       &     *(1.-0.5*XC(I,J,bi,bj)/(float(Nx)*DelX(1)))       &     *(1.-0.5*XC(I,J,bi,bj)/(float(Nx)*DelX(1)))
97  C-- end of modified part  C-- end of modified part
98            ENDDO            ENDDO
# Line 120  C- fill in the overlap : Line 120  C- fill in the overlap :
120    
121  c     CALL PLOT_FIELD_XYRS(R_low,'Bottom depths (ini_depths)',1,myThid)  c     CALL PLOT_FIELD_XYRS(R_low,'Bottom depths (ini_depths)',1,myThid)
122  c     _BEGIN_MASTER( myThid )  c     _BEGIN_MASTER( myThid )
123  c     CALL WRITE_FLD_XY_RS( 'R_low' ,' ', R_low, 0,myThid)  c     CALL WRITE_FLD_XY_RS( 'R_low' ,' ', R_low, 0,myThid)
124  c     _END_MASTER(myThid)  c     _END_MASTER(myThid)
125    
126  c---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|  c---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
# Line 129  C------ Line 129  C------
129  C   2) Set R_surf = Surface boundary: ocean surface / ground for the atmosphere  C   2) Set R_surf = Surface boundary: ocean surface / ground for the atmosphere
130  C------  C------
131    
132        IF ( groundAtK1 .AND. bathyFile.NE.' ' ) THEN        IF ( usingPCoords .AND. bathyFile.NE.' ' ) THEN
133  C------ read directly Po_surf from bathyFile (only for backward compatibility)  C------ read directly Po_surf from bathyFile (only for backward compatibility)
134    
135          _BEGIN_MASTER( myThid )          _BEGIN_MASTER( myThid )
136          CALL READ_REC_XY_RS( bathyFile, Ro_surf, 1, 0, myThid )          CALL READ_REC_XY_RS( bathyFile, Ro_surf, 1, 0, myThid )
# Line 161  C- read surface topography (in m) from t Line 161  C- read surface topography (in m) from t
161    
162          IF (buoyancyRelation .EQ. 'ATMOSPHERIC') THEN          IF (buoyancyRelation .EQ. 'ATMOSPHERIC') THEN
163  C----  C----
164  C   Convert Surface Geopotential to (reference) Surface Pressure  C   Convert Surface Geopotential to (reference) Surface Pressure
165  C   according to Tref profile, using same discretisation as in calc_phi_hyd  C   according to Tref profile, using same discretisation as in calc_phi_hyd
166  C----  C----
167  c         _BEGIN_MASTER( myThid )  c         _BEGIN_MASTER( myThid )
168  c         CALL WRITE_FLD_XY_RS( 'topo_Z',' ',topoZ,0,myThid)  c         CALL WRITE_FLD_XY_RS( 'topo_Z',' ',topoZ,0,myThid)
169  c         _END_MASTER(myThid)  c         _END_MASTER(myThid)
170    
171            CALL INI_P_GROUND( selectFindRoSurf, topoZ,            CALL INI_P_GROUND( 2, topoZ,
172       O                       Ro_surf,       O                       Ro_surf,
173       I                       myThid )       I                       myThid )
174    
175            _BARRIER            _BARRIER
176            _BEGIN_MASTER( myThid )  C         This I/O is now done in write_grid.F
177            CALL WRITE_FLD_XY_RS( 'topo_P',' ',Ro_surf,0,myThid)  c         _BEGIN_MASTER( myThid )
178            _END_MASTER(myThid)  c         CALL WRITE_FLD_XY_RS( 'topo_P',' ',Ro_surf,0,myThid)
179    c         _END_MASTER(myThid)
180    
181          ELSE          ELSE
182  C----  C----
183  C   Direct Transfer to Ro_surf :  C   Direct Transfer to Ro_surf (e.g., to specify upper ocean boundary
184    C    below an ice-shelf - NOTE - actually not yet implemented )
185            DO bj = myByLo(myThid), myByHi(myThid)            DO bj = myByLo(myThid), myByHi(myThid)
186             DO bi = myBxLo(myThid), myBxHi(myThid)             DO bi = myBxLo(myThid), myBxHi(myThid)
187              DO j=1,sNy              DO j=1,sNy
# Line 195  C   Direct Transfer to Ro_surf : Line 197  C   Direct Transfer to Ro_surf :
197  C------ end case "read topoFile"  C------ end case "read topoFile"
198        ENDIF        ENDIF
199    
200  C----- fill in the overlap :  C----- fill in the overlap :
201        _EXCH_XY_R4(Ro_surf, myThid )        _EXCH_XY_R4(Ro_surf, myThid )
202    
203  c---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|  c---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
# Line 203  c---+----1----+----2----+----3----+----4 Line 205  c---+----1----+----2----+----3----+----4
205  C------  C------
206  C   3) Close the Domain (special configuration).  C   3) Close the Domain (special configuration).
207  C------  C------
208        IF (groundAtK1) THEN        IF (usingPCoords) THEN
209         DO bj = myByLo(myThid), myByHi(myThid)         DO bj = myByLo(myThid), myByHi(myThid)
210          DO bi = myBxLo(myThid), myBxHi(myThid)          DO bi = myBxLo(myThid), myBxHi(myThid)
211           DO j=1-Oly,sNy+Oly           DO j=1-Oly,sNy+Oly
# Line 214  C          Test for eastern edge Line 216  C          Test for eastern edge
216  c          IF ( iG .EQ. Nx )  Ro_surf(i,j,bi,bj) = 0.  c          IF ( iG .EQ. Nx )  Ro_surf(i,j,bi,bj) = 0.
217  C          Test for northern edge  C          Test for northern edge
218  c          IF ( jG .EQ. Ny )  Ro_surf(i,j,bi,bj) = 0.  c          IF ( jG .EQ. Ny )  Ro_surf(i,j,bi,bj) = 0.
219             IF (usingSphericalPolarGrid .AND. abs(yC(I,J,bi,bj)).GE.90. )             IF (usingSphericalPolarGrid .AND. abs(yC(I,J,bi,bj)).GE.90. )
220       &       Ro_surf(I,J,bi,bj) = rF(Nr+1)       &       Ro_surf(I,J,bi,bj) = rF(Nr+1)
221            ENDDO            ENDDO
222           ENDDO           ENDDO
# Line 231  C          Test for eastern edge Line 233  C          Test for eastern edge
233  c          IF ( iG .EQ. Nx )  R_low(i,j,bi,bj) = 0.  c          IF ( iG .EQ. Nx )  R_low(i,j,bi,bj) = 0.
234  C          Test for northern edge  C          Test for northern edge
235  c          IF ( jG .EQ. Ny )  R_low(i,j,bi,bj) = 0.  c          IF ( jG .EQ. Ny )  R_low(i,j,bi,bj) = 0.
236             IF (usingSphericalPolarGrid .AND. abs(yC(I,J,bi,bj)).GE.90. )             IF (usingSphericalPolarGrid .AND. abs(yC(I,J,bi,bj)).GE.90. )
237       &       R_low(I,J,bi,bj) = Ro_SeaLevel       &       R_low(I,J,bi,bj) = Ro_SeaLevel
238            ENDDO            ENDDO
239           ENDDO           ENDDO
# Line 240  c          IF ( jG .EQ. Ny )  R_low(i,j, Line 242  c          IF ( jG .EQ. Ny )  R_low(i,j,
242        ENDIF        ENDIF
243    
244  c     _BEGIN_MASTER( myThid )  c     _BEGIN_MASTER( myThid )
245  c     CALL WRITE_FLD_XY_RS('Ro_surf',' ',Ro_surf,0,myThid)  c     CALL WRITE_FLD_XY_RS('Ro_surf',' ',Ro_surf,0,myThid)
246  c     _END_MASTER(myThid)  c     _END_MASTER(myThid)
247    
248        RETURN        RETURN

Legend:
Removed from v.1.2  
changed lines
  Added in v.1.3

  ViewVC Help
Powered by ViewVC 1.1.22