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

Diff of /MITgcm/model/src/config_check.F

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

revision 1.8.2.2 by heimbach, Tue Jun 24 23:05:28 2003 UTC revision 1.60 by mlosch, Sat Mar 24 20:53:36 2012 UTC
# Line 1  Line 1 
1  C $Header$  C $Header$
2  C $Name$  C $Name$
3    
4    #include "PACKAGES_CONFIG.h"
5  #include "CPP_OPTIONS.h"  #include "CPP_OPTIONS.h"
6    
7  CBOP  CBOP
# Line 15  C     *================================= Line 16  C     *=================================
16  C     | This routine help to prevent the use of parameters  C     | This routine help to prevent the use of parameters
17  C     | that are not compatible with the model configuration.  C     | that are not compatible with the model configuration.
18  C     *=========================================================*  C     *=========================================================*
19  C     \ev                                                            C     \ev
20    
21  C     !USES:  C     !USES:
22        IMPLICIT NONE        IMPLICIT NONE
# Line 33  CEndOfInterface Line 34  CEndOfInterface
34    
35  C     !LOCAL VARIABLES:  C     !LOCAL VARIABLES:
36  C     == Local variables ==  C     == Local variables ==
37  C     msgBuf :: Informational/error meesage buffer  C     msgBuf :: Informational/error message buffer
38        CHARACTER*(MAX_LEN_MBUF) msgBuf        CHARACTER*(MAX_LEN_MBUF) msgBuf
39  CEOP  CEOP
40    
41  C-  check that CPP option is "defined" when running-flag parameter is on:  C-  check that CPP option is "defined" when running-flag parameter is on:
42    
43  #ifndef INCLUDE_CD_CODE  C     o If diffKrFile is set, then we should make sure the corresponing
44        IF (useCDscheme) THEN  C       code is being compiled
45          WRITE(msgBuf,'(A)')  #ifndef ALLOW_3D_DIFFKR
46       &   'CONFIG_CHECK: #undef INCLUDE_CD_CODE and'        IF (diffKrFile.NE.' ') THEN
47          CALL PRINT_ERROR( msgBuf , myThid)          WRITE(msgBuf,'(A)')
48         &  'CONFIG_CHECK: diffKrFile is set but never used.'
49            CALL PRINT_ERROR( msgBuf, myThid )
50          WRITE(msgBuf,'(A)')          WRITE(msgBuf,'(A)')
51       &   'CONFIG_CHECK: useCDscheme is TRUE'       &  'Re-compile with:  #define ALLOW_3D_DIFFKR'
52          CALL PRINT_ERROR( msgBuf , myThid)          CALL PRINT_ERROR( msgBuf, myThid )
53          STOP 'ABNORMAL END: S/R CONFIG_CHECK'          STOP 'ABNORMAL END: S/R CONFIG_CHECK'
54        ENDIF        ENDIF
55  #endif  #endif
56    
57  #ifndef ALLOW_NONHYDROSTATIC  #ifndef ALLOW_NONHYDROSTATIC
58        IF (nonHydrostatic) THEN        IF (use3Dsolver) THEN
         WRITE(msgBuf,'(A)')  
      &   'CONFIG_CHECK: #undef ALLOW_NONHYDROSTATIC and'  
         CALL PRINT_ERROR( msgBuf , myThid)  
