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

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

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

revision 1.9 by jmc, Mon Mar 17 16:42:07 2003 UTC revision 1.10 by jmc, Wed Jun 22 00:18:49 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 49  C     iG, jG - Global coordinate index Line 49  C     iG, jG - Global coordinate index
49  C     bi,bj  - Tile indices  C     bi,bj  - Tile indices
50  C     I,J,K  - Loop counters  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 116  C- fill in the overlap : Line 116  C- fill in the overlap :
116    
117  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)
118  c     _BEGIN_MASTER( myThid )  c     _BEGIN_MASTER( myThid )
119  c     CALL WRITE_FLD_XY_RS( 'R_low' ,' ', R_low, 0,myThid)  c     CALL WRITE_FLD_XY_RS( 'R_low' ,' ', R_low, 0,myThid)
120  c     _END_MASTER(myThid)  c     _END_MASTER(myThid)
121    
122  c---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|  c---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
# Line 125  C------ Line 125  C------
125  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
126  C------  C------
127    
128        IF ( groundAtK1 .AND. bathyFile.NE.' ' ) THEN        IF ( usingPCoords .AND. bathyFile.NE.' ' ) THEN
129  C------ read directly Po_surf from bathyFile (only for backward compatibility)  C------ read directly Po_surf from bathyFile (only for backward compatibility)
130    
131          _BEGIN_MASTER( myThid )          _BEGIN_MASTER( myThid )
132          CALL READ_REC_XY_RS( bathyFile, Ro_surf, 1, 0, myThid )          CALL READ_REC_XY_RS( bathyFile, Ro_surf, 1, 0, myThid )
# Line 157  C- read surface topography (in m) from t Line 157  C- read surface topography (in m) from t
157    
158          IF (buoyancyRelation .EQ. 'ATMOSPHERIC') THEN          IF (buoyancyRelation .EQ. 'ATMOSPHERIC') THEN
159  C----  C----
160  C   Convert Surface Geopotential to (reference) Surface Pressure  C   Convert Surface Geopotential to (reference) Surface Pressure
161  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
162  C----  C----
163  c         _BEGIN_MASTER( myThid )  c         _BEGIN_MASTER( myThid )
164  c         CALL WRITE_FLD_XY_RS( 'topo_Z',' ',topoZ,0,myThid)  c         CALL WRITE_FLD_XY_RS( 'topo_Z',' ',topoZ,0,myThid)
165  c         _END_MASTER(myThid)  c         _END_MASTER(myThid)
166    
167            CALL INI_P_GROUND( 2, topoZ,            CALL INI_P_GROUND( 2, topoZ,
# Line 169  c         _END_MASTER(myThid) Line 169  c         _END_MASTER(myThid)
169       I                       myThid )       I                       myThid )
170    
171            _BARRIER            _BARRIER
172            _BEGIN_MASTER( myThid )  C         This I/O is now done in write_grid.F
173            CALL WRITE_FLD_XY_RS( 'topo_P',' ',Ro_surf,0,myThid)  c         _BEGIN_MASTER( myThid )
174            _END_MASTER(myThid)  c         CALL WRITE_FLD_XY_RS( 'topo_P',' ',Ro_surf,0,myThid)
175    c         _END_MASTER(myThid)
176    
177          ELSE          ELSE
178  C----  C----
179  C   Direct Transfer to Ro_surf (e.g., to specify upper ocean boundary  C   Direct Transfer to Ro_surf (e.g., to specify upper ocean boundary
180  C    below an ice-shelf - NOTE - actually not yet implemented )  C    below an ice-shelf - NOTE - actually not yet implemented )
181            DO bj = myByLo(myThid), myByHi(myThid)            DO bj = myByLo(myThid), myByHi(myThid)
182             DO bi = myBxLo(myThid), myBxHi(myThid)             DO bi = myBxLo(myThid), myBxHi(myThid)
# Line 192  C    below an ice-shelf - NOTE - actuall Line 193  C    below an ice-shelf - NOTE - actuall
193  C------ end case "read topoFile"  C------ end case "read topoFile"
194        ENDIF        ENDIF
195    
196  C----- fill in the overlap :  C----- fill in the overlap :
197        _EXCH_XY_R4(Ro_surf, myThid )        _EXCH_XY_R4(Ro_surf, myThid )
198    
199  c---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|  c---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
# Line 200  c---+----1----+----2----+----3----+----4 Line 201  c---+----1----+----2----+----3----+----4
201  C------  C------
202  C   3) Close the Domain (special configuration).  C   3) Close the Domain (special configuration).
203  C------  C------
204        IF (groundAtK1) THEN        IF (usingPCoords) THEN
205         DO bj = myByLo(myThid), myByHi(myThid)         DO bj = myByLo(myThid), myByHi(myThid)
206          DO bi = myBxLo(myThid), myBxHi(myThid)          DO bi = myBxLo(myThid), myBxHi(myThid)
207           DO j=1-Oly,sNy+Oly           DO j=1-Oly,sNy+Oly
# Line 215  c- Domain : Symetric % Eq. & closed at N Line 216  c- Domain : Symetric % Eq. & closed at N
216             IF (usingSphericalPolarGrid .AND.             IF (usingSphericalPolarGrid .AND.
217       &         abs(yC(I,J,bi,bj)).GE.-phiMin)       &         abs(yC(I,J,bi,bj)).GE.-phiMin)
218       &       Ro_surf(I,J,bi,bj) = rF(Nr+1)       &       Ro_surf(I,J,bi,bj) = rF(Nr+1)
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 236  c- Domain : Symetric % Eq. & closed at N Line 237  c- Domain : Symetric % Eq. & closed at N
237             IF (usingSphericalPolarGrid .AND.             IF (usingSphericalPolarGrid .AND.
238       &         abs(yC(I,J,bi,bj)).GE.-phiMin)       &         abs(yC(I,J,bi,bj)).GE.-phiMin)
239       &       R_low(I,J,bi,bj) = Ro_SeaLevel       &       R_low(I,J,bi,bj) = Ro_SeaLevel
240             IF (usingSphericalPolarGrid .AND. abs(yC(I,J,bi,bj)).GE.90. )             IF (usingSphericalPolarGrid .AND. abs(yC(I,J,bi,bj)).GE.90. )
241       &       R_low(I,J,bi,bj) = Ro_SeaLevel       &       R_low(I,J,bi,bj) = Ro_SeaLevel
242            ENDDO            ENDDO
243           ENDDO           ENDDO
# Line 245  c- Domain : Symetric % Eq. & closed at N Line 246  c- Domain : Symetric % Eq. & closed at N
246        ENDIF        ENDIF
247    
248  c     _BEGIN_MASTER( myThid )  c     _BEGIN_MASTER( myThid )
249  c     CALL WRITE_FLD_XY_RS('Ro_surf',' ',Ro_surf,0,myThid)  c     CALL WRITE_FLD_XY_RS('Ro_surf',' ',Ro_surf,0,myThid)
250  c     _END_MASTER(myThid)  c     _END_MASTER(myThid)
251    
252        RETURN        RETURN

Legend:
Removed from v.1.9  
changed lines
  Added in v.1.10

  ViewVC Help
Powered by ViewVC 1.1.22