/[MITgcm]/MITgcm_contrib/submesoscale/code/obcs_check.F
ViewVC logotype

Annotation of /MITgcm_contrib/submesoscale/code/obcs_check.F

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


Revision 1.1 - (hide annotations) (download)
Sat May 31 00:13:54 2008 UTC (17 years, 1 month ago) by dimitri
Branch: MAIN
Adding ini_grid.F and obcs_check.F (checkpoint59r) in preparation to
fixing dxC and dyC in the overlap regions.

1 dimitri 1.1 C $Header: /u/gcmpack/MITgcm/pkg/obcs/obcs_check.F,v 1.12 2008/04/24 08:22:06 mlosch Exp $
2     C $Name: $
3    
4     #include "OBCS_OPTIONS.h"
5    
6     SUBROUTINE OBCS_CHECK( myThid )
7     C /==========================================================\
8     C | SUBROUTINE OBCS_CHECK |
9     C | o Check dependences with other packages |
10     C |==========================================================|
11     C \==========================================================/
12     IMPLICIT NONE
13    
14     C === Global variables ===
15     #include "SIZE.h"
16     #include "EEPARAMS.h"
17     #include "PARAMS.h"
18     #include "OBCS.h"
19    
20     C === Routine arguments ===
21     C myThid - Number of this instances
22     INTEGER myThid
23    
24     #ifdef ALLOW_OBCS
25    
26     C === Local variables ===
27     C msgBuf - Informational/error meesage buffer
28     CHARACTER*(MAX_LEN_MBUF) msgBuf
29     INTEGER i,j,bi,bj
30    
31     WRITE(msgBuf,'(A)') 'OBCS_CHECK: #define ALLOW_OBCS'
32     CALL PRINT_MESSAGE(msgBuf,standardMessageUnit,
33     & SQUEEZE_RIGHT,myThid)
34    
35     #ifdef ALLOW_CD_CODE
36     IF ( useCDscheme ) THEN
37     WRITE(msgBuf,'(A)')
38     & 'OBCS_CHECK: ERROR: useCDscheme = .TRUE.'
39     CALL PRINT_ERROR( msgBuf , 1)
40     WRITE(msgBuf,'(A)')
41     & 'OBCS_CHECK: ERROR: The CD-scheme does not work with OBCS.'
42     CALL PRINT_ERROR( msgBuf , 1)
43     WRITE(msgBuf,'(A)')
44     & 'OBCS_CHECK: ERROR: Sorry, not yet implemented.'
45     CALL PRINT_ERROR( msgBuf , 1)
46     STOP 'ABNORMAL END: S/R OBCS_CHECK'
47     ENDIF
48     #endif /* ALLOW_CD_CODE */
49    
50     #ifdef ALLOW_ORLANSKI
51     WRITE(msgBuf,'(A)') 'OBCS_CHECK: #define ALLOW_ORLANSKI'
52     CALL PRINT_MESSAGE(msgBuf,standardMessageUnit,
53     & SQUEEZE_RIGHT,myThid)
54     #else
55     IF (useOrlanskiNorth.OR.useOrlanskiSouth.OR.
56     & useOrlanskiEast.OR.useOrlanskiWest) THEN
57     WRITE(msgBuf,'(A)')
58     & 'OBCS_CHECK: ERROR: #undef OBCS_RADIATE_ORLANSKI and'
59     CALL PRINT_ERROR( msgBuf , 1)
60     WRITE(msgBuf,'(A)')
61     & 'OBCS_CHECK: ERROR: one of useOrlanski* logicals is true'
62     CALL PRINT_ERROR( msgBuf , 1)
63     STOP 'ABNORMAL END: S/R OBCS_CHECK'
64     ENDIF
65     #endif /* ALLOW_ORLANSKI */
66    
67     IF (useOrlanskiNorth.OR.useOrlanskiSouth.OR.
68     & useOrlanskiEast.OR.useOrlanskiWest) THEN
69     IF (nonlinFreeSurf.GT.0) THEN
70     WRITE(msgBuf,'(A)')
71     & 'OBCS_CHECK: ERROR: useOrlanski* Rad OBC with'
72     CALL PRINT_ERROR( msgBuf , 1)
73     WRITE(msgBuf,'(A)')
74     & 'OBCS_CHECK: ERROR: nonlinFreeSurf not yet implemented'
75     CALL PRINT_ERROR( msgBuf , 1)
76     STOP 'ABNORMAL END: S/R OBCS_CHECK'
77     ENDIF
78     IF (usePTracers) THEN
79     WRITE(msgBuf,'(A)')
80     & 'OBCS_CHECK: ERROR: useOrlanski* Rad OBC with'
81     CALL PRINT_ERROR( msgBuf , 1)
82     WRITE(msgBuf,'(A)')
83     & 'OBCS_CHECK: ERROR: pTracers not yet implemented'
84     CALL PRINT_ERROR( msgBuf , 1)
85     STOP 'ABNORMAL END: S/R OBCS_CHECK'
86     ENDIF
87     IF (useSEAICE) THEN
88     WRITE(msgBuf,'(A)')
89     & 'OBCS_CHECK: ERROR: useOrlanski* Rad OBC with'
90     CALL PRINT_ERROR( msgBuf , 1)
91     WRITE(msgBuf,'(A)')
92     & 'OBCS_CHECK: ERROR: SEAICE not yet implemented'
93     CALL PRINT_ERROR( msgBuf , 1)
94     STOP 'ABNORMAL END: S/R OBCS_CHECK'
95     ENDIF
96     ENDIF
97    
98     #ifndef ALLOW_OBCS_PRESCRIBE
99     IF (useOBCSprescribe) THEN
100     WRITE(msgBuf,'(A)')
101     & 'OBCS_CHECK: ERROR: useOBCSprescribe = .TRUE. for'
102     CALL PRINT_ERROR( msgBuf , 1)
103     WRITE(msgBuf,'(A)')
104     & 'OBCS_CHECK: undef ALLOW_OBCS_PRESCRIBE'
105     CALL PRINT_ERROR( msgBuf , 1)
106     STOP 'ABNORMAL END: S/R OBCS_CHECK'
107     ENDIF
108     #endif
109    
110     IF (useSEAICE .AND. .NOT. useEXF) THEN
111     WRITE(msgBuf,'(A)')
112     & 'OBCS_CHECK: ERROR: for SEAICE OBCS, use'
113     CALL PRINT_ERROR( msgBuf , 1)
114     WRITE(msgBuf,'(A)')
115     & 'OBCS_CHECK: pkg/exf to read input files'
116     CALL PRINT_ERROR( msgBuf , 1)
117     STOP 'ABNORMAL END: S/R OBCS_CHECK'
118     ENDIF
119    
120     IF ( debugLevel.GE.debLevB ) THEN
121     _BEGIN_MASTER( myThid )
122     DO bj = 1,nSy
123     DO bi = 1,nSx
124     write(*,*) 'bi,bj:',bi,bj,' OB_Jn=',(OB_Jn(i,bi,bj),i=1,sNx)
125     write(*,*) 'bi,bj:',bi,bj,' OB_Js=',(OB_Js(i,bi,bj),i=1,sNx)
126     write(*,*) 'bi,bj:',bi,bj,' OB_Ie=',(OB_Ie(j,bi,bj),j=1,sNy)
127     write(*,*) 'bi,bj:',bi,bj,' OB_Iw=',(OB_Iw(j,bi,bj),j=1,sNy)
128     ENDDO
129     ENDDO
130     _END_MASTER(myThid)
131     ENDIF
132    
133     WRITE(msgBuf,'(A)') 'OBCS_CHECK: OK'
134     CALL PRINT_MESSAGE(msgBuf,standardMessageUnit,
135     & SQUEEZE_RIGHT,myThid)
136    
137     #endif /* ALLOW_OBCS */
138     RETURN
139     END
140    
141     SUBROUTINE OBCS_CHECK_TOPOGRAPHY( myThid )
142     C /==========================================================\
143     C | SUBROUTINE OBCS_CHECK_TOPOGRAPHY |
144     C | o Check for non-zero normal gradient across open |
145     C | boundaries |
146     C | o fix them if required and print a message |
147     C |==========================================================|
148     C \==========================================================/
149     IMPLICIT NONE
150    
151     C === Global variables ===
152     #include "SIZE.h"
153     #include "EEPARAMS.h"
154     #include "PARAMS.h"
155     #include "GRID.h"
156     #include "OBCS.h"
157    
158     C === Routine arguments ===
159     C myThid - Number of this instances
160     INTEGER myThid
161    
162     #ifdef ALLOW_OBCS
163     C === Local variables ===
164     C msgBuf - Informational/error meesage buffer
165     CHARACTER*(MAX_LEN_MBUF) msgBuf
166     INTEGER bi, bj, I, J, K, ichanged
167    
168     IF ( OBCSfixTopo ) THEN
169     C-- Modify topography to ensure that outward d(topography)/dn >= 0,
170     C topography at open boundary points must be equal or shallower than
171     C topography one grid-point inward from open boundary
172     ichanged = 0
173     DO bj = myByLo(myThid), myByHi(myThid)
174     DO bi = myBxLo(myThid), myBxHi(myThid)
175    
176     DO K=1,Nr
177     #ifdef ALLOW_OBCS_NORTH
178     DO I=1,sNx
179     J=OB_Jn(I,bi,bj)
180     IF ( J .NE. 0 .AND.
181     & ( R_low(I,J,bi,bj) .LT. R_low(I,J-1,bi,bj) ) ) THEN
182     ichanged = ichanged + 1
183     R_low(I,J,bi,bj) = R_low(I,J-1,bi,bj)
184     WRITE(msgBuf,'(2A,(1X,4I6))')
185     & 'S/R OBCS_CHECK_TOPOGRAPHY: fixed topography at ',
186     & '(i,j,bi,bj) = ', I, J, bi, bj
187     CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,
188     & SQUEEZE_RIGHT, myThid)
189     ENDIF
190     ENDDO
191     #endif
192     #ifdef ALLOW_OBCS_SOUTH
193     DO I=1,sNx
194     J=OB_Js(I,bi,bj)
195     IF ( J .NE. 0 .AND.
196     & ( R_low(I,J,bi,bj) .LT. R_low(I,J+1,bi,bj) ) ) THEN
197     ichanged = ichanged + 1
198     R_low(I,J,bi,bj) = R_low(I,J+1,bi,bj)
199     WRITE(msgBuf,'(2A,(1X,4I6))')
200     & 'S/R OBCS_CHECK_TOPOGRAPHY: fixed topography at ',
201     & '(i,j,bi,bj) = ', I, J, bi, bj
202     CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,
203     & SQUEEZE_RIGHT, myThid)
204     ENDIF
205     ENDDO
206     #endif
207     #ifdef ALLOW_OBCS_EAST
208     DO J=1,sNy
209     I = OB_Ie(J,bi,bj)
210     IF ( I .NE. 0 .AND.
211     & ( R_low(I,J,bi,bj) .LT. R_low(I-1,J,bi,bj) ) ) THEN
212     ichanged = ichanged + 1
213     R_low(I,J,bi,bj) = R_low(I-1,J,bi,bj)
214     WRITE(msgBuf,'(2A,(1X,4I6))')
215     & 'S/R OBCS_CHECK_TOPOGRAPHY: fixed topography at ',
216     & '(i,j,bi,bj) = ', I, J, bi, bj
217     CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,
218     & SQUEEZE_RIGHT, myThid)
219     ENDIF
220     ENDDO
221     #endif
222     C Western boundary
223     #ifdef ALLOW_OBCS_WEST
224     DO J=1,sNy
225     I = OB_Iw(J,bi,bj)
226     IF ( I .NE. 0 .AND.
227     & ( R_low(I,J,bi,bj) .LT. R_low(I+1,J,bi,bj) ) ) THEN
228     ichanged = ichanged + 1
229     R_low(I,J,bi,bj) = R_low(I+1,J,bi,bj)
230     WRITE(msgBuf,'(2A,(1X,4I6))')
231     & 'S/R OBCS_CHECK_TOPOGRAPHY: fixed topography at ',
232     & '(i,j,bi,bj) = ', I, J, bi, bj
233     CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,
234     & SQUEEZE_RIGHT, myThid)
235     ENDIF
236     ENDDO
237     #endif
238     ENDDO
239    
240     ENDDO
241     ENDDO
242     C-- some diagnostics to stdout
243     IF ( ichanged .GT. 0 ) THEN
244     WRITE(msgBuf,'(A,I7,A,A)')
245     & 'OBCS message: corrected ', ichanged,
246     & ' instances of problematic topography gradients',
247     & ' normal to open boundaries'
248     CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,
249     & SQUEEZE_RIGHT, myThid)
250     ENDIF
251     C endif (OBCSfixTopo)
252     ENDIF
253     #endif /* ALLOW_OBCS */
254    
255     RETURN
256     END

  ViewVC Help
Powered by ViewVC 1.1.22