59          WRITE(msgBuf,'(A)')          WRITE(msgBuf,'(A)')
60         &   'CONFIG_CHECK: #undef ALLOW_NONHYDROSTATIC and'
61            CALL PRINT_ERROR( msgBuf, myThid )
62           IF ( implicitIntGravWave ) WRITE(msgBuf,'(A)')
63         &   'CONFIG_CHECK: implicitIntGravWave is TRUE'
64           IF ( nonHydrostatic ) WRITE(msgBuf,'(A)')
65       &   'CONFIG_CHECK: nonHydrostatic is TRUE'       &   'CONFIG_CHECK: nonHydrostatic is TRUE'
66          CALL PRINT_ERROR( msgBuf , myThid)          CALL PRINT_ERROR( msgBuf, myThid )
67            STOP 'ABNORMAL END: S/R CONFIG_CHECK'
68          ENDIF
69    #endif
70    
71    #ifndef ALLOW_ADAMSBASHFORTH_3
72          IF ( alph_AB.NE.UNSET_RL .OR. beta_AB.NE.UNSET_RL ) THEN
73            WRITE(msgBuf,'(2A)') 'CONFIG_CHECK: ',
74         &   '#undef ALLOW_ADAMSBASHFORTH_3 but alph_AB,beta_AB'
75            CALL PRINT_ERROR( msgBuf, myThid )
76            WRITE(msgBuf,'(A,1P2E20.7)')
77         &   'CONFIG_CHECK: are set to:',alph_AB,beta_AB
78            CALL PRINT_ERROR( msgBuf, myThid )
79            STOP 'ABNORMAL END: S/R CONFIG_CHECK'
80          ENDIF
81    #endif
82    
83    #ifndef INCLUDE_IMPLVERTADV_CODE
84          IF ( momImplVertAdv ) THEN
85            WRITE(msgBuf,'(A)')
86         &   'CONFIG_CHECK: #undef INCLUDE_IMPLVERTADV_CODE'
87            CALL PRINT_ERROR( msgBuf, myThid )
88            WRITE(msgBuf,'(A)')
89         &   'CONFIG_CHECK: but momImplVertAdv is TRUE'
90            CALL PRINT_ERROR( msgBuf, myThid )
91            STOP 'ABNORMAL END: S/R CONFIG_CHECK'
92          ENDIF
93          IF ( tempImplVertAdv ) THEN
94            WRITE(msgBuf,'(A)')
95         &   'CONFIG_CHECK: #undef INCLUDE_IMPLVERTADV_CODE'
96            CALL PRINT_ERROR( msgBuf, myThid )
97            WRITE(msgBuf,'(A)')
98         &   'CONFIG_CHECK: but tempImplVertAdv is TRUE'
99            CALL PRINT_ERROR( msgBuf, myThid )
100            STOP 'ABNORMAL END: S/R CONFIG_CHECK'
101          ENDIF
102          IF ( saltImplVertAdv ) THEN
103            WRITE(msgBuf,'(A)')
104         &   'CONFIG_CHECK: #undef INCLUDE_IMPLVERTADV_CODE'
105            CALL PRINT_ERROR( msgBuf, myThid )
106            WRITE(msgBuf,'(A)')
107         &   'CONFIG_CHECK: but saltImplVertAdv is TRUE'
108            CALL PRINT_ERROR( msgBuf, myThid )
109            STOP 'ABNORMAL END: S/R CONFIG_CHECK'
110          ENDIF
111          IF ( dTtracerLev(1).NE.dTtracerLev(Nr) .AND. implicitDiffusion
112         &     .AND. ( saltStepping .OR. tempStepping .OR. usePTRACERS )
113         &   ) THEN
114            WRITE(msgBuf,'(A)')
115         &   'CONFIG_CHECK: #undef INCLUDE_IMPLVERTADV_CODE'
116            CALL PRINT_ERROR( msgBuf, myThid )
117            WRITE(msgBuf,'(2A)') 'CONFIG_CHECK: ',
118         &   'but implicitDiffusion=T with non-uniform dTtracerLev'
119            CALL PRINT_ERROR( msgBuf, myThid )
120            STOP 'ABNORMAL END: S/R CONFIG_CHECK'
121          ENDIF
122    #endif
123    
124    #ifdef ALLOW_AUTODIFF_TAMC
125          IF ( momImplVertAdv ) THEN
126            WRITE(msgBuf,'(A)')
127         &   'CONFIG_CHECK: momImplVertAdv is not yet'
128            CALL PRINT_ERROR( msgBuf, myThid )
129            WRITE(msgBuf,'(A)')
130         &   'CONFIG_CHECK: supported in adjoint mode'
131            CALL PRINT_ERROR( msgBuf, myThid )
132            STOP 'ABNORMAL END: S/R CONFIG_CHECK'
133          ENDIF
134    #endif
135    
136    #ifdef ALLOW_DEPTH_CONTROL
137          IF ( implicitDiffusion ) THEN
138            WRITE(msgBuf,'(2A)') 'CONFIG_CHECK: ',
139         &       'implicitDiffusion not available with DEPTH_CONTROL'
140            CALL PRINT_ERROR( msgBuf, myThid )
141            STOP 'ABNORMAL END: S/R CONFIG_CHECK'
142          ENDIF
143          IF ( useOBCS ) THEN
144            WRITE(msgBuf,'(A)')
145         &   'CONFIG_CHECK: DEPTH_CONTROL code not compatible with OBCS'
146            CALL PRINT_ERROR( msgBuf, myThid )
147          STOP 'ABNORMAL END: S/R CONFIG_CHECK'          STOP 'ABNORMAL END: S/R CONFIG_CHECK'
148        ENDIF        ENDIF
149  #endif  #endif
150    
151  #ifndef EXACT_CONSERV  #ifndef EXACT_CONSERV
152        IF (exactConserv) THEN        IF (exactConserv) THEN
153          WRITE(msgBuf,'(A)')          WRITE(msgBuf,'(A)')
154       &   'CONFIG_CHECK: #undef EXACT_CONSERV and'       &   'CONFIG_CHECK: #undef EXACT_CONSERV and'
155          CALL PRINT_ERROR( msgBuf , myThid)          CALL PRINT_ERROR( msgBuf, myThid )
156          WRITE(msgBuf,'(A)')          WRITE(msgBuf,'(A)')
157       &   'CONFIG_CHECK: exactConserv is TRUE'       &   'CONFIG_CHECK: exactConserv is TRUE'
158          CALL PRINT_ERROR( msgBuf , myThid)          CALL PRINT_ERROR( msgBuf, myThid )
159          STOP 'ABNORMAL END: S/R CONFIG_CHECK'          STOP 'ABNORMAL END: S/R CONFIG_CHECK'
160        ENDIF        ENDIF
161  #endif  #endif
162    
163  #ifndef NONLIN_FRSURF  #ifndef NONLIN_FRSURF
164        IF (nonlinFreeSurf.NE.0) THEN        IF (nonlinFreeSurf.NE.0) THEN
165          WRITE(msgBuf,'(A)')          WRITE(msgBuf,'(A)')
166       &   'CONFIG_CHECK: #undef NONLIN_FRSURF and'       &   'CONFIG_CHECK: #undef NONLIN_FRSURF and'
167          CALL PRINT_ERROR( msgBuf , myThid)          CALL PRINT_ERROR( msgBuf, myThid )
168          WRITE(msgBuf,'(A)')          WRITE(msgBuf,'(A)')
169       &   'CONFIG_CHECK: nonlinFreeSurf is non-zero'       &   'CONFIG_CHECK: nonlinFreeSurf is non-zero'
170          CALL PRINT_ERROR( msgBuf , myThid)          CALL PRINT_ERROR( msgBuf, myThid )
171          STOP 'ABNORMAL END: S/R CONFIG_CHECK'          STOP 'ABNORMAL END: S/R CONFIG_CHECK'
172        ENDIF        ENDIF
173  #endif  #endif
174    
175  #ifndef NONLIN_FRSURF  #ifndef NONLIN_FRSURF
176        IF (select_rStar .NE. 0) THEN        IF (select_rStar .NE. 0) THEN
177          WRITE(msgBuf,'(A)')          WRITE(msgBuf,'(A)')
178       &   'CONFIG_CHECK: rStar is part of NonLin-FS '       &   'CONFIG_CHECK: rStar is part of NonLin-FS '
179          CALL PRINT_ERROR( msgBuf, myThid)                                CALL PRINT_ERROR( msgBuf, myThid )
180          WRITE(msgBuf,'(A)')          WRITE(msgBuf,'(A)')
181       &   'CONFIG_CHECK: ==> use #define NONLIN_FRSURF to use it'       &   'CONFIG_CHECK: ==> set #define NONLIN_FRSURF to use it'
182          CALL PRINT_ERROR( msgBuf, myThid)                                CALL PRINT_ERROR( msgBuf, myThid )
183          STOP 'ABNORMAL END: S/R CONFIG_CHECK'          STOP 'ABNORMAL END: S/R CONFIG_CHECK'
184        ENDIF        ENDIF
185  #endif /* NONLIN_FRSURF */  #endif /* NONLIN_FRSURF */
186    
187    #ifdef DISABLE_RSTAR_CODE
188          IF ( select_rStar.NE.0 ) THEN
189            WRITE(msgBuf,'(A)')
190         &   'CONFIG_CHECK: rStar code disable (DISABLE_RSTAR_CODE defined)'
191            CALL PRINT_ERROR( msgBuf, myThid )
192            WRITE(msgBuf,'(A)')
193         &   'CONFIG_CHECK: ==> set #undef DISABLE_RSTAR_CODE to use it'
194            CALL PRINT_ERROR( msgBuf, myThid )
195            STOP 'ABNORMAL END: S/R CONFIG_CHECK'
196          ENDIF
197    #endif /* DISABLE_RSTAR_CODE */
198    
199    #ifdef DISABLE_SIGMA_CODE
200          IF ( selectSigmaCoord.NE.0 ) THEN
201            WRITE(msgBuf,'(A)')
202         &   'CONFIG_CHECK: Sigma code disable (DISABLE_SIGMA_CODE defined)'
203            CALL PRINT_ERROR( msgBuf, myThid )
204            WRITE(msgBuf,'(A)')
205         &   'CONFIG_CHECK: ==> set #undef DISABLE_SIGMA_CODE to use it'
206            CALL PRINT_ERROR( msgBuf, myThid )
207            STOP 'ABNORMAL END: S/R CONFIG_CHECK'
208          ENDIF
209    #endif /* DISABLE_SIGMA_CODE */
210    
211  #ifdef USE_NATURAL_BCS  #ifdef USE_NATURAL_BCS
212          WRITE(msgBuf,'(A)')          WRITE(msgBuf,'(A)')
213       &   'CONFIG_CHECK: USE_NATURAL_BCS option has been replaced'       &   'CONFIG_CHECK: USE_NATURAL_BCS option has been replaced'
214          CALL PRINT_ERROR( msgBuf , myThid)          CALL PRINT_ERROR( msgBuf, myThid )
215          WRITE(msgBuf,'(A)')          WRITE(msgBuf,'(A)')
216       &   'CONFIG_CHECK: by useRealFreshWaterFlux=TRUE in data file'       &   'CONFIG_CHECK: by useRealFreshWaterFlux=TRUE in data file'
217          CALL PRINT_ERROR( msgBuf , myThid)          CALL PRINT_ERROR( msgBuf, myThid )
218          STOP 'ABNORMAL END: S/R CONFIG_CHECK'          STOP 'ABNORMAL END: S/R CONFIG_CHECK'
219  #endif  #endif
220    
221    #ifndef ALLOW_ADDFLUID
222          IF ( selectAddFluid.NE.0 ) THEN
223            WRITE(msgBuf,'(A)')
224         &   'CONFIG_CHECK: #undef ALLOW_ADDFLUID and'
225            CALL PRINT_ERROR( msgBuf, myThid )
226            WRITE(msgBuf,'(A,I4,A)') 'CONFIG_CHECK: selectAddFluid=',
227         &                           selectAddFluid, ' is not zero'
228            CALL PRINT_ERROR( msgBuf, myThid )
229            STOP 'ABNORMAL END: S/R CONFIG_CHECK'
230          ENDIF
231    #endif /* ALLOW_ADDFLUID */
232    
233  C     o If pLoadFile is set, then we should make sure the corresponing  C     o If pLoadFile is set, then we should make sure the corresponing
234  C       code is being compiled  C       code is being compiled
235  #ifndef ATMOSPHERIC_LOADING  #ifndef ATMOSPHERIC_LOADING
236        IF (pLoadFile.NE.' ') THEN        IF (pLoadFile.NE.' ') THEN
237          WRITE(msgBuf,'(A)')          WRITE(msgBuf,'(A)')
238       &  'CONFIG_CHECK: pLoadFile is set but you have not'       &  'CONFIG_CHECK: pLoadFile is set but you have not'
239          CALL PRINT_ERROR( msgBuf , myThid)          CALL PRINT_ERROR( msgBuf, myThid )
240          WRITE(msgBuf,'(A)')          WRITE(msgBuf,'(A)')
241       &  'compiled the model with the pressure loading code.'       &  'compiled the model with the pressure loading code.'
242          CALL PRINT_ERROR( msgBuf , myThid)          CALL PRINT_ERROR( msgBuf, myThid )
243          WRITE(msgBuf,'(A,A)')          WRITE(msgBuf,'(A)')
244       &  'Re-compile with:  #define ATMOSPHERIC_LOADING',       &  'Re-compile with:  #define ATMOSPHERIC_LOADING'
245       &  '              or  -DATMOSPHERIC_LOADING'          CALL PRINT_ERROR( msgBuf, myThid )
         CALL PRINT_ERROR( msgBuf , myThid)  
