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

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

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


Revision 1.80 - (hide annotations) (download)
Thu Jan 22 18:30:00 2015 UTC (9 years, 4 months ago) by jmc
Branch: MAIN
CVS Tags: checkpoint65j, checkpoint65k, checkpoint65i, checkpoint65l, checkpoint65m
Changes since 1.79: +1 -7 lines
remove the stop for addFrictionHeating with not synchronous time-stepping

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

  ViewVC Help
Powered by ViewVC 1.1.22