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

Legend:
Removed from v.1.1  
changed lines
  Added in v.1.71

  ViewVC Help
Powered by ViewVC 1.1.22