246          STOP 'ABNORMAL END: S/R CONFIG_CHECK'          STOP 'ABNORMAL END: S/R CONFIG_CHECK'
247        ENDIF        ENDIF
248  #endif        IF ( useRealFreshWaterFlux .AND. useThSIce ) THEN
249            WRITE(msgBuf,'(A)')
250  C     o If taveFreq is finite, then we must make sure the diagnostics       &  'CONFIG_CHECK: sIceLoad is computed but'
251  C       code is being compiled          CALL PRINT_ERROR( msgBuf, myThid )
 #ifndef ALLOW_TIMEAVE  
       IF (taveFreq.NE.0.) THEN  
252          WRITE(msgBuf,'(A)')          WRITE(msgBuf,'(A)')
253       &  'CONFIG_CHECK: taveFreq <> 0  but you have'       &  'pressure loading code is not compiled.'
254          CALL PRINT_ERROR( msgBuf , 1)          CALL PRINT_ERROR( msgBuf, myThid )
255          WRITE(msgBuf,'(A)')          WRITE(msgBuf,'(A)')
256       &  'not compiled the model with the diagnostics routines.'       &  'Re-compile with:  #define ATMOSPHERIC_LOADING'
257          CALL PRINT_ERROR( msgBuf , 1)          CALL PRINT_ERROR( msgBuf, myThid )
258            STOP 'ABNORMAL END: S/R CONFIG_CHECK'
259          ENDIF
260    #endif
261    
262    #ifndef ALLOW_BALANCE_FLUXES
263          IF (balanceEmPmR .OR. balanceQnet) THEN
264          WRITE(msgBuf,'(A,A)')          WRITE(msgBuf,'(A,A)')
265       &  'Re-compile with:  #define ALLOW_TIMEAVE',       &  'CONFIG_CHECK: balanceEmPmR/Qnet is set but balance code ',
266       &  '              or  -DALLOW_TIMEAVE'       &  'is not compiled.'
267          CALL PRINT_ERROR( msgBuf , 1)          CALL PRINT_ERROR( msgBuf, myThid )
268            WRITE(msgBuf,'(A)')
269         &  'Re-compile with  ALLOW_BALANCE_FLUXES defined'
270            CALL PRINT_ERROR( msgBuf, myThid )
271          STOP 'ABNORMAL END: S/R CONFIG_CHECK'          STOP 'ABNORMAL END: S/R CONFIG_CHECK'
272        ENDIF        ENDIF
273  #endif  #endif
274    
275    #ifndef ALLOW_SRCG
276          IF (useSRCGSolver) THEN
277            WRITE(msgBuf,'(A,A)')
278         &  'CONFIG_CHECK: useSRCGSolver = .TRUE., but single reduction ',
279         &  'code is not compiled.'
280            CALL PRINT_ERROR( msgBuf, myThid )
281            WRITE(msgBuf,'(A)')
282         &  'CONFIG_CHECK: Re-compile with ALLOW_SRCG defined'
283            CALL PRINT_ERROR( msgBuf, myThid )
284            STOP 'ABNORMAL END: S/R CONFIG_CHECK'
285          ENDIF
286    #endif /* ALLOW_SRCG */
287    
288  C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|  C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
289    
290  C-  check parameter consistency :  C--   Check parameter consistency :
291    
292        IF ( viscA4.NE.0. .AND. (Olx.LT.3 .OR. Oly.LT.3)) THEN        IF ( ( OLx.LT.3 .OR. OLy.LT.3 ) .AND.
293         &     ( viscC4leithD.NE.0.  .OR. viscC4leith.NE.0.
294         &     .OR. viscC4smag.NE.0. .OR. viscA4Grid.NE.0.
295         &     .OR. viscA4D.NE.0.    .OR. viscA4Z.NE.0. ) ) THEN
296          WRITE(msgBuf,'(A,A)')          WRITE(msgBuf,'(A,A)')
297       &  'CONFIG_CHECK: cannot use Biharmonic Visc. (viscA4) with',       &  'CONFIG_CHECK: cannot use Biharmonic Visc. (viscA4) with',
298       &  ' overlap (Olx,Oly) smaller than 3'       &  ' overlap (OLx,OLy) smaller than 3'
299          CALL PRINT_ERROR( msgBuf , myThid)          CALL PRINT_ERROR( msgBuf, myThid )
300            STOP 'ABNORMAL END: S/R CONFIG_CHECK'
301          ENDIF
302          IF ( ( OLx.LT.3 .OR. OLy.LT.3 ) .AND.
303         &     ( viscC2leithD.NE.0. .OR. viscC4leithD.NE.0. )
304         &   ) THEN
305            WRITE(msgBuf,'(A,A)')
306         &  'CONFIG_CHECK: cannot use Leith Visc.(div.part) with',
307         &  ' overlap (OLx,OLy) smaller than 3'
308            CALL PRINT_ERROR( msgBuf, myThid )
309            STOP 'ABNORMAL END: S/R CONFIG_CHECK'
310          ENDIF
311    
312    C     Overlaps cannot be larger than interior tile except for special
313    C     cases
314          IF ( sNx.LT.OLx ) THEN
315    #ifdef ALLOW_EXCH2
316           WRITE(msgBuf,'(A)')
317         &  'CONFIG_CHECK: sNx<OLx not allowed with ALLOW_EXCH2 defined'
318           CALL PRINT_ERROR( msgBuf, myThid )
319           STOP 'ABNORMAL END: S/R CONFIG_CHECK'
320    #endif /* ALLOW_EXCH2 */
321           IF ( Nx.NE.1 ) THEN
322            WRITE(msgBuf,'(A)')
323         &  'CONFIG_CHECK: sNx<OLx not allowed unless Nx=1'
324            CALL PRINT_ERROR( msgBuf, myThid )
325            STOP 'ABNORMAL END: S/R CONFIG_CHECK'
326           ENDIF
327          ENDIF
328          IF ( sNy.LT.OLy ) THEN
329    #ifdef ALLOW_EXCH2
330           WRITE(msgBuf,'(A)')
331         &  'CONFIG_CHECK: sNy<OLy not allowed with ALLOW_EXCH2 defined'
332           CALL PRINT_ERROR( msgBuf, myThid )
333           STOP 'ABNORMAL END: S/R CONFIG_CHECK'
334    #endif /* ALLOW_EXCH2 */
335           IF ( Ny.NE.1 ) THEN
336            WRITE(msgBuf,'(A)')
337         &  'CONFIG_CHECK: sNy<OLy not allowed unless Ny=1'
338            CALL PRINT_ERROR( msgBuf, myThid )
339            STOP 'ABNORMAL END: S/R CONFIG_CHECK'
340           ENDIF
341          ENDIF
342    
343    C--   Deep-Atmosphere & Anelastic limitations:
344          IF ( deepAtmosphere .AND.
345         &     useRealFreshWaterFlux .AND. usingPCoords ) THEN
346            WRITE(msgBuf,'(A,A)')
347         &  'CONFIG_CHECK: Deep-Atmosphere not yet implemented with',
348         &  ' real-Fresh-Water option in P-coordinate'
349            CALL PRINT_ERROR( msgBuf, myThid )
350            STOP 'ABNORMAL END: S/R CONFIG_CHECK'
351          ENDIF
352          IF ( select_rStar.NE.0 .AND.
353         &        ( deepAtmosphere .OR.
354         &          usingZCoords.AND.rhoRefFile .NE. ' ' ) ) THEN
355            WRITE(msgBuf,'(A,A)')
356         &  'CONFIG_CHECK: Deep-Atmosphere or Anelastic',
357         &  ' not yet implemented with rStar'
358            CALL PRINT_ERROR( msgBuf, myThid )
359          STOP 'ABNORMAL END: S/R CONFIG_CHECK'          STOP 'ABNORMAL END: S/R CONFIG_CHECK'
360        ENDIF                        ENDIF
361          IF ( vectorInvariantMomentum .AND.
362         &        ( deepAtmosphere .OR.
363         &          usingZCoords.AND.rhoRefFile .NE. ' ' ) ) THEN
364            WRITE(msgBuf,'(A,A)')
365         &  'CONFIG_CHECK: Deep-Atmosphere or Anelastic',
366         &  ' not yet implemented in Vector-Invariant momentum code'
367            CALL PRINT_ERROR( msgBuf, myThid )
368            STOP 'ABNORMAL END: S/R CONFIG_CHECK'
369          ENDIF
370    
371    C--   Free-surface related limitations:
372        IF ( rigidLid .AND. implicitFreeSurface ) THEN        IF ( rigidLid .AND. implicitFreeSurface ) THEN
373          WRITE(msgBuf,'(A,A)')          WRITE(msgBuf,'(A,A)')
374       &  'CONFIG_CHECK: Cannot select both implicitFreeSurface',       &  'CONFIG_CHECK: Cannot select both implicitFreeSurface',
375       &  ' and rigidLid.'       &  ' and rigidLid.'
376          CALL PRINT_ERROR( msgBuf , myThid)          CALL PRINT_ERROR( msgBuf, myThid )
377          STOP 'ABNORMAL END: S/R CONFIG_CHECK'          STOP 'ABNORMAL END: S/R CONFIG_CHECK'
378        ENDIF                        ENDIF
379    
380        IF (rigidLid .AND. exactConserv) THEN        IF (rigidLid .AND. exactConserv) THEN
381          WRITE(msgBuf,'(A)')          WRITE(msgBuf,'(A)')
382       &   'CONFIG_CHECK: exactConserv not compatible with'       &   'CONFIG_CHECK: exactConserv not compatible with'
383          CALL PRINT_ERROR( msgBuf , myThid)          CALL PRINT_ERROR( msgBuf, myThid )
384          WRITE(msgBuf,'(A)')          WRITE(msgBuf,'(A)')
385       &   'CONFIG_CHECK: rigidLid (meaningless in that case)'       &   'CONFIG_CHECK: rigidLid (meaningless in that case)'
386          CALL PRINT_ERROR( msgBuf , myThid)          CALL PRINT_ERROR( msgBuf, myThid )
387          STOP 'ABNORMAL END: S/R CONFIG_CHECK'          STOP 'ABNORMAL END: S/R CONFIG_CHECK'
388        ENDIF        ENDIF
389    
390        IF (rigidLid .AND. useRealFreshWaterFlux) THEN        IF ( linFSConserveTr .AND. nonlinFreeSurf.NE.0 ) THEN
         WRITE(msgBuf,'(A)')  
      &   'CONFIG_CHECK: useRealFreshWaterFlux not compatible with'  
         CALL PRINT_ERROR( msgBuf , myThid)  
391          WRITE(msgBuf,'(A)')          WRITE(msgBuf,'(A)')
392       &   'CONFIG_CHECK: rigidLid (meaningless in that case)'       &   'CONFIG_CHECK: Cannot select both a Nonlinear Free Surf.'
393          CALL PRINT_ERROR( msgBuf , myThid)          CALL PRINT_ERROR( msgBuf, myThid )
394            WRITE(msgBuf,'(A)')
395         &   'CONFIG_CHECK: and Tracer Correction of Lin. Free Surf.'
396            CALL PRINT_ERROR( msgBuf, myThid )
397          STOP 'ABNORMAL END: S/R CONFIG_CHECK'          STOP 'ABNORMAL END: S/R CONFIG_CHECK'
398        ENDIF        ENDIF
399    
400        IF ( (implicSurfPress.NE.1. .OR. implicDiv2DFlow.NE.1.)        IF (rigidLid .AND. useRealFreshWaterFlux) THEN
401       &    .AND. nonHydrostatic ) THEN          WRITE(msgBuf,'(A)')
402          WRITE(msgBuf,'(A,A)') 'CONFIG_CHECK: nonHydrostatic',       &   'CONFIG_CHECK: useRealFreshWaterFlux not compatible with'
403       & ' NOT SAFE with non-fully implicit Barotropic solver'          CALL PRINT_ERROR( msgBuf, myThid )
404          CALL PRINT_ERROR( msgBuf , myThid)          WRITE(msgBuf,'(A)')
405          WRITE(msgBuf,'(A,A)') 'CONFIG_CHECK: To by-pass this',       &   'CONFIG_CHECK: rigidLid (meaningless in that case)'
406       &    'STOP, comment this test and re-compile config_check'          CALL PRINT_ERROR( msgBuf, myThid )
         CALL PRINT_ERROR( msgBuf , myThid)  
407          STOP 'ABNORMAL END: S/R CONFIG_CHECK'          STOP 'ABNORMAL END: S/R CONFIG_CHECK'
408        ENDIF        ENDIF
409    
410        IF (nonlinFreeSurf.NE.0 .AND. .NOT.exactConserv) THEN        IF (nonlinFreeSurf.NE.0 .AND. .NOT.exactConserv) THEN
411          WRITE(msgBuf,'(A)')          WRITE(msgBuf,'(A)')
412       &   'CONFIG_CHECK: nonlinFreeSurf cannot be used'       &   'CONFIG_CHECK: nonlinFreeSurf cannot be used'
413          CALL PRINT_ERROR( msgBuf , myThid)          CALL PRINT_ERROR( msgBuf, myThid )
414          WRITE(msgBuf,'(A)')          WRITE(msgBuf,'(A)')
415       &   'CONFIG_CHECK: without exactConserv'       &   'CONFIG_CHECK: without exactConserv'
416          CALL PRINT_ERROR( msgBuf , myThid)          CALL PRINT_ERROR( msgBuf, myThid )
417          STOP 'ABNORMAL END: S/R CONFIG_CHECK'          STOP 'ABNORMAL END: S/R CONFIG_CHECK'
418        ENDIF        ENDIF
419    
420        IF (select_rStar.NE.0 .AND. .NOT.exactConserv) THEN        IF (select_rStar.NE.0 .AND. .NOT.exactConserv) THEN
421          WRITE(msgBuf,'(A)')          WRITE(msgBuf,'(A)')
422       &   'CONFIG_CHECK: r* Coordinate cannot be used'       &   'CONFIG_CHECK: r* Coordinate cannot be used'
423          CALL PRINT_ERROR( msgBuf , myThid)          CALL PRINT_ERROR( msgBuf, myThid )
424          WRITE(msgBuf,'(A)')          WRITE(msgBuf,'(A)')
425       &   'CONFIG_CHECK: without exactConserv'       &   'CONFIG_CHECK: without exactConserv'
426          CALL PRINT_ERROR( msgBuf , myThid)          CALL PRINT_ERROR( msgBuf, myThid )
427          STOP 'ABNORMAL END: S/R CONFIG_CHECK'          STOP 'ABNORMAL END: S/R CONFIG_CHECK'
428        ENDIF        ENDIF
429    
430  C- note : not implemented in checkpoint48b but it's done now (since 01-28-03)        IF ( selectSigmaCoord.NE.0 ) THEN
431  c     IF (select_rStar.GT.0 .AND. useOBCS ) THEN         IF ( fluidIsWater ) THEN
 c       WRITE(msgBuf,'(A)')  
 c    &   'CONFIG_CHECK: r* Coordinate not yet implemented'  
 c       CALL PRINT_ERROR( msgBuf , 1)  
 c       WRITE(msgBuf,'(A)')  
 c    &   'CONFIG_CHECK: in OBC package'  
 c       CALL PRINT_ERROR( msgBuf , 1)  
 c       STOP 'ABNORMAL END: S/R CONFIG_CHECK'  
 c     ENDIF  
   
       IF (nonlinFreeSurf.NE.0 .AND. nonHydrostatic) THEN  
         WRITE(msgBuf,'(A)')  
      &   'CONFIG_CHECK: nonlinFreeSurf not yet implemented'  
         CALL PRINT_ERROR( msgBuf , myThid)  
432          WRITE(msgBuf,'(A)')          WRITE(msgBuf,'(A)')
433       &   'CONFIG_CHECK: in nonHydrostatic code'       &   'CONFIG_CHECK: Sigma-Coords not yet coded for Oceanic set-up'
434          CALL PRINT_ERROR( msgBuf , myThid)          CALL PRINT_ERROR( msgBuf, myThid )
435            STOP 'ABNORMAL END: S/R CONFIG_CHECK'
436           ENDIF
437           IF ( nonlinFreeSurf.LE.0 ) THEN
438            WRITE(msgBuf,'(A)')
439         &   'CONFIG_CHECK: Sigma-Coords not coded for Lin-FreeSurf'
440            CALL PRINT_ERROR( msgBuf, myThid )
441            STOP 'ABNORMAL END: S/R CONFIG_CHECK'
442           ENDIF
443           IF (select_rStar.NE.0 ) THEN
444            WRITE(msgBuf,'(A)')
445         &   'CONFIG_CHECK: Sigma-Coords and rStar are not compatible'
446            CALL PRINT_ERROR( msgBuf, myThid )
447          STOP 'ABNORMAL END: S/R CONFIG_CHECK'          STOP 'ABNORMAL END: S/R CONFIG_CHECK'
448           ENDIF
449            WRITE(msgBuf,'(A)')
450         &   'CONFIG_CHECK: Sigma-Coords code neither complete nor tested'
451            CALL PRINT_MESSAGE( msgBuf, errorMessageUnit,
452         &                      SQUEEZE_RIGHT, myThid )
453        ENDIF        ENDIF
454    
455        IF (nonlinFreeSurf.NE.0.AND.deltaTfreesurf.NE.deltaTtracer) THEN  C- note : not implemented in checkpoint48b but it is done now (since 01-28-03)
456          WRITE(msgBuf,'(A)')  c     IF (select_rStar.GT.0 .AND. useOBCS ) THEN
457       &   'CONFIG_CHECK: WARNING: nonlinFreeSurf might cause problems'  c       STOP 'ABNORMAL END: S/R CONFIG_CHECK'
458    c     ENDIF
459    
460          IF ( nonlinFreeSurf.NE.0 .AND.
461         &     deltaTfreesurf.NE.dTtracerLev(1) ) THEN
462            WRITE(msgBuf,'(2A)') '** WARNING ** CONFIG_CHECK: ',
463         &                       'nonlinFreeSurf might cause problems'
464          CALL PRINT_MESSAGE( msgBuf, errorMessageUnit,          CALL PRINT_MESSAGE( msgBuf, errorMessageUnit,
465       &                    SQUEEZE_RIGHT , myThid)                             &                      SQUEEZE_RIGHT, myThid )
466          WRITE(msgBuf,'(A)')          WRITE(msgBuf,'(2A)') '** WARNING ** ',
467       &   'CONFIG_CHECK: with different FreeSurf & Tracer time-steps'       &               'with different FreeSurf & Tracer time-steps'
468          CALL PRINT_MESSAGE( msgBuf, errorMessageUnit,          CALL PRINT_MESSAGE( msgBuf, errorMessageUnit,
469       &                    SQUEEZE_RIGHT , myThid)                             &                      SQUEEZE_RIGHT, myThid )
470        ENDIF        ENDIF
471    
472        IF (useRealFreshWaterFlux .AND. exactConserv        IF ( useRealFreshWaterFlux .AND. exactConserv
473       &    .AND.startTime.NE.0. .AND. implicSurfPress.EQ.0. _d 0) THEN       &     .AND. implicDiv2Dflow.EQ.0. _d 0
474          WRITE(msgBuf,'(A)')       &     .AND. startTime.NE.baseTime .AND. usePickupBeforeC54 ) THEN
475            WRITE(msgBuf,'(A)')
476       &   'CONFIG_CHECK: RealFreshWaterFlux+implicSurfP=0+exactConserv:'       &   'CONFIG_CHECK: RealFreshWaterFlux+implicSurfP=0+exactConserv:'
477          CALL PRINT_ERROR( msgBuf , myThid)          CALL PRINT_ERROR( msgBuf, myThid )
478          WRITE(msgBuf,'(A)')          WRITE(msgBuf,'(A)')
479       &   'CONFIG_CHECK: restart not implemented in this config'       &   'CONFIG_CHECK: restart not implemented in this config'
480          CALL PRINT_ERROR( msgBuf , myThid)          CALL PRINT_ERROR( msgBuf, myThid )
481          STOP 'ABNORMAL END: S/R CONFIG_CHECK'          STOP 'ABNORMAL END: S/R CONFIG_CHECK'
482        ENDIF        ENDIF
483    
484  #ifdef NONLIN_FRSURF        IF ( useRealFreshWaterFlux .AND. .NOT.exactConserv
485         &     .AND. implicDiv2Dflow.NE.1. ) THEN
486            WRITE(msgBuf,'(2A)') '** WARNING ** CONFIG_CHECK: ',
487         &   'RealFreshWater & implicDiv2Dflow < 1'
488            CALL PRINT_MESSAGE( msgBuf, errorMessageUnit,
489         &                      SQUEEZE_RIGHT, myThid )
490            WRITE(msgBuf,'(2A)') '** WARNING ** works better',
491         &   ' with exactConserv=.T. (+ #define EXACT_CONSERV)'
492            CALL PRINT_MESSAGE( msgBuf, errorMessageUnit,
493         &                      SQUEEZE_RIGHT, myThid )
494          ENDIF
495    
496    #ifdef EXACT_CONSERV
497        IF (useRealFreshWaterFlux .AND. .NOT.exactConserv        IF (useRealFreshWaterFlux .AND. .NOT.exactConserv
498       &            .AND. buoyancyRelation.EQ.'OCEANICP' ) THEN       &            .AND. buoyancyRelation.EQ.'OCEANICP' ) THEN
499          WRITE(msgBuf,'(A)')          WRITE(msgBuf,'(A)')
500       &   'CONFIG_CHECK: RealFreshWaterFlux with OCEANICP'       &   'CONFIG_CHECK: RealFreshWaterFlux with OCEANICP'
501          CALL PRINT_ERROR( msgBuf , myThid)          CALL PRINT_ERROR( msgBuf, myThid )
502          WRITE(msgBuf,'(A)')          WRITE(msgBuf,'(A)')
503       &   'CONFIG_CHECK: requires exactConserv=T'       &   'CONFIG_CHECK: requires exactConserv=T'
504          CALL PRINT_ERROR( msgBuf , myThid)          CALL PRINT_ERROR( msgBuf, myThid )
505          STOP 'ABNORMAL END: S/R CONFIG_CHECK'          STOP 'ABNORMAL END: S/R CONFIG_CHECK'
506        ENDIF        ENDIF
507  #else  #else
508        IF (useRealFreshWaterFlux .AND. exactConserv        IF (useRealFreshWaterFlux
509       &            .AND. implicSurfPress.NE.1. _d 0 ) THEN       &            .AND. buoyancyRelation.EQ.'OCEANICP' ) THEN
510          WRITE(msgBuf,'(A)')          WRITE(msgBuf,'(2A)') '** WARNING ** CONFIG_CHECK: ',
511       &   'CONFIG_CHECK: Pb with restart in this config'       &               'E-P effects on wVel are not included'
512          CALL PRINT_ERROR( msgBuf , myThid)          CALL PRINT_MESSAGE( msgBuf, errorMessageUnit,
513         &                      SQUEEZE_RIGHT, myThid )
514            WRITE(msgBuf,'(2A)') '** WARNING ** CONFIG_CHECK: ',
515         &               '==> use #define EXACT_CONSERV to fix it'
516            CALL PRINT_MESSAGE( msgBuf, errorMessageUnit,
517         &                      SQUEEZE_RIGHT, myThid )
518          ENDIF
519    #endif /* EXACT_CONSERV */
520    
521          IF ( selectAddFluid.LT.-1 .OR. selectAddFluid.GT.2 ) THEN
522            WRITE(msgBuf,'(A,I10,A)') 'CONFIG_CHECK: selectAddFluid=',
523         &                             selectAddFluid, ' not allowed'
524            CALL PRINT_ERROR( msgBuf, myThid )
525            WRITE(msgBuf,'(2A)') 'CONFIG_CHECK: ',
526         &       'should be =0 (Off), 1,2 (Add Mass) or -1 (Virtual Flux)'
527            CALL PRINT_ERROR( msgBuf, myThid )
528            STOP 'ABNORMAL END: S/R CONFIG_CHECK'
529          ENDIF
530          IF ( selectAddFluid.GE.1 .AND. rigidLid ) THEN
531          WRITE(msgBuf,'(A)')          WRITE(msgBuf,'(A)')
532       &   'CONFIG_CHECK: ==> use #define NONLIN_FRSURF to fix it'       &   'CONFIG_CHECK: selectAddFluid > 0 not compatible with'
533          CALL PRINT_ERROR( msgBuf , myThid)          CALL PRINT_ERROR( msgBuf, myThid )
534            WRITE(msgBuf,'(A)')
535         &   'CONFIG_CHECK: rigidLid (meaningless in that case)'
536            CALL PRINT_ERROR( msgBuf, myThid )
537          STOP 'ABNORMAL END: S/R CONFIG_CHECK'          STOP 'ABNORMAL END: S/R CONFIG_CHECK'
538        ENDIF        ENDIF
539          IF ( selectAddFluid.GE.1 .AND. .NOT.staggerTimeStep ) THEN
540        IF (useRealFreshWaterFlux          WRITE(msgBuf,'(2A)') '** WARNING ** CONFIG_CHECK: ',
541       &            .AND. buoyancyRelation.EQ.'OCEANICP' ) THEN       &   'synchronous time-stepping =>'
542          WRITE(msgBuf,'(A)')          CALL PRINT_MESSAGE( msgBuf, errorMessageUnit,
543       &   'CONFIG_CHECK: E-P effects on wVel are not included'       &                      SQUEEZE_RIGHT, myThid )
544            WRITE(msgBuf,'(2A)') '** WARNING ** ',
545         &   '1 time-step mismatch in AddFluid effects on T & S'
546          CALL PRINT_MESSAGE( msgBuf, errorMessageUnit,          CALL PRINT_MESSAGE( msgBuf, errorMessageUnit,
547       &                    SQUEEZE_RIGHT , myThid)                             &                      SQUEEZE_RIGHT, myThid )
548          ENDIF
549    
550    C--   Non-hydrostatic and 3-D solver related limitations:
551          IF (nonlinFreeSurf.NE.0 .AND. use3Dsolver) THEN
552            WRITE(msgBuf,'(A)')
553         &   'CONFIG_CHECK: nonlinFreeSurf not yet implemented'
554            CALL PRINT_ERROR( msgBuf, myThid )
555          WRITE(msgBuf,'(A)')          WRITE(msgBuf,'(A)')
556       &   'CONFIG_CHECK: ==> use #define NONLIN_FRSURF to fix it'       &   'CONFIG_CHECK: in nonHydrostatic code'
557            CALL PRINT_ERROR( msgBuf, myThid )
558            STOP 'ABNORMAL END: S/R CONFIG_CHECK'
559          ENDIF
560    
561          IF ( implicitNHPress*implicSurfPress*implicDiv2Dflow.NE.1.
562         &     .AND. implicitIntGravWave ) THEN
563            WRITE(msgBuf,'(2A)') 'CONFIG_CHECK: implicitIntGravWave',
564         &    ' NOT SAFE with non-fully implicit solver'
565            CALL PRINT_ERROR( msgBuf, myThid )
566            WRITE(msgBuf,'(2A)') 'CONFIG_CHECK: To by-pass this',
567         &    'STOP, comment this test and re-compile config_check'
568            CALL PRINT_ERROR( msgBuf, myThid )
569            STOP 'ABNORMAL END: S/R CONFIG_CHECK'
570          ENDIF
571          IF ( nonHydrostatic .AND. .NOT.exactConserv
572         &     .AND. implicDiv2Dflow.NE.1. ) THEN
573            WRITE(msgBuf,'(2A)') 'CONFIG_CHECK: Needs exactConserv=T',
574         &               ' for nonHydrostatic with implicDiv2Dflow < 1'
575            CALL PRINT_ERROR( msgBuf, myThid )
576            STOP 'ABNORMAL END: S/R CONFIG_CHECK'
577          ENDIF
578          IF ( nonHydrostatic .AND.
579         &     implicitNHPress.NE.implicSurfPress ) THEN
580            WRITE(msgBuf,'(2A)') '** WARNING ** CONFIG_CHECK: ',
581         &               ' nonHydrostatic might cause problems with'
582            CALL PRINT_MESSAGE( msgBuf, errorMessageUnit,
583         &                      SQUEEZE_RIGHT, myThid )
584            WRITE(msgBuf,'(2A)') '** WARNING ** CONFIG_CHECK: ',
585         &               'different implicitNHPress & implicSurfPress'
586          CALL PRINT_MESSAGE( msgBuf, errorMessageUnit,          CALL PRINT_MESSAGE( msgBuf, errorMessageUnit,
587       &                    SQUEEZE_RIGHT , myThid)                             &                      SQUEEZE_RIGHT, myThid )
588          ENDIF
589    
590          IF ( implicitViscosity .AND. use3Dsolver ) THEN
591            WRITE(msgBuf,'(2A)') '** WARNING ** CONFIG_CHECK: ',
592         &    'Implicit viscosity applies to provisional u,vVel'
593            CALL PRINT_MESSAGE( msgBuf, errorMessageUnit,
594         &                      SQUEEZE_RIGHT, myThid )
595            WRITE(msgBuf,'(2A)') '** WARNING ** => not consistent with',
596         &    'final vertical shear (after appling 3-D solver solution'
597            CALL PRINT_MESSAGE( msgBuf, errorMessageUnit,
598         &                      SQUEEZE_RIGHT, myThid )
599          ENDIF
600          IF ( implicitViscosity .AND. nonHydrostatic ) THEN
601            WRITE(msgBuf,'(2A)') '** WARNING ** CONFIG_CHECK: ',
602         &    'Implicit viscosity not implemented in CALC_GW'
603            CALL PRINT_MESSAGE( msgBuf, errorMessageUnit,
604         &                      SQUEEZE_RIGHT, myThid )
605            WRITE(msgBuf,'(2A)') '** WARNING ** CONFIG_CHECK: ',
606         &    'Explicit viscosity might become unstable if too large'
607            CALL PRINT_MESSAGE( msgBuf, errorMessageUnit,
608         &                      SQUEEZE_RIGHT, myThid )
609          ENDIF
610    
611    C--   Momentum related limitations:
612          IF ( vectorInvariantMomentum.AND.momStepping ) THEN
613           IF ( highOrderVorticity.AND.upwindVorticity ) THEN
614            WRITE(msgBuf,'(2A)') 'CONFIG_CHECK: ',
615         &   '"highOrderVorticity" conflicts with "upwindVorticity"'
616            CALL PRINT_ERROR( msgBuf, myThid )
617            STOP 'ABNORMAL END: S/R CONFIG_CHECK'
618           ENDIF
619          ENDIF
620          IF ( selectCoriMap.LT.0 .OR. selectCoriMap.GT.3 ) THEN
621            WRITE(msgBuf,'(2A,I4)') 'CONFIG_CHECK: ',
622         &       'Invalid option: selectCoriMap=', selectCoriMap
623            CALL PRINT_ERROR( msgBuf, myThid )
624            STOP 'ABNORMAL END: S/R CONFIG_CHECK'
625        ENDIF        ENDIF
 #endif /* NONLIN_FRSURF */  
626    
627        IF (.NOT.useCDscheme .AND. (tauCD.NE.0. .OR. rCD.NE.-1.) ) THEN        IF (.NOT.useCDscheme .AND. (tauCD.NE.0. .OR. rCD.NE.-1.) ) THEN
628  C- jmc: since useCDscheme is a new [04-13-03] flag (default=F),  C- jmc: since useCDscheme is a new [04-13-03] flag (default=F),
629  C       put this WARNING to stress that even if CD-scheme parameters  C       put this WARNING to stress that even if CD-scheme parameters
630  C       (tauCD,rCD) are set, CD-scheme is not used without useCDscheme=T  C       (tauCD,rCD) are set, CD-scheme is not used without useCDscheme=T
631  C-    and STOP if using mom_fluxform (following Chris advise).  C-    and STOP if using mom_fluxform (following Chris advise).
632  C- jmc: but ultimately, this block can/will be removed.  C- jmc: but ultimately, this block can/will be removed.
633         IF (.NOT.vectorInvariantMomentum.AND.momStepping) THEN         IF (.NOT.vectorInvariantMomentum.AND.momStepping) THEN
634          WRITE(msgBuf,'(A)')          WRITE(msgBuf,'(A)')
635       &   'CONFIG_CHECK: CD-scheme is OFF but params(tauCD,rCD) are set'       &   'CONFIG_CHECK: CD-scheme is OFF but params(tauCD,rCD) are set'
636          CALL PRINT_ERROR( msgBuf , myThid)          CALL PRINT_ERROR( msgBuf, myThid )
637          WRITE(msgBuf,'(2A)')          WRITE(msgBuf,'(2A)')
638       &   'CONFIG_CHECK: to turn ON CD-scheme: => "useCDscheme=.TRUE."',       &   'CONFIG_CHECK: to turn ON CD-scheme: => "useCDscheme=.TRUE."',
639       &   ' in "data", namelist PARM01'       &   ' in "data", namelist PARM01'
640          CALL PRINT_ERROR( msgBuf , myThid)          CALL PRINT_ERROR( msgBuf, myThid )
641          STOP 'ABNORMAL END: S/R CONFIG_CHECK'          STOP 'ABNORMAL END: S/R CONFIG_CHECK'
642         ENDIF         ENDIF
643          WRITE(msgBuf,'(2A)') '**WARNNING** ',          WRITE(msgBuf,'(2A)') '** WARNING ** CONFIG_CHECK: ',
644       &   'CONFIG_CHECK: CD-scheme is OFF but params(tauCD,rCD) are set'       &   'CD-scheme is OFF but params(tauCD,rCD) are set'
645          CALL PRINT_MESSAGE( msgBuf, errorMessageUnit,          CALL PRINT_MESSAGE( msgBuf, errorMessageUnit,
646       &                    SQUEEZE_RIGHT , myThid)                             &                      SQUEEZE_RIGHT, myThid )
647          WRITE(msgBuf,'(2A)')          WRITE(msgBuf,'(3A)') '** WARNING ** ',
648       &   'CONFIG_CHECK: to turn ON CD-scheme: => "useCDscheme=.TRUE."',       &   'to turn ON CD-scheme: => "useCDscheme=.TRUE."',
649       &   ' in "data", namelist PARM01'       &   ' in "data", namelist PARM01'
650            WRITE(msgBuf,'(3A)') '** WARNING ** to turn ON CD-scheme:',
651         &   ' => "useCDscheme=.TRUE." in "data", namelist PARM01'
652          CALL PRINT_MESSAGE( msgBuf, errorMessageUnit,          CALL PRINT_MESSAGE( msgBuf, errorMessageUnit,
653       &                    SQUEEZE_RIGHT , myThid)                             &                      SQUEEZE_RIGHT, myThid )
654          ENDIF
655    
656          IF ( useCDscheme .AND. useCubedSphereExchange ) THEN
657            WRITE(msgBuf,'(2A)')
658         &   'CONFIG_CHECK: CD-scheme not implemented on CubedSphere grid'
659            CALL PRINT_ERROR( msgBuf, myThid )
660    cph        STOP 'ABNORMAL END: S/R CONFIG_CHECK'
661          ENDIF
662    
663    C--   Time-stepping limitations
664          IF ( momForcingOutAB.NE.0 .AND. momForcingOutAB.NE.1 ) THEN
665            WRITE(msgBuf,'(A,I10,A)') 'CONFIG_CHECK: momForcingOutAB=',
666         &                             momForcingOutAB, ' not allowed'
667            CALL PRINT_ERROR( msgBuf, myThid )
668            WRITE(msgBuf,'(2A)') 'CONFIG_CHECK: momForcingOutAB ',
669         &                       'should be =1 (Out of AB) or =0 (In AB)'
670            CALL PRINT_ERROR( msgBuf, myThid )
671            STOP 'ABNORMAL END: S/R CONFIG_CHECK'
672          ENDIF
673          IF ( tracForcingOutAB.NE.0 .AND. tracForcingOutAB.NE.1 ) THEN
674            WRITE(msgBuf,'(A,I10,A)') 'CONFIG_CHECK: tracForcingOutAB=',
675         &                             tracForcingOutAB, ' not allowed'
676            CALL PRINT_ERROR( msgBuf, myThid )
677            WRITE(msgBuf,'(2A)') 'CONFIG_CHECK: tracForcingOutAB ',
678         &                       'should be =1 (Out of AB) or =0 (In AB)'
679            CALL PRINT_ERROR( msgBuf, myThid )
680            STOP 'ABNORMAL END: S/R CONFIG_CHECK'
681          ENDIF
682    
683    C--   Grid limitations:
684          IF ( rotateGrid ) THEN
685           IF ( .NOT. usingSphericalPolarGrid ) THEN
686            WRITE(msgBuf,'(2A)')
687         &       'CONFIG_CHECK: specifying Euler angles makes only ',
688         &       'sense with usingSphericalGrid=.TRUE.'
689            CALL PRINT_ERROR( msgBuf, myThid )
690            STOP 'ABNORMAL END: S/R CONFIG_CHECK'
691           ENDIF
692           IF ( useFLT .OR. useZonal_Filt .OR. useECCO ) THEN
693            WRITE(msgBuf,'(2A)')
694         &       'CONFIG_CHECK: specifying Euler angles will probably ',
695         &       'not work with pkgs FLT, ZONAL_FLT, ECCO'
696            CALL PRINT_ERROR( msgBuf, myThid )
697            STOP 'ABNORMAL END: S/R CONFIG_CHECK'
698           ENDIF
699    #ifdef ALLOW_PROFILES
700            WRITE(msgBuf,'(2A)')
701         &       'CONFIG_CHECK: specifying Euler angles will probably ',
702         &       'not work with pkg profiles'
703            CALL PRINT_ERROR( msgBuf, myThid )
704            STOP 'ABNORMAL END: S/R CONFIG_CHECK'
705    #endif /* ALLOW_PROFILES */
706          ENDIF
707    
708    C--   Packages conflict
709          IF ( useMATRIX .AND. useGCHEM ) THEN
710            WRITE(msgBuf,'(2A)')
711         &   'CONFIG_CHECK: cannot set both: useMATRIX & useGCHEM'
712            CALL PRINT_ERROR( msgBuf, myThid )
713            STOP 'ABNORMAL END: S/R CONFIG_CHECK'
714          ENDIF
715    
716          IF ( useMATRIX .AND. .NOT.usePTRACERS ) THEN
717            WRITE(msgBuf,'(2A)')
718         &       'CONFIG_CHECK: cannot set useMATRIX without ',
719         &       'setting usePTRACERS'
720            CALL PRINT_ERROR( msgBuf, myThid )
721            STOP 'ABNORMAL END: S/R CONFIG_CHECK'
722          ENDIF
723    
724          IF ( (useSEAICE .OR. useThSIce) .AND. allowFreezing ) THEN
725            WRITE(msgBuf,'(2A)')
726         &       'CONFIG_CHECK: cannot set allowFreezing',
727         &       ' with pkgs SEAICE or THSICE'
728            CALL PRINT_ERROR( msgBuf, myThid )
729            STOP 'ABNORMAL END: S/R CONFIG_CHECK'
730        ENDIF        ENDIF
731    
732        WRITE(msgBuf,'(A)') 'CONFIG_CHECK: OK'        WRITE(msgBuf,'(A)')
733        CALL PRINT_MESSAGE(msgBuf,standardMessageUnit,       &'// ======================================================='
734       &                   SQUEEZE_RIGHT,myThid)        CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,
735         &                    SQUEEZE_RIGHT, myThid )
736          WRITE(msgBuf,'(A)') '// CONFIG_CHECK : Normal End'
737          CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,
738         &                    SQUEEZE_RIGHT, myThid )
739          WRITE(msgBuf,'(A)')
740         &'// ======================================================='
741          CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,
742         &                    SQUEEZE_RIGHT, myThid )
743          WRITE(msgBuf,'(A)') ' '
744          CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,
745         &                    SQUEEZE_RIGHT, myThid )
746    
747        RETURN        RETURN
748        END        END

Legend:
Removed from v.1.8.2.2  
changed lines
  Added in v.1.60

  ViewVC Help
Powered by ViewVC 1.1